Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ d99012a6

History | View | Annotate | Download (5.1 kB)

1
{-| ConstantUtils contains the helper functions for constants
2

    
3
This module cannot be merged with 'Ganeti.Utils' because it would
4
create a circular dependency if imported, for example, from
5
'Ganeti.Constants'.
6

    
7
-}
8

    
9
{-
10

    
11
Copyright (C) 2013 Google Inc.
12

    
13
This program is free software; you can redistribute it and/or modify
14
it under the terms of the GNU General Public License as published by
15
the Free Software Foundation; either version 2 of the License, or
16
(at your option) any later version.
17

    
18
This program is distributed in the hope that it will be useful, but
19
WITHOUT ANY WARRANTY; without even the implied warranty of
20
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21
General Public License for more details.
22

    
23
You should have received a copy of the GNU General Public License
24
along with this program; if not, write to the Free Software
25
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26
02110-1301, USA.
27

    
28
-}
29
module Ganeti.ConstantUtils where
30

    
31
import Data.Char (ord)
32
import Data.Set (Set)
33
import qualified Data.Set as Set (fromList, toList, union)
34

    
35
import Ganeti.THH (PyValue(..))
36
import Ganeti.PyValueInstances ()
37

    
38
-- | PythonChar wraps a Python 'char'
39
newtype PythonChar = PythonChar { unPythonChar :: Char }
40
  deriving (Show)
41

    
42
instance PyValue PythonChar where
43
  showValue c = "chr(" ++ show (ord (unPythonChar c)) ++ ")"
44

    
45
-- | FrozenSet wraps a Haskell 'Set'
46
--
47
-- See 'PyValue' instance for 'FrozenSet'.
48
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
49
  deriving (Eq, Show)
50

    
51
-- | Converts a Haskell 'Set' into a Python 'frozenset'
52
--
53
-- This instance was supposed to be for 'Set' instead of 'FrozenSet'.
54
-- However, 'ghc-6.12.1' seems to be crashing with 'segmentation
55
-- fault' due to the presence of more than one instance of 'Set',
56
-- namely, this one and the one in 'Ganeti.OpCodes'.  For this reason,
57
-- we wrap 'Set' into 'FrozenSet'.
58
instance PyValue a => PyValue (FrozenSet a) where
59
  showValue s = "frozenset(" ++ showValue (Set.toList (unFrozenSet s)) ++ ")"
60

    
61
mkSet :: Ord a => [a] -> FrozenSet a
62
mkSet = FrozenSet . Set.fromList
63

    
64
union :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
65
union x y = FrozenSet (unFrozenSet x `Set.union` unFrozenSet y)
66

    
67
-- | 'Protocol' represents the protocols used by the daemons
68
data Protocol = Tcp | Udp
69
  deriving (Show)
70

    
71
-- | 'PyValue' instance of 'Protocol'
72
--
73
-- This instance is used by the Haskell to Python constants
74
instance PyValue Protocol where
75
  showValue Tcp = "\"tcp\""
76
  showValue Udp = "\"udp\""
77

    
78
-- | Failure exit code
79
--
80
-- These are defined here and not in 'Ganeti.HsConstants' together with
81
-- the other exit codes in order to avoid a circular dependency
82
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
83
exitFailure :: Int
84
exitFailure = 1
85

    
86
-- | Console device
87
--
88
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
89
-- a circular dependency between 'Ganeti.HsConstants' and
90
-- 'Ganeti.Logging'
91
devConsole :: String
92
devConsole = "/dev/console"
93

    
94
-- | Random uuid generator
95
--
96
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
97
-- a circular dependendy between 'Ganeti.HsConstants' and
98
-- 'Ganeti.Types'
99
randomUuidFile :: String
100
randomUuidFile = "/proc/sys/kernel/random/uuid"
101

    
102
-- * Priority levels
103
--
104
-- This is defined here and not in 'Ganeti.Types' in order to avoid a
105
-- GHC stage restriction and because there is no suitable 'declareADT'
106
-- variant that handles integer values directly.
107

    
108
priorityLow :: Int
109
priorityLow = 10
110

    
111
priorityNormal :: Int
112
priorityNormal = 0
113

    
114
priorityHigh :: Int
115
priorityHigh = -10
116

    
117
-- | Calculates int version number from major, minor and revision
118
-- numbers.
119
buildVersion :: Int -> Int -> Int -> Int
120
buildVersion major minor revision =
121
  1000000 * major + 10000 * minor + 1 * revision
122

    
123
-- | Confd protocol version
124
--
125
-- This is defined here in order to avoid a circular dependency
126
-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
127
confdProtocolVersion :: Int
128
confdProtocolVersion = 1
129

    
130
-- * Confd request query fields
131
--
132
-- These are defined here and not in 'Ganeti.Types' due to GHC stage
133
-- restrictions concerning Template Haskell.  They are also not
134
-- defined in 'Ganeti.HsConstants' in order to avoid a circular
135
-- dependency between that module and 'Ganeti.Types'.
136

    
137
confdReqqLink :: String
138
confdReqqLink = "0"
139

    
140
confdReqqIp :: String
141
confdReqqIp = "1"
142

    
143
confdReqqIplist :: String
144
confdReqqIplist = "2"
145

    
146
confdReqqFields :: String
147
confdReqqFields = "3"
148

    
149
-- * ISpec
150

    
151
ispecMemSize :: String
152
ispecMemSize = "memory-size"
153

    
154
ispecCpuCount :: String
155
ispecCpuCount = "cpu-count"
156

    
157
ispecDiskCount :: String
158
ispecDiskCount = "disk-count"
159

    
160
ispecDiskSize :: String
161
ispecDiskSize = "disk-size"
162

    
163
ispecNicCount :: String
164
ispecNicCount = "nic-count"
165

    
166
ispecSpindleUse :: String
167
ispecSpindleUse = "spindle-use"
168

    
169
ispecsMinmax :: String
170
ispecsMinmax = "minmax"
171

    
172
ispecsStd :: String
173
ispecsStd = "std"
174

    
175
ipolicyDts :: String
176
ipolicyDts = "disk-templates"
177

    
178
ipolicyVcpuRatio :: String
179
ipolicyVcpuRatio = "vcpu-ratio"
180

    
181
ipolicySpindleRatio :: String
182
ipolicySpindleRatio = "spindle-ratio"
183

    
184
ipolicyDefaultsVcpuRatio :: Double
185
ipolicyDefaultsVcpuRatio = 4.0
186

    
187
ipolicyDefaultsSpindleRatio :: Double
188
ipolicyDefaultsSpindleRatio = 32.0