Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ cc6a469e

History | View | Annotate | Download (4.9 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)
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
-- | 'Protocol' represents the protocols used by the daemons
65
data Protocol = Tcp | Udp
66
  deriving (Show)
67

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

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

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

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

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

    
105
priorityLow :: Int
106
priorityLow = 10
107

    
108
priorityNormal :: Int
109
priorityNormal = 0
110

    
111
priorityHigh :: Int
112
priorityHigh = -10
113

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

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

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

    
134
confdReqqLink :: String
135
confdReqqLink = "0"
136

    
137
confdReqqIp :: String
138
confdReqqIp = "1"
139

    
140
confdReqqIplist :: String
141
confdReqqIplist = "2"
142

    
143
confdReqqFields :: String
144
confdReqqFields = "3"
145

    
146
-- * ISpec
147

    
148
ispecMemSize :: String
149
ispecMemSize = "memory-size"
150

    
151
ispecCpuCount :: String
152
ispecCpuCount = "cpu-count"
153

    
154
ispecDiskCount :: String
155
ispecDiskCount = "disk-count"
156

    
157
ispecDiskSize :: String
158
ispecDiskSize = "disk-size"
159

    
160
ispecNicCount :: String
161
ispecNicCount = "nic-count"
162

    
163
ispecSpindleUse :: String
164
ispecSpindleUse = "spindle-use"
165

    
166
ispecsMinmax :: String
167
ispecsMinmax = "minmax"
168

    
169
ispecsStd :: String
170
ispecsStd = "std"
171

    
172
ipolicyDts :: String
173
ipolicyDts = "disk-templates"
174

    
175
ipolicyVcpuRatio :: String
176
ipolicyVcpuRatio = "vcpu-ratio"
177

    
178
ipolicySpindleRatio :: String
179
ipolicySpindleRatio = "spindle-ratio"
180

    
181
ipolicyDefaultsVcpuRatio :: Double
182
ipolicyDefaultsVcpuRatio = 4.0
183

    
184
ipolicyDefaultsSpindleRatio :: Double
185
ipolicyDefaultsSpindleRatio = 32.0