Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 34ad1d7c

History | View | Annotate | Download (15.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common types.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011, 2012, 2013 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
  , NetworkID
41
  , InstanceStatus(..)
42
  , instanceStatusFromRaw
43
  , instanceStatusToRaw
44
  , RSpec(..)
45
  , AllocInfo(..)
46
  , AllocStats
47
  , DynUtil(..)
48
  , zeroUtil
49
  , baseUtil
50
  , addUtil
51
  , subUtil
52
  , defReservedDiskRatio
53
  , unitMem
54
  , unitCpu
55
  , unitDsk
56
  , unitSpindle
57
  , unknownField
58
  , Placement
59
  , IMove(..)
60
  , DiskTemplate(..)
61
  , diskTemplateToRaw
62
  , diskTemplateFromRaw
63
  , MirrorType(..)
64
  , templateMirrorType
65
  , MoveJob
66
  , JobSet
67
  , Element(..)
68
  , FailMode(..)
69
  , FailStats
70
  , OpResult
71
  , opToResult
72
  , EvacMode(..)
73
  , ISpec(..)
74
  , MinMaxISpecs(..)
75
  , IPolicy(..)
76
  , defIPolicy
77
  , rspecFromISpec
78
  , AutoRepairType(..)
79
  , autoRepairTypeToRaw
80
  , autoRepairTypeFromRaw
81
  , AutoRepairResult(..)
82
  , autoRepairResultToRaw
83
  , autoRepairResultFromRaw
84
  , AutoRepairPolicy(..)
85
  , AutoRepairSuspendTime(..)
86
  , AutoRepairData(..)
87
  , AutoRepairStatus(..)
88
  ) where
89

    
90
import qualified Data.Map as M
91
import System.Time (ClockTime)
92

    
93
import qualified Ganeti.Constants as C
94
import qualified Ganeti.THH as THH
95
import Ganeti.BasicTypes
96
import Ganeti.Types
97

    
98
-- | The instance index type.
99
type Idx = Int
100

    
101
-- | The node index type.
102
type Ndx = Int
103

    
104
-- | The group index type.
105
type Gdx = Int
106

    
107
-- | The type used to hold name-to-idx mappings.
108
type NameAssoc = M.Map String Int
109

    
110
-- | A separate name for the cluster score type.
111
type Score = Double
112

    
113
-- | A separate name for a weight metric.
114
type Weight = Double
115

    
116
-- | The Group UUID type.
117
type GroupID = String
118

    
119
-- | Default group UUID (just a string, not a real UUID).
120
defaultGroupID :: GroupID
121
defaultGroupID = "00000000-0000-0000-0000-000000000000"
122

    
123
-- | Mirroring type.
124
data MirrorType = MirrorNone     -- ^ No mirroring/movability
125
                | MirrorInternal -- ^ DRBD-type mirroring
126
                | MirrorExternal -- ^ Shared-storage type mirroring
127
                  deriving (Eq, Show)
128

    
129
-- | Correspondence between disk template and mirror type.
130
templateMirrorType :: DiskTemplate -> MirrorType
131
templateMirrorType DTDiskless   = MirrorExternal
132
templateMirrorType DTFile       = MirrorNone
133
templateMirrorType DTSharedFile = MirrorExternal
134
templateMirrorType DTPlain      = MirrorNone
135
templateMirrorType DTBlock      = MirrorExternal
136
templateMirrorType DTDrbd8      = MirrorInternal
137
templateMirrorType DTRbd        = MirrorExternal
138
templateMirrorType DTExt        = MirrorExternal
139

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

    
148
-- | Allocation stats type. This is used instead of 'RSpec' (which was
149
-- used at first), because we need to track more stats. The actual
150
-- data can refer either to allocated, or available, etc. values
151
-- depending on the context. See also
152
-- 'Cluster.computeAllocationDelta'.
153
data AllocInfo = AllocInfo
154
  { allocInfoVCpus :: Int    -- ^ VCPUs
155
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
156
  , allocInfoMem   :: Int    -- ^ Memory
157
  , allocInfoDisk  :: Int    -- ^ Disk
158
  , allocInfoSpn   :: Int    -- ^ Spindles
159
  } deriving (Show, Eq)
160

    
161
-- | Currently used, possibly to allocate, unallocable.
162
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
163

    
164
-- | The network UUID type.
165
type NetworkID = String
166

    
167
-- | Instance specification type.
168
$(THH.buildObject "ISpec" "iSpec"
169
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
170
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
171
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
172
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
173
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
174
  , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
175
  ])
176

    
177
-- | The default minimum ispec.
178
defMinISpec :: ISpec
179
defMinISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMinMemorySize
180
                    , iSpecCpuCount   = C.ispecsMinmaxDefaultsMinCpuCount
181
                    , iSpecDiskSize   = C.ispecsMinmaxDefaultsMinDiskSize
