Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ 96e3dfa7

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.Constants' together with
93
-- the other exit codes in order to avoid a circular dependency
94
-- between 'Ganeti.Constants' and 'Ganeti.Runtime'
95
exitFailure :: Int
96
exitFailure = 1
97

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

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

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

    
118
priorityLow :: Int
119
priorityLow = 10
120

    
121
priorityNormal :: Int
122
priorityNormal = 0
123

    
124
priorityHigh :: Int
125
priorityHigh = -10
126

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

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

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

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

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

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

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

    
159
-- * ISpec
160

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

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

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

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

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

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

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

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

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

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

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

    
194
ipolicyDefaultsVcpuRatio :: Double
195
ipolicyDefaultsVcpuRatio = 4.0
196

    
197
ipolicyDefaultsSpindleRatio :: Double
198
ipolicyDefaultsSpindleRatio = 32.0