Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ 07e68848

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