182
                    , iSpecDiskCount  = C.ispecsMinmaxDefaultsMinDiskCount
183
                    , iSpecNicCount   = C.ispecsMinmaxDefaultsMinNicCount
184
                    , iSpecSpindleUse = C.ispecsMinmaxDefaultsMinSpindleUse
185
                    }
186

    
187
-- | The default standard ispec.
188
defStdISpec :: ISpec
189
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
190
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
191
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
192
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
193
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
194
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
195
                    }
196

    
197
-- | The default max ispec.
198
defMaxISpec :: ISpec
199
defMaxISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMaxMemorySize
200
                    , iSpecCpuCount   = C.ispecsMinmaxDefaultsMaxCpuCount
201
                    , iSpecDiskSize   = C.ispecsMinmaxDefaultsMaxDiskSize
202
                    , iSpecDiskCount  = C.ispecsMinmaxDefaultsMaxDiskCount
203
                    , iSpecNicCount   = C.ispecsMinmaxDefaultsMaxNicCount
204
                    , iSpecSpindleUse = C.ispecsMinmaxDefaultsMaxSpindleUse
205
                    }
206

    
207
-- | Minimum and maximum instance specs type.
208
$(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
209
  [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
210
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
211
  ])
212

    
213
-- | Defult minimum and maximum instance specs.
214
defMinMaxISpecs :: [MinMaxISpecs]
215
defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
216
                                , minMaxISpecsMaxSpec = defMaxISpec
217
                                }]
218

    
219
-- | Instance policy type.
220
$(THH.buildObject "IPolicy" "iPolicy"
221
  [ THH.renameField "MinMaxISpecs" $
222
      THH.simpleField C.ispecsMinmax [t| [MinMaxISpecs] |]
223
  , THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
224
  , THH.renameField "DiskTemplates" $
225
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
226
  , THH.renameField "VcpuRatio" $
227
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
228
  , THH.renameField "SpindleRatio" $
229
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
230
  ])
231

    
232
-- | Converts an ISpec type to a RSpec one.
233
rspecFromISpec :: ISpec -> RSpec
234
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
235
                             , rspecMem = iSpecMemorySize ispec
236
                             , rspecDsk = iSpecDiskSize ispec
237
                             , rspecSpn = iSpecSpindleUse ispec
238
                             }
239

    
240
-- | The default instance policy.
241
defIPolicy :: IPolicy
242
defIPolicy = IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
243
                     , iPolicyStdSpec = defStdISpec
244
                     -- hardcoding here since Constants.hs exports the
245
                     -- string values, not the actual type; and in
246
                     -- htools, we are mostly looking at DRBD
247
                     , iPolicyDiskTemplates = [minBound..maxBound]
248
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
249
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
250
                     }
251

    
252
-- | The dynamic resource specs of a machine (i.e. load or load
253
-- capacity, as opposed to size).
254
data DynUtil = DynUtil
255
  { cpuWeight :: Weight -- ^ Standardised CPU usage
256
  , memWeight :: Weight -- ^ Standardised memory load
257
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
258
  , netWeight :: Weight -- ^ Standardised network usage
259
  } deriving (Show, Eq)
260

    
261
-- | Initial empty utilisation.
262
zeroUtil :: DynUtil
263
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
264
                   , dskWeight = 0, netWeight = 0 }
265

    
266
-- | Base utilisation (used when no actual utilisation data is
267
-- supplied).
268
baseUtil :: DynUtil
269
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
270
                   , dskWeight = 1, netWeight = 1 }
271

    
272
-- | Sum two utilisation records.
273
addUtil :: DynUtil -> DynUtil -> DynUtil
274
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
275
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
276

    
277
-- | Substracts one utilisation record from another.
278
subUtil :: DynUtil -> DynUtil -> DynUtil
279
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
280
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
281

    
282
-- | The description of an instance placement. It contains the
283
-- instance index, the new primary and secondary node, the move being
284
-- performed and the score of the cluster after the move.
285
type Placement = (Idx, Ndx, Ndx, IMove, Score)
286

    
287
-- | An instance move definition.
288
data IMove = Failover                -- ^ Failover the instance (f)
289
           | FailoverToAny Ndx       -- ^ Failover to a random node
290
                                     -- (fa:np), for shared storage
291
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
292
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
293
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
294
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
295
             deriving (Show)
