Statistics
| Branch: | Tag: | Revision:

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

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.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, Ord, 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
toList :: FrozenSet a -> [a]
65
toList = Set.toList . unFrozenSet
66

    
67
union :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
68
union x y = FrozenSet (unFrozenSet x `Set.union` unFrozenSet y)
69

    
70
difference :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
71
difference x y = FrozenSet (unFrozenSet x `Set.difference` unFrozenSet y)
72

    
73
-- | 'Protocol' represents the protocols used by the daemons
74
data Protocol = Tcp | Udp
75
  deriving (Show)
76

    
77
-- | 'PyValue' instance of 'Protocol'
78
--
79
-- This instance is used by the Haskell to Python constants
80
instance PyValue Protocol where
81
  showValue Tcp = "\"tcp\""
82
  showValue Udp = "\"udp\""
83

    
84
-- | Failure exit code
85
--
86
-- These are defined here and not in 'Ganeti.HsConstants' together with
87
-- the other exit codes in order to avoid a circular dependency
88
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
89
exitFailure :: Int
90
exitFailure = 1
91

    
92
-- | Console device
93
--
94
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
95
-- a circular dependency between 'Ganeti.HsConstants' and
96
-- 'Ganeti.Logging'
97
devConsole :: String
98
devConsole = "/dev/console"
99

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

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

    
114
priorityLow :: Int
115
priorityLow = 10
116

    
117
priorityNormal :: Int
118
priorityNormal = 0
119

    
120
priorityHigh :: Int
121
priorityHigh = -10
122

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

    
129
-- | Confd protocol version
130
--
131
-- This is defined here in order to avoid a circular dependency
132
-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
133
confdProtocolVersion :: Int
134
confdProtocolVersion = 1
135

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

    
143
confdReqqLink :: String
144
confdReqqLink = "0"
145

    
146
confdReqqIp :: String
147
confdReqqIp = "1"
148

    
149
confdReqqIplist :: String
150
confdReqqIplist = "2"
151

    
152
confdReqqFields :: String
153
confdReqqFields = "3"
154

    
155
-- * ISpec
156

    
157
ispecMemSize :: String
158
ispecMemSize = "memory-size"
159

    
160
ispecCpuCount :: String
161
ispecCpuCount = "cpu-count"
162

    
163
ispecDiskCount :: String
164
ispecDiskCount = "disk-count"
165

    
166
ispecDiskSize :: String
167
ispecDiskSize = "disk-size"
168

    
169
ispecNicCount :: String
170
ispecNicCount = "nic-count"
171

    
172
ispecSpindleUse :: String
173
ispecSpindleUse = "spindle-use"
174

    
175
ispecsMinmax :: String
176
ispecsMinmax = "minmax"
177

    
178
ispecsStd :: String
179
ispecsStd = "std"
180

    
181
ipolicyDts :: String
182
ipolicyDts = "disk-templates"
183

    
184
ipolicyVcpuRatio :: String
185
ipolicyVcpuRatio = "vcpu-ratio"
186

    
187
ipolicySpindleRatio :: String
188
ipolicySpindleRatio = "spindle-ratio"
189

    
190
ipolicyDefaultsVcpuRatio :: Double
191
ipolicyDefaultsVcpuRatio = 4.0
192

    
193
ipolicyDefaultsSpindleRatio :: Double
194
ipolicyDefaultsSpindleRatio = 32.0