Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ a07343b2

History | View | Annotate | Download (9.2 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common types.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.HTools.Types
29
  ( Idx
30
  , Ndx
31
  , Gdx
32
  , NameAssoc
33
  , Score
34
  , Weight
35
  , GroupID
36
  , defaultGroupID
37
  , AllocPolicy(..)
38
  , allocPolicyFromRaw
39
  , allocPolicyToRaw
40
  , InstanceStatus(..)
41
  , instanceStatusFromRaw
42
  , instanceStatusToRaw
43
  , RSpec(..)
44
  , DynUtil(..)
45
  , zeroUtil
46
  , baseUtil
47
  , addUtil
48
  , subUtil
49
  , defVcpuRatio
50
  , defReservedDiskRatio
51
  , unitMem
52
  , unitCpu
53
  , unitDsk
54
  , unknownField
55
  , Placement
56
  , IMove(..)
57
  , DiskTemplate(..)
58
  , diskTemplateToRaw
59
  , diskTemplateFromRaw
60
  , MoveJob
61
  , JobSet
62
  , Result(..)
63
  , isOk
64
  , isBad
65
  , eitherToResult
66
  , annotateResult
67
  , Element(..)
68
  , FailMode(..)
69
  , FailStats
70
  , OpResult(..)
71
  , opToResult
72
  , connTimeout
73
  , queryTimeout
74
  , EvacMode(..)
75
  , ISpec(..)
76
  , IPolicy(..)
77
  ) where
78

    
79
import qualified Data.Map as M
80
import Text.JSON (makeObj, readJSON, showJSON)
81

    
82
import qualified Ganeti.Constants as C
83
import qualified Ganeti.THH as THH
84
import Ganeti.BasicTypes
85
import Ganeti.HTools.JSON
86

    
87
-- | The instance index type.
88
type Idx = Int
89

    
90
-- | The node index type.
91
type Ndx = Int
92

    
93
-- | The group index type.
94
type Gdx = Int
95

    
96
-- | The type used to hold name-to-idx mappings.
97
type NameAssoc = M.Map String Int
98

    
99
-- | A separate name for the cluster score type.
100
type Score = Double
101

    
102
-- | A separate name for a weight metric.
103
type Weight = Double
104

    
105
-- | The Group UUID type.
106
type GroupID = String
107

    
108
-- | Default group UUID (just a string, not a real UUID).
109
defaultGroupID :: GroupID
110
defaultGroupID = "00000000-0000-0000-0000-000000000000"
111

    
112
-- | The Group allocation policy type.
113
--
114
-- Note that the order of constructors is important as the automatic
115
-- Ord instance will order them in the order they are defined, so when
116
-- changing this data type be careful about the interaction with the
117
-- desired sorting order.
118
$(THH.declareSADT "AllocPolicy"
119
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
120
       , ("AllocLastResort",  'C.allocPolicyLastResort)
121
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
122
       ])
123
$(THH.makeJSONInstance ''AllocPolicy)
124

    
125
-- | The Instance real state type.
126
$(THH.declareSADT "InstanceStatus"
127
       [ ("AdminDown", 'C.inststAdmindown)
128
       , ("AdminOffline", 'C.inststAdminoffline)
129
       , ("ErrorDown", 'C.inststErrordown)
130
       , ("ErrorUp", 'C.inststErrorup)
131
       , ("NodeDown", 'C.inststNodedown)
132
       , ("NodeOffline", 'C.inststNodeoffline)
133
       , ("Running", 'C.inststRunning)
134
       , ("WrongNode", 'C.inststWrongnode)
135
       ])
136
$(THH.makeJSONInstance ''InstanceStatus)
137

    
138
-- | The resource spec type.
139
data RSpec = RSpec
140
  { rspecCpu  :: Int  -- ^ Requested VCPUs
141
  , rspecMem  :: Int  -- ^ Requested memory
142
  , rspecDsk  :: Int  -- ^ Requested disk
143
  } deriving (Show, Read, Eq)
144

    
145

    
146
-- | Instance specification type.
147
$(THH.buildObject "ISpec" "iSpec"
148
  [ THH.renameField "MemorySize" $ THH.simpleField "memory-size" [t| Int |]
149
  , THH.renameField "CpuCount"   $ THH.simpleField "cpu-count"   [t| Int |]
150
  , THH.renameField "DiskSize"   $ THH.simpleField "disk-size"   [t| Int |]
151
  , THH.renameField "DiskCount"  $ THH.simpleField "disk-count"  [t| Int |]
152
  , THH.renameField "NicCount"   $ THH.simpleField "nic-count"   [t| Int |]
153
  ])
154

    
155
-- | Instance policy type.
156
$(THH.buildObject "IPolicy" "iPolicy"
157
  [ THH.renameField "StdSpec" $ THH.simpleField "std" [t| ISpec |]
158
  , THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
159
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
160
  ])
161

    
162
-- | The dynamic resource specs of a machine (i.e. load or load
163
-- capacity, as opposed to size).
164
data DynUtil = DynUtil
165
  { cpuWeight :: Weight -- ^ Standardised CPU usage
166
  , memWeight :: Weight -- ^ Standardised memory load
167
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
168
  , netWeight :: Weight -- ^ Standardised network usage
169
  } deriving (Show, Read, Eq)
170

    
171
-- | Initial empty utilisation.
172
zeroUtil :: DynUtil
173
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
174
                   , dskWeight = 0, netWeight = 0 }
175

    
176
-- | Base utilisation (used when no actual utilisation data is
177
-- supplied).
178
baseUtil :: DynUtil
179
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
180
                   , dskWeight = 1, netWeight = 1 }
181

    
182
-- | Sum two utilisation records.
183
addUtil :: DynUtil -> DynUtil -> DynUtil
184
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
185
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
186

    
187
-- | Substracts one utilisation record from another.
188
subUtil :: DynUtil -> DynUtil -> DynUtil
189
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
190
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
191

    
192
-- | The description of an instance placement. It contains the
193
-- instance index, the new primary and secondary node, the move being
194
-- performed and the score of the cluster after the move.
195
type Placement = (Idx, Ndx, Ndx, IMove, Score)
196

    
197
-- | An instance move definition.
198
data IMove = Failover                -- ^ Failover the instance (f)
199
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
200
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
201
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
202
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
203
             deriving (Show, Read)
204

    
205
-- | Instance disk template type.
206
$(THH.declareSADT "DiskTemplate"
207
       [ ("DTDiskless",   'C.dtDiskless)
208
       , ("DTFile",       'C.dtFile)
209
       , ("DTSharedFile", 'C.dtSharedFile)
210
       , ("DTPlain",      'C.dtPlain)
211
       , ("DTBlock",      'C.dtBlock)
212
       , ("DTDrbd8",      'C.dtDrbd8)
213
       ])
214
$(THH.makeJSONInstance ''DiskTemplate)
215

    
216
-- | Formatted solution output for one move (involved nodes and
217
-- commands.
218
type MoveJob = ([Ndx], Idx, IMove, [String])
219

    
220
-- | Unknown field in table output.
221
unknownField :: String
222
unknownField = "<unknown field>"
223

    
224
-- | A list of command elements.
225
type JobSet = [MoveJob]
226

    
227
-- | Connection timeout (when using non-file methods).
228
connTimeout :: Int
229
connTimeout = 15
230

    
231
-- | The default timeout for queries (when using non-file methods).
232
queryTimeout :: Int
233
queryTimeout = 60
234

    
235
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
236
defVcpuRatio :: Double
237
defVcpuRatio = 64
238

    
239
-- | Default max disk usage ratio.
240
defReservedDiskRatio :: Double
241
defReservedDiskRatio = 0
242

    
243
-- | Base memory unit.
244
unitMem :: Int
245
unitMem = 64
246

    
247
-- | Base disk unit.
248
unitDsk :: Int
249
unitDsk = 256
250

    
251
-- | Base vcpus unit.
252
unitCpu :: Int
253
unitCpu = 1
254

    
255
-- | Reason for an operation's falure.
256
data FailMode = FailMem  -- ^ Failed due to not enough RAM
257
              | FailDisk -- ^ Failed due to not enough disk
258
              | FailCPU  -- ^ Failed due to not enough CPU capacity
259
              | FailN1   -- ^ Failed due to not passing N1 checks
260
              | FailTags -- ^ Failed due to tag exclusion
261
                deriving (Eq, Enum, Bounded, Show, Read)
262

    
263
-- | List with failure statistics.
264
type FailStats = [(FailMode, Int)]
265

    
266
-- | Either-like data-type customized for our failure modes.
267
--
268
-- The failure values for this monad track the specific allocation
269
-- failures, so this is not a general error-monad (compare with the
270
-- 'Result' data type). One downside is that this type cannot encode a
271
-- generic failure mode, hence 'fail' for this monad is not defined
272
-- and will cause an exception.
273
data OpResult a = OpFail FailMode -- ^ Failed operation
274
                | OpGood a        -- ^ Success operation
275
                  deriving (Show, Read)
276

    
277
instance Monad OpResult where
278
  (OpGood x) >>= fn = fn x
279
  (OpFail y) >>= _ = OpFail y
280
  return = OpGood
281

    
282
-- | Conversion from 'OpResult' to 'Result'.
283
opToResult :: OpResult a -> Result a
284
opToResult (OpFail f) = Bad $ show f
285
opToResult (OpGood v) = Ok v
286

    
287
-- | A generic class for items that have updateable names and indices.
288
class Element a where
289
  -- | Returns the name of the element
290
  nameOf  :: a -> String
291
  -- | Returns all the known names of the element
292
  allNames :: a -> [String]
293
  -- | Returns the index of the element
294
  idxOf   :: a -> Int
295
  -- | Updates the alias of the element
296
  setAlias :: a -> String -> a
297
  -- | Compute the alias by stripping a given suffix (domain) from
298
  -- the name
299
  computeAlias :: String -> a -> a
300
  computeAlias dom e = setAlias e alias
301
    where alias = take (length name - length dom) name
302
          name = nameOf e
303
  -- | Updates the index of the element
304
  setIdx  :: a -> Int -> a
305

    
306
-- | The iallocator node-evacuate evac_mode type.
307
$(THH.declareSADT "EvacMode"
308
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
309
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
310
       , ("ChangeAll",       'C.iallocatorNevacAll)
311
       ])
312
$(THH.makeJSONInstance ''EvacMode)