Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ b9202225

History | View | Annotate | Download (5.3 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.PyValue
36

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

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

    
44
-- | 'PythonNone' wraps Python 'None'
45
data PythonNone = PythonNone
46

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

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

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

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

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

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

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

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

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

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

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

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

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

    
117
priorityLow :: Int
118
priorityLow = 10
119

    
120
priorityNormal :: Int
121
priorityNormal = 0
122

    
123
priorityHigh :: Int
124
priorityHigh = -10
125

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

    
132
-- | Confd protocol version
133
--
134
-- This is defined here in order to avoid a circular dependency
135
-- between 'Ganeti.Confd.Types' and 'Ganeti.Constants'.
136
confdProtocolVersion :: Int
137
confdProtocolVersion = 1
138

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

    
146
confdReqqLink :: String
147
confdReqqLink = "0"
148

    
149
confdReqqIp :: String
150
confdReqqIp = "1"
151

    
152
confdReqqIplist :: String
153
confdReqqIplist = "2"
154

    
155
confdReqqFields :: String
156
confdReqqFields = "3"
157

    
158
-- * ISpec
159

    
160
ispecMemSize :: String
161
ispecMemSize = "memory-size"
162

    
163
ispecCpuCount :: String
164
ispecCpuCount = "cpu-count"
165

    
166
ispecDiskCount :: String
167
ispecDiskCount = "disk-count"
168

    
169
ispecDiskSize :: String
170
ispecDiskSize = "disk-size"
171

    
172
ispecNicCount :: String
173
ispecNicCount = "nic-count"
174

    
175
ispecSpindleUse :: String
176
ispecSpindleUse = "spindle-use"
177

    
178
ispecsMinmax :: String
179
ispecsMinmax = "minmax"
180

    
181
ispecsStd :: String
182
ispecsStd = "std"
183

    
184
ipolicyDts :: String
185
ipolicyDts = "disk-templates"
186

    
187
ipolicyVcpuRatio :: String
188
ipolicyVcpuRatio = "vcpu-ratio"
189

    
190
ipolicySpindleRatio :: String
191
ipolicySpindleRatio = "spindle-ratio"
192

    
193
ipolicyDefaultsVcpuRatio :: Double
194
ipolicyDefaultsVcpuRatio = 4.0
195

    
196
ipolicyDefaultsSpindleRatio :: Double
197
ipolicyDefaultsSpindleRatio = 32.0