Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ cdac0552

History | View | Annotate | Download (4 kB)

1 f2b6e7d4 Jose A. Lopes
{-| ConstantUtils contains the helper functions for constants
2 f2b6e7d4 Jose A. Lopes
3 f2b6e7d4 Jose A. Lopes
This module cannot be merged with 'Ganeti.Utils' because it would
4 f2b6e7d4 Jose A. Lopes
create a circular dependency if imported, for example, from
5 f2b6e7d4 Jose A. Lopes
'Ganeti.Constants'.
6 f2b6e7d4 Jose A. Lopes
7 f2b6e7d4 Jose A. Lopes
-}
8 f2b6e7d4 Jose A. Lopes
9 f2b6e7d4 Jose A. Lopes
{-
10 f2b6e7d4 Jose A. Lopes
11 f2b6e7d4 Jose A. Lopes
Copyright (C) 2013 Google Inc.
12 f2b6e7d4 Jose A. Lopes
13 f2b6e7d4 Jose A. Lopes
This program is free software; you can redistribute it and/or modify
14 f2b6e7d4 Jose A. Lopes
it under the terms of the GNU General Public License as published by
15 f2b6e7d4 Jose A. Lopes
the Free Software Foundation; either version 2 of the License, or
16 f2b6e7d4 Jose A. Lopes
(at your option) any later version.
17 f2b6e7d4 Jose A. Lopes
18 f2b6e7d4 Jose A. Lopes
This program is distributed in the hope that it will be useful, but
19 f2b6e7d4 Jose A. Lopes
WITHOUT ANY WARRANTY; without even the implied warranty of
20 f2b6e7d4 Jose A. Lopes
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 f2b6e7d4 Jose A. Lopes
General Public License for more details.
22 f2b6e7d4 Jose A. Lopes
23 f2b6e7d4 Jose A. Lopes
You should have received a copy of the GNU General Public License
24 f2b6e7d4 Jose A. Lopes
along with this program; if not, write to the Free Software
25 f2b6e7d4 Jose A. Lopes
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 f2b6e7d4 Jose A. Lopes
02110-1301, USA.
27 f2b6e7d4 Jose A. Lopes
28 f2b6e7d4 Jose A. Lopes
-}
29 f2b6e7d4 Jose A. Lopes
module Ganeti.ConstantUtils where
30 f2b6e7d4 Jose A. Lopes
31 f2b6e7d4 Jose A. Lopes
import Data.Set (Set)
32 f2b6e7d4 Jose A. Lopes
import qualified Data.Set as Set (fromList, toList)
33 f2b6e7d4 Jose A. Lopes
34 f2b6e7d4 Jose A. Lopes
import Ganeti.THH (PyValue(..))
35 f2b6e7d4 Jose A. Lopes
import Ganeti.PyValueInstances ()
36 f2b6e7d4 Jose A. Lopes
37 f2b6e7d4 Jose A. Lopes
-- | FrozenSet wraps a Haskell 'Set'
38 f2b6e7d4 Jose A. Lopes
--
39 f2b6e7d4 Jose A. Lopes
-- See 'PyValue' instance for 'FrozenSet'.
40 f2b6e7d4 Jose A. Lopes
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
41 f361a6ee Jose A. Lopes
  deriving (Eq, Show)
42 f2b6e7d4 Jose A. Lopes
43 f2b6e7d4 Jose A. Lopes
-- | Converts a Haskell 'Set' into a Python 'frozenset'
44 f2b6e7d4 Jose A. Lopes
--
45 f2b6e7d4 Jose A. Lopes
-- This instance was supposed to be for 'Set' instead of 'FrozenSet'.
46 f2b6e7d4 Jose A. Lopes
-- However, 'ghc-6.12.1' seems to be crashing with 'segmentation
47 f2b6e7d4 Jose A. Lopes
-- fault' due to the presence of more than one instance of 'Set',
48 f2b6e7d4 Jose A. Lopes
-- namely, this one and the one in 'Ganeti.OpCodes'.  For this reason,
49 f2b6e7d4 Jose A. Lopes
-- we wrap 'Set' into 'FrozenSet'.
50 f2b6e7d4 Jose A. Lopes
instance PyValue a => PyValue (FrozenSet a) where
51 f2b6e7d4 Jose A. Lopes
  showValue s = "frozenset(" ++ showValue (Set.toList (unFrozenSet s)) ++ ")"
52 f2b6e7d4 Jose A. Lopes
53 f2b6e7d4 Jose A. Lopes
mkSet :: Ord a => [a] -> FrozenSet a
54 f2b6e7d4 Jose A. Lopes
mkSet = FrozenSet . Set.fromList
55 cd0359bc Jose A. Lopes
56 cd0359bc Jose A. Lopes
-- | 'Protocol' represents the protocols used by the daemons
57 cd0359bc Jose A. Lopes
data Protocol = Tcp | Udp
58 cd0359bc Jose A. Lopes
  deriving (Show)
59 cd0359bc Jose A. Lopes
60 cd0359bc Jose A. Lopes
-- | 'PyValue' instance of 'Protocol'
61 cd0359bc Jose A. Lopes
--
62 cd0359bc Jose A. Lopes
-- This instance is used by the Haskell to Python constants
63 cd0359bc Jose A. Lopes
instance PyValue Protocol where
64 cd0359bc Jose A. Lopes
  showValue Tcp = "\"tcp\""