296

    
297
-- | Formatted solution output for one move (involved nodes and
298
-- commands.
299
type MoveJob = ([Ndx], Idx, IMove, [String])
300

    
301
-- | Unknown field in table output.
302
unknownField :: String
303
unknownField = "<unknown field>"
304

    
305
-- | A list of command elements.
306
type JobSet = [MoveJob]
307

    
308
-- | Default max disk usage ratio.
309
defReservedDiskRatio :: Double
310
defReservedDiskRatio = 0
311

    
312
-- | Base memory unit.
313
unitMem :: Int
314
unitMem = 64
315

    
316
-- | Base disk unit.
317
unitDsk :: Int
318
unitDsk = 256
319

    
320
-- | Base vcpus unit.
321
unitCpu :: Int
322
unitCpu = 1
323

    
324
-- | Base spindles unit.
325
unitSpindle :: Int
326
unitSpindle = 1
327

    
328
-- | Reason for an operation's falure.
329
data FailMode = FailMem  -- ^ Failed due to not enough RAM
330
              | FailDisk -- ^ Failed due to not enough disk
331
              | FailCPU  -- ^ Failed due to not enough CPU capacity
332
              | FailN1   -- ^ Failed due to not passing N1 checks
333
              | FailTags -- ^ Failed due to tag exclusion
334
              | FailDiskCount -- ^ Failed due to wrong number of disks
335
              | FailSpindles -- ^ Failed due to wrong/missing spindles
336
              | FailInternal -- ^ Internal error
337
                deriving (Eq, Enum, Bounded, Show)
338

    
339
-- | List with failure statistics.
340
type FailStats = [(FailMode, Int)]
341

    
342
-- | Either-like data-type customized for our failure modes.
343
--
344
-- The failure values for this monad track the specific allocation
345
-- failures, so this is not a general error-monad (compare with the
346
-- 'Result' data type). One downside is that this type cannot encode a
347
-- generic failure mode, hence our way to build a FailMode from string
348
-- will instead raise an exception.
349
type OpResult = GenericResult FailMode
350

    
351
-- | 'FromString' instance for 'FailMode' designed to catch unintended
352
-- use as a general monad.
353
instance FromString FailMode where
354
  mkFromString v = error $ "Programming error: OpResult used as generic monad"
355
                           ++ v
356

    
357
-- | Conversion from 'OpResult' to 'Result'.
358
opToResult :: OpResult a -> Result a
359
opToResult (Bad f) = Bad $ show f
360
opToResult (Ok v) = Ok v
361

    
362
-- | A generic class for items that have updateable names and indices.
363
class Element a where
364
  -- | Returns the name of the element
365
  nameOf  :: a -> String
366
  -- | Returns all the known names of the element
367
  allNames :: a -> [String]
368
  -- | Returns the index of the element
369
  idxOf   :: a -> Int
370
  -- | Updates the alias of the element
371
  setAlias :: a -> String -> a
372
  -- | Compute the alias by stripping a given suffix (domain) from
373
  -- the name
374
  computeAlias :: String -> a -> a
375
  computeAlias dom e = setAlias e alias
376
    where alias = take (length name - length dom) name
377
          name = nameOf e
378
  -- | Updates the index of the element
379
  setIdx  :: a -> Int -> a
380

    
381
-- | The iallocator node-evacuate evac_mode type.
382
$(THH.declareSADT "EvacMode"
383
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
384
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
385
       , ("ChangeAll",       'C.iallocatorNevacAll)
386
       ])
387
$(THH.makeJSONInstance ''EvacMode)
388

    
389
-- | The repair modes for the auto-repair tool.
390
$(THH.declareSADT "AutoRepairType"
391
       -- Order is important here: from least destructive to most.
392
       [ ("ArFixStorage", 'C.autoRepairFixStorage)
393
       , ("ArMigrate",    'C.autoRepairMigrate)
394
       , ("ArFailover",   'C.autoRepairFailover)
395
       , ("ArReinstall",  'C.autoRepairReinstall)
396
       ])
397

    
398
-- | The possible auto-repair results.
399
$(THH.declareSADT "AutoRepairResult"
400
       -- Order is important here: higher results take precedence when an object
401
       -- has several result annotations attached.
402
       [ ("ArEnoperm", 'C.autoRepairEnoperm)
403
       , ("ArSuccess", 'C.autoRepairSuccess)
404
       , ("ArFailure", 'C.autoRepairFailure)
405
       ])
406

    
407
-- | The possible auto-repair policy for a given instance.
408
data AutoRepairPolicy
409
  = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
410
  | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
411
  | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
412
  deriving (Eq, Show)
413

    
414
-- | The suspend timeout for 'ArSuspended'.
415
data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
416
                           | Until ClockTime -- ^ Suspended up to a certain time
417
                           deriving (Eq, Show)
418

    
419
-- | The possible auto-repair states for any given instance.
420
data AutoRepairStatus
421
  = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
422
  | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
423
  | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
424
  | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
425
  deriving (Eq, Show)
426

    
427
-- | The data accompanying a repair operation (future, pending, or failed).
428
data AutoRepairData = AutoRepairData { arType :: AutoRepairType
429
                                     , arUuid :: String
430
                                     , arTime :: ClockTime
431
                                     , arJobs :: [JobId]
432
                                     , arResult :: Maybe AutoRepairResult
433
                                     , arTag :: String
434
                                     }
435
                    deriving (Eq, Show)