Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ 88ac4075

History | View | Annotate | Download (5.4 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 (difference, 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
-- | 'PythonNone' wraps Python 'None'
46
data PythonNone = PythonNone
47

    
48
instance PyValue PythonNone where
49
  showValue _ = "None"
50

    
51
-- | FrozenSet wraps a Haskell 'Set'
52
--
53
-- See 'PyValue' instance for 'FrozenSet'.
54
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
55
  deriving (Eq, Ord, Show)
56

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

    
67
mkSet :: Ord a => [a] -> FrozenSet a
68
mkSet = FrozenSet . Set.fromList
69

    
70
toList :: FrozenSet a -> [a]
71
toList = Set.toList . unFrozenSet
72

    
73
union :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
74
union x y = FrozenSet (unFrozenSet x `Set.union` unFrozenSet y)
75

    
76
difference :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
77
difference x y = FrozenSet (unFrozenSet x `Set.difference` unFrozenSet y)
78

    
79
-- | 'Protocol' represents the protocols used by the daemons
80
data Protocol = Tcp | Udp
81
  deriving (Show)
82

    
83
-- | 'PyValue' instance of 'Protocol'
84
--
85
-- This instance is used by the Haskell to Python constants
86
instance PyValue Protocol where
87
  showValue Tcp = "\"tcp\""
88
  showValue Udp = "\"udp\""
89

    
90
-- | Failure exit code
91
--
92
-- These are defined here and not in 'Ganeti.HsConstants' together with
93
-- the other exit codes in order to avoid a circular dependency
94
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
95
exitFailure :: Int
96
exitFailure = 1
97

    
98
-- | Console device
99
--
100
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
101
-- a circular dependency between 'Ganeti.HsConstants' and
102
-- 'Ganeti.Logging'
103
devConsole :: String
104
devConsole = "/dev/console"
105

    
106
-- | Random uuid generator
107
--
108
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
109
-- a circular dependendy between 'Ganeti.HsConstants' and
110
-- 'Ganeti.Types'
111
randomUuidFile :: String
112
randomUuidFile = "/proc/sys/kernel/random/uuid"
113

    
114
-- * Priority levels
115
--
116
-- This is defined here and not in 'Ganeti.Types' in order to avoid a
117
-- GHC stage restriction and because there is no suitable 'declareADT'
118
-- variant that handles integer values directly.
119

    
120
priorityLow :: Int
121
priorityLow = 10
122

    
123
priorityNormal :: Int
124
priorityNormal = 0
125

    
126
priorityHigh :: Int
127
priorityHigh = -10
128

    
129
-- | Calculates int version number from major, minor and revision
130
-- numbers.
131
buildVersion :: Int -> Int -> Int -> Int
132
buildVersion major minor revision =
133
  1000000 * major + 10000 * minor + 1 * revision
134

    
135
-- | Confd protocol version
136
--
137
-- This is defined here in order to avoid a circular dependency
138
-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
139
confdProtocolVersion :: Int
140
confdProtocolVersion = 1
141

    
142
-- * Confd request query fields
143
--
144
-- These are defined here and not in 'Ganeti.Types' due to GHC stage
145
-- restrictions concerning Template Haskell.  They are also not
146
-- defined in 'Ganeti.HsConstants' in order to avoid a circular
147
-- dependency between that module and 'Ganeti.Types'.
148

    
149
confdReqqLink :: String
150
confdReqqLink = "0"
151

    
152
confdReqqIp :: String
153
confdReqqIp = "1"
154

    
155
confdReqqIplist :: String
156
confdReqqIplist = "2"
157

    
158
confdReqqFields :: String
159
confdReqqFields = "3"
160

    
161
-- * ISpec
162

    
163
ispecMemSize :: String
164
ispecMemSize = "memory-size"
165

    
166
ispecCpuCount :: String
167
ispecCpuCount = "cpu-count"
168

    
169
ispecDiskCount :: String
170
ispecDiskCount = "disk-count"
171

    
172
ispecDiskSize :: String
173
ispecDiskSize = "disk-size"
174

    
175
ispecNicCount :: String
176
ispecNicCount = "nic-count"
177

    
178
ispecSpindleUse :: String
179
ispecSpindleUse = "spindle-use"
180

    
181
ispecsMinmax :: String
182
ispecsMinmax = "minmax"
183

    
184
ispecsStd :: String
185
ispecsStd = "std"
186

    
187
ipolicyDts :: String
188
ipolicyDts = "disk-templates"
189

    
190
ipolicyVcpuRatio :: String
191
ipolicyVcpuRatio = "vcpu-ratio"
192

    
193
ipolicySpindleRatio :: String
194
ipolicySpindleRatio = "spindle-ratio"
195

    
196
ipolicyDefaultsVcpuRatio :: Double
197
ipolicyDefaultsVcpuRatio = 4.0
198

    
199
ipolicyDefaultsSpindleRatio :: Double
200
ipolicyDefaultsSpindleRatio = 32.0