65 cd0359bc Jose A. Lopes
  showValue Udp = "\"udp\""
66 1c31b263 Jose A. Lopes
67 1c31b263 Jose A. Lopes
-- | Failure exit code
68 1c31b263 Jose A. Lopes
--
69 8e4e0268 Jose A. Lopes
-- These are defined here and not in 'Ganeti.HsConstants' together with
70 1c31b263 Jose A. Lopes
-- the other exit codes in order to avoid a circular dependency
71 1c31b263 Jose A. Lopes
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
72 1c31b263 Jose A. Lopes
exitFailure :: Int
73 1c31b263 Jose A. Lopes
exitFailure = 1
74 df726590 Jose A. Lopes
75 df726590 Jose A. Lopes
-- | Console device
76 df726590 Jose A. Lopes
--
77 df726590 Jose A. Lopes
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
78 df726590 Jose A. Lopes
-- a circular dependency between 'Ganeti.HsConstants' and
79 df726590 Jose A. Lopes
-- 'Ganeti.Logging'
80 df726590 Jose A. Lopes
devConsole :: String
81 df726590 Jose A. Lopes
devConsole = "/dev/console"
82 72e18df1 Jose A. Lopes
83 06fd57e5 Jose A. Lopes
-- | Random uuid generator
84 06fd57e5 Jose A. Lopes
--
85 06fd57e5 Jose A. Lopes
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
86 06fd57e5 Jose A. Lopes
-- a circular dependendy between 'Ganeti.HsConstants' and
87 06fd57e5 Jose A. Lopes
-- 'Ganeti.Types'
88 06fd57e5 Jose A. Lopes
randomUuidFile :: String
89 06fd57e5 Jose A. Lopes
randomUuidFile = "/proc/sys/kernel/random/uuid"
90 06fd57e5 Jose A. Lopes
91 8e4e0268 Jose A. Lopes
-- * Priority levels
92 72e18df1 Jose A. Lopes
--
93 8e4e0268 Jose A. Lopes
-- This is defined here and not in 'Ganeti.Types' in order to avoid a
94 8e4e0268 Jose A. Lopes
-- GHC stage restriction and because there is no suitable 'declareADT'
95 72e18df1 Jose A. Lopes
-- variant that handles integer values directly.
96 8e4e0268 Jose A. Lopes
97 72e18df1 Jose A. Lopes
priorityLow :: Int
98 72e18df1 Jose A. Lopes
priorityLow = 10
99 72e18df1 Jose A. Lopes
100 72e18df1 Jose A. Lopes
priorityNormal :: Int
101 72e18df1 Jose A. Lopes
priorityNormal = 0
102 72e18df1 Jose A. Lopes
103 72e18df1 Jose A. Lopes
priorityHigh :: Int
104 72e18df1 Jose A. Lopes
priorityHigh = -10
105 b78d0757 Jose A. Lopes
106 b78d0757 Jose A. Lopes
-- | Calculates int version number from major, minor and revision
107 b78d0757 Jose A. Lopes
-- numbers.
108 b78d0757 Jose A. Lopes
buildVersion :: Int -> Int -> Int -> Int
109 b78d0757 Jose A. Lopes
buildVersion major minor revision =
110 b78d0757 Jose A. Lopes
  1000000 * major + 10000 * minor + 1 * revision
111 8e4e0268 Jose A. Lopes
112 cdac0552 Jose A. Lopes
-- | Confd protocol version
113 cdac0552 Jose A. Lopes
--
114 cdac0552 Jose A. Lopes
-- This is defined here in order to avoid a circular dependency
115 cdac0552 Jose A. Lopes
-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
116 cdac0552 Jose A. Lopes
confdProtocolVersion :: Int
117 cdac0552 Jose A. Lopes
confdProtocolVersion = 1
118 cdac0552 Jose A. Lopes
119 8e4e0268 Jose A. Lopes
-- * Confd request query fields.
120 8e4e0268 Jose A. Lopes
--
121 8e4e0268 Jose A. Lopes
-- These are defined here and not in 'Ganeti.Types' due to GHC stage
122 8e4e0268 Jose A. Lopes
-- restrictions concerning Template Haskell.  They are also not
123 8e4e0268 Jose A. Lopes
-- defined in 'Ganeti.HsConstants' in order to avoid a circular
124 8e4e0268 Jose A. Lopes
-- dependency between that module and 'Ganeti.Types'.
125 8e4e0268 Jose A. Lopes
126 8e4e0268 Jose A. Lopes
confdReqqLink :: String
127 8e4e0268 Jose A. Lopes
confdReqqLink = "0"
128 8e4e0268 Jose A. Lopes
129 8e4e0268 Jose A. Lopes
confdReqqIp :: String
130 8e4e0268 Jose A. Lopes
confdReqqIp = "1"
131 8e4e0268 Jose A. Lopes
132 8e4e0268 Jose A. Lopes
confdReqqIplist :: String
133 8e4e0268 Jose A. Lopes
confdReqqIplist = "2"
134 8e4e0268 Jose A. Lopes
135 8e4e0268 Jose A. Lopes
confdReqqFields :: String
136 8e4e0268 Jose A. Lopes
confdReqqFields = "3"