Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ a91d6b30

History | View | Annotate | Download (5.1 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 5d4e1402 Jose A. Lopes
import Data.Char (ord)
32 f2b6e7d4 Jose A. Lopes
import Data.Set (Set)
33 4c1275f9 Jose A. Lopes
import qualified Data.Set as Set (fromList, toList, union)
34 f2b6e7d4 Jose A. Lopes
35 f2b6e7d4 Jose A. Lopes
import Ganeti.THH (PyValue(..))
36 f2b6e7d4 Jose A. Lopes
import Ganeti.PyValueInstances ()
37 f2b6e7d4 Jose A. Lopes
38 5d4e1402 Jose A. Lopes
-- | PythonChar wraps a Python 'char'
39 5d4e1402 Jose A. Lopes
newtype PythonChar = PythonChar { unPythonChar :: Char }
40 5d4e1402 Jose A. Lopes
  deriving (Show)
41 5d4e1402 Jose A. Lopes
42 5d4e1402 Jose A. Lopes
instance PyValue PythonChar where
43 5d4e1402 Jose A. Lopes
  showValue c = "chr(" ++ show (ord (unPythonChar c)) ++ ")"
44 5d4e1402 Jose A. Lopes
45 f2b6e7d4 Jose A. Lopes
-- | FrozenSet wraps a Haskell 'Set'
46 f2b6e7d4 Jose A. Lopes
--
47 f2b6e7d4 Jose A. Lopes
-- See 'PyValue' instance for 'FrozenSet'.
48 f2b6e7d4 Jose A. Lopes
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
49 f361a6ee Jose A. Lopes
  deriving (Eq, Show)
50 f2b6e7d4 Jose A. Lopes
51 f2b6e7d4 Jose A. Lopes
-- | Converts a Haskell 'Set' into a Python 'frozenset'
52 f2b6e7d4 Jose A. Lopes
--
53 f2b6e7d4 Jose A. Lopes
-- This instance was supposed to be for 'Set' instead of 'FrozenSet'.
54 f2b6e7d4 Jose A. Lopes
-- However, 'ghc-6.12.1' seems to be crashing with 'segmentation
55 f2b6e7d4 Jose A. Lopes
-- fault' due to the presence of more than one instance of 'Set',
56 f2b6e7d4 Jose A. Lopes
-- namely, this one and the one in 'Ganeti.OpCodes'.  For this reason,
57 f2b6e7d4 Jose A. Lopes
-- we wrap 'Set' into 'FrozenSet'.
58 f2b6e7d4 Jose A. Lopes
instance PyValue a => PyValue (FrozenSet a) where
59 f2b6e7d4 Jose A. Lopes
  showValue s = "frozenset(" ++ showValue (Set.toList (unFrozenSet s)) ++ ")"
60 f2b6e7d4 Jose A. Lopes
61 f2b6e7d4 Jose A. Lopes
mkSet :: Ord a => [a] -> FrozenSet a
62 f2b6e7d4 Jose A. Lopes
mkSet = FrozenSet . Set.fromList
63 cd0359bc Jose A. Lopes
64 4c1275f9 Jose A. Lopes
union :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
65 4c1275f9 Jose A. Lopes
union x y = FrozenSet (unFrozenSet x `Set.union` unFrozenSet y)
66 4c1275f9 Jose A. Lopes
67 cd0359bc Jose A. Lopes
-- | 'Protocol' represents the protocols used by the daemons
68 cd0359bc Jose A. Lopes
data Protocol = Tcp | Udp
69 cd0359bc Jose A. Lopes
  deriving (Show)
70 cd0359bc Jose A. Lopes
71 cd0359bc Jose A. Lopes
-- | 'PyValue' instance of 'Protocol'
72 cd0359bc Jose A. Lopes
--
73 cd0359bc Jose A. Lopes
-- This instance is used by the Haskell to Python constants
74 cd0359bc Jose A. Lopes
instance PyValue Protocol where
75 cd0359bc Jose A. Lopes
  showValue Tcp = "\"tcp\""
76 cd0359bc Jose A. Lopes
  showValue Udp = "\"udp\""
77 1c31b263 Jose A. Lopes
78 1c31b263 Jose A. Lopes
-- | Failure exit code
79 1c31b263 Jose A. Lopes
--
80 8e4e0268 Jose A. Lopes
-- These are defined here and not in 'Ganeti.HsConstants' together with
81 1c31b263 Jose A. Lopes
-- the other exit codes in order to avoid a circular dependency
82 1c31b263 Jose A. Lopes
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
83 1c31b263 Jose A. Lopes
exitFailure :: Int
84 1c31b263 Jose A. Lopes
exitFailure = 1
85 df726590 Jose A. Lopes
86 df726590 Jose A. Lopes
-- | Console device
87 df726590 Jose A. Lopes
--
88 df726590 Jose A. Lopes
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
89 df726590 Jose A. Lopes
-- a circular dependency between 'Ganeti.HsConstants' and
90 df726590 Jose A. Lopes
-- 'Ganeti.Logging'
91 df726590 Jose A. Lopes
devConsole :: String
92 df726590 Jose A. Lopes
devConsole = "/dev/console"
93 72e18df1 Jose A. Lopes
94 06fd57e5 Jose A. Lopes
-- | Random uuid generator
95 06fd57e5 Jose A. Lopes
--
96 06fd57e5 Jose A. Lopes
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
97 06fd57e5 Jose A. Lopes
-- a circular dependendy between 'Ganeti.HsConstants' and
98 06fd57e5 Jose A. Lopes
-- 'Ganeti.Types'
99 06fd57e5 Jose A. Lopes
randomUuidFile :: String
100 06fd57e5 Jose A. Lopes
randomUuidFile = "/proc/sys/kernel/random/uuid"
101 06fd57e5 Jose A. Lopes
102 8e4e0268 Jose A. Lopes
-- * Priority levels
103 72e18df1 Jose A. Lopes
--
104 8e4e0268 Jose A. Lopes
-- This is defined here and not in 'Ganeti.Types' in order to avoid a
105 8e4e0268 Jose A. Lopes
-- GHC stage restriction and because there is no suitable 'declareADT'
106 72e18df1 Jose A. Lopes
-- variant that handles integer values directly.
107 8e4e0268 Jose A. Lopes
108 72e18df1 Jose A. Lopes
priorityLow :: Int
109 72e18df1 Jose A. Lopes
priorityLow = 10
110 72e18df1 Jose A. Lopes
111 72e18df1 Jose A. Lopes
priorityNormal :: Int
112 72e18df1 Jose A. Lopes
priorityNormal = 0
113 72e18df1 Jose A. Lopes
114 72e18df1 Jose A. Lopes
priorityHigh :: Int
115 72e18df1 Jose A. Lopes
priorityHigh = -10
116 b78d0757 Jose A. Lopes
117 b78d0757 Jose A. Lopes
-- | Calculates int version number from major, minor and revision
118 b78d0757 Jose A. Lopes
-- numbers.
119 b78d0757 Jose A. Lopes
buildVersion :: Int -> Int -> Int -> Int
120 b78d0757 Jose A. Lopes
buildVersion major minor revision =
121 b78d0757 Jose A. Lopes
  1000000 * major + 10000 * minor + 1 * revision
122 8e4e0268 Jose A. Lopes
123 cdac0552 Jose A. Lopes
-- | Confd protocol version
124 cdac0552 Jose A. Lopes
--
125 cdac0552 Jose A. Lopes
-- This is defined here in order to avoid a circular dependency
126 cdac0552 Jose A. Lopes
-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
127 cdac0552 Jose A. Lopes
confdProtocolVersion :: Int
128 cdac0552 Jose A. Lopes
confdProtocolVersion = 1
129 cdac0552 Jose A. Lopes
130 cc6a469e Jose A. Lopes
-- * Confd request query fields
131 8e4e0268 Jose A. Lopes
--
132 8e4e0268 Jose A. Lopes
-- These are defined here and not in 'Ganeti.Types' due to GHC stage
133 8e4e0268 Jose A. Lopes
-- restrictions concerning Template Haskell.  They are also not
134 8e4e0268 Jose A. Lopes
-- defined in 'Ganeti.HsConstants' in order to avoid a circular
135 8e4e0268 Jose A. Lopes
-- dependency between that module and 'Ganeti.Types'.
136 8e4e0268 Jose A. Lopes
137 8e4e0268 Jose A. Lopes
confdReqqLink :: String
138 8e4e0268 Jose A. Lopes
confdReqqLink = "0"
139 8e4e0268 Jose A. Lopes
140 8e4e0268 Jose A. Lopes
confdReqqIp :: String
141 8e4e0268 Jose A. Lopes
confdReqqIp = "1"
142 8e4e0268 Jose A. Lopes
143 8e4e0268 Jose A. Lopes
confdReqqIplist :: String
144 8e4e0268 Jose A. Lopes
confdReqqIplist = "2"
145 8e4e0268 Jose A. Lopes
146 8e4e0268 Jose A. Lopes
confdReqqFields :: String
147 8e4e0268 Jose A. Lopes
confdReqqFields = "3"
148 8397ffde Jose A. Lopes
149 8397ffde Jose A. Lopes
-- * ISpec
150 8397ffde Jose A. Lopes
151 8397ffde Jose A. Lopes
ispecMemSize :: String
152 8397ffde Jose A. Lopes
ispecMemSize = "memory-size"
153 8397ffde Jose A. Lopes
154 8397ffde Jose A. Lopes
ispecCpuCount :: String
155 8397ffde Jose A. Lopes
ispecCpuCount = "cpu-count"
156 8397ffde Jose A. Lopes
157 8397ffde Jose A. Lopes
ispecDiskCount :: String
158 8397ffde Jose A. Lopes
ispecDiskCount = "disk-count"
159 8397ffde Jose A. Lopes
160 8397ffde Jose A. Lopes
ispecDiskSize :: String
161 8397ffde Jose A. Lopes
ispecDiskSize = "disk-size"
162 8397ffde Jose A. Lopes
163 8397ffde Jose A. Lopes
ispecNicCount :: String
164 8397ffde Jose A. Lopes
ispecNicCount = "nic-count"
165 8397ffde Jose A. Lopes
166 8397ffde Jose A. Lopes
ispecSpindleUse :: String
167 8397ffde Jose A. Lopes
ispecSpindleUse = "spindle-use"
168 8397ffde Jose A. Lopes
169 8397ffde Jose A. Lopes
ispecsMinmax :: String
170 8397ffde Jose A. Lopes
ispecsMinmax = "minmax"
171 8397ffde Jose A. Lopes
172 8397ffde Jose A. Lopes
ispecsStd :: String
173 8397ffde Jose A. Lopes
ispecsStd = "std"
174 8397ffde Jose A. Lopes
175 8397ffde Jose A. Lopes
ipolicyDts :: String
176 8397ffde Jose A. Lopes
ipolicyDts = "disk-templates"
177 8397ffde Jose A. Lopes
178 8397ffde Jose A. Lopes
ipolicyVcpuRatio :: String
179 8397ffde Jose A. Lopes
ipolicyVcpuRatio = "vcpu-ratio"
180 8397ffde Jose A. Lopes
181 8397ffde Jose A. Lopes
ipolicySpindleRatio :: String
182 8397ffde Jose A. Lopes
ipolicySpindleRatio = "spindle-ratio"
183 8397ffde Jose A. Lopes
184 8397ffde Jose A. Lopes
ipolicyDefaultsVcpuRatio :: Double
185 8397ffde Jose A. Lopes
ipolicyDefaultsVcpuRatio = 4.0
186 8397ffde Jose A. Lopes
187 8397ffde Jose A. Lopes
ipolicyDefaultsSpindleRatio :: Double
188 8397ffde Jose A. Lopes
ipolicyDefaultsSpindleRatio = 32.0