Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ e061eb16

History | View | Annotate | Download (14.5 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
  , ISpec(..)
73
  , defMinISpec
74
  , defStdISpec
75
  , maxDisks
76
  , maxNics
77
  , defMaxISpec
78
  , MinMaxISpecs(..)
79
  , IPolicy(..)
80
  , defIPolicy
81
  , rspecFromISpec
82
  , AutoRepairType(..)
83
  , autoRepairTypeToRaw
84
  , autoRepairTypeFromRaw
85
  , AutoRepairResult(..)
86
  , autoRepairResultToRaw
87
  , autoRepairResultFromRaw
88
  , AutoRepairPolicy(..)
89
  , AutoRepairSuspendTime(..)
90
  , AutoRepairData(..)
91
  , AutoRepairStatus(..)
92
  ) where
93

    
94
import qualified Data.Map as M
95
import System.Time (ClockTime)
96

    
97
import qualified Ganeti.ConstantUtils as ConstantUtils
98
import qualified Ganeti.THH as THH
99
import Ganeti.BasicTypes
100
import Ganeti.Types
101

    
102
-- | The instance index type.
103
type Idx = Int
104

    
105
-- | The node index type.
106
type Ndx = Int
107

    
108
-- | The group index type.
109
type Gdx = Int
110

    
111
-- | The type used to hold name-to-idx mappings.
112
type NameAssoc = M.Map String Int
113

    
114
-- | A separate name for the cluster score type.
115
type Score = Double
116

    
117
-- | A separate name for a weight metric.
118
type Weight = Double
119

    
120
-- | The Group UUID type.
121
type GroupID = String
122

    
123
-- | Default group UUID (just a string, not a real UUID).
124
defaultGroupID :: GroupID
125
defaultGroupID = "00000000-0000-0000-0000-000000000000"
126

    
127
-- | Mirroring type.
128
data MirrorType = MirrorNone     -- ^ No mirroring/movability
129
                | MirrorInternal -- ^ DRBD-type mirroring
130
                | MirrorExternal -- ^ Shared-storage type mirroring
131
                  deriving (Eq, Show)
132

    
133
-- | Correspondence between disk template and mirror type.
134
templateMirrorType :: DiskTemplate -> MirrorType
135
templateMirrorType DTDiskless   = MirrorExternal
136
templateMirrorType DTFile       = MirrorNone
137
templateMirrorType DTSharedFile = MirrorExternal
138
templateMirrorType DTPlain      = MirrorNone
139
templateMirrorType DTBlock      = MirrorExternal
140
templateMirrorType DTDrbd8      = MirrorInternal
141
templateMirrorType DTRbd        = MirrorExternal
142
templateMirrorType DTExt        = MirrorExternal
143
templateMirrorType DTGluster    = MirrorExternal
144

    
145
-- | The resource spec type.
146
data RSpec = RSpec
147
  { rspecCpu  :: Int  -- ^ Requested VCPUs
148
  , rspecMem  :: Int  -- ^ Requested memory
149
  , rspecDsk  :: Int  -- ^ Requested disk
150
  , rspecSpn  :: Int  -- ^ Requested spindles
151
  } deriving (Show, Eq)
152

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

    
166
-- | Currently used, possibly to allocate, unallocable.
167
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
168

    
169
-- | The network UUID type.
170
type NetworkID = String
171

    
172
-- | Instance specification type.
173
$(THH.buildObject "ISpec" "iSpec"
174
  [ THH.renameField "MemorySize" $
175
    THH.simpleField ConstantUtils.ispecMemSize    [t| Int |]
176
  , THH.renameField "CpuCount"   $
177
    THH.simpleField ConstantUtils.ispecCpuCount   [t| Int |]
178
  , THH.renameField "DiskSize"   $
179
    THH.simpleField ConstantUtils.ispecDiskSize   [t| Int |]
180
  , THH.renameField "DiskCount"  $
181
    THH.simpleField ConstantUtils.ispecDiskCount  [t| Int |]
182
  , THH.renameField "NicCount"   $
183
    THH.simpleField ConstantUtils.ispecNicCount   [t| Int |]
184
  , THH.renameField "SpindleUse" $
185
    THH.simpleField ConstantUtils.ispecSpindleUse [t| Int |]
186
  ])
187

    
188
-- | The default minimum ispec.
189
defMinISpec :: ISpec
190
defMinISpec = ISpec { iSpecMemorySize = 128
191
                    , iSpecCpuCount   = 1
192
                    , iSpecDiskCount  = 1
193
                    , iSpecDiskSize   = 1024
194
                    , iSpecNicCount   = 1
195
                    , iSpecSpindleUse = 1
196
                    }
197

    
198
-- | The default standard ispec.
199
defStdISpec :: ISpec
200
defStdISpec = ISpec { iSpecMemorySize = 128
201
                    , iSpecCpuCount   = 1
202
                    , iSpecDiskCount  = 1
203
                    , iSpecDiskSize   = 1024
204
                    , iSpecNicCount   = 1
205
                    , iSpecSpindleUse = 1
206
                    }
207

    
208
maxDisks :: Int
209
maxDisks = 16
210

    
211
maxNics :: Int
212
maxNics = 8
213

    
214
-- | The default max ispec.
215
defMaxISpec :: ISpec
216
defMaxISpec = ISpec { iSpecMemorySize = 32768
217
                    , iSpecCpuCount   = 8
218
                    , iSpecDiskCount  = maxDisks
219
                    , iSpecDiskSize   = 1024 * 1024
220
                    , iSpecNicCount   = maxNics
221
                    , iSpecSpindleUse = 12
222
                    }
223

    
224
-- | Minimum and maximum instance specs type.
225
$(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
226
  [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
227
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
228
  ])
229

    
230
-- | Defult minimum and maximum instance specs.
231
defMinMaxISpecs :: [MinMaxISpecs]
232
defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
233
                                , minMaxISpecsMaxSpec = defMaxISpec
234
                                }]
235

    
236
-- | Instance policy type.
237
$(THH.buildObject "IPolicy" "iPolicy"
238
  [ THH.renameField "MinMaxISpecs" $
239
      THH.simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
240
  , THH.renameField "StdSpec" $
241
      THH.simpleField ConstantUtils.ispecsStd [t| ISpec |]
242
  , THH.renameField "DiskTemplates" $
243
      THH.simpleField ConstantUtils.ipolicyDts [t| [DiskTemplate] |]
244
  , THH.renameField "VcpuRatio" $
245
      THH.simpleField ConstantUtils.ipolicyVcpuRatio [t| Double |]
246
  , THH.renameField "SpindleRatio" $
247
      THH.simpleField ConstantUtils.ipolicySpindleRatio [t| Double |]
248
  ])
249

    
250
-- | Converts an ISpec type to a RSpec one.
251
rspecFromISpec :: ISpec -> RSpec
252
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
253
                             , rspecMem = iSpecMemorySize ispec
254
                             , rspecDsk = iSpecDiskSize ispec
255
                             , rspecSpn = iSpecSpindleUse ispec
256
                             }
257

    
258
-- | The default instance policy.
259
defIPolicy :: IPolicy
260
defIPolicy =
261
  IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
262
          , iPolicyStdSpec = defStdISpec
263
          -- hardcoding here since Constants.hs exports the
264
          -- string values, not the actual type; and in
265
          -- htools, we are mostly looking at DRBD
266
          , iPolicyDiskTemplates = [minBound..maxBound]
267
          , iPolicyVcpuRatio = ConstantUtils.ipolicyDefaultsVcpuRatio
268
          , iPolicySpindleRatio = ConstantUtils.ipolicyDefaultsSpindleRatio
269
          }
270

    
271
-- | The dynamic resource specs of a machine (i.e. load or load
272
-- capacity, as opposed to size).
273
data DynUtil = DynUtil
274
  { cpuWeight :: Weight -- ^ Standardised CPU usage
275
  , memWeight :: Weight -- ^ Standardised memory load
276
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
277
  , netWeight :: Weight -- ^ Standardised network usage
278
  } deriving (Show, Eq)
279

    
280
-- | Initial empty utilisation.
281
zeroUtil :: DynUtil
282
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
283
                   , dskWeight = 0, netWeight = 0 }
284

    
285
-- | Base utilisation (used when no actual utilisation data is
286
-- supplied).
287
baseUtil :: DynUtil
288
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
289
                   , dskWeight = 1, netWeight = 1 }
290

    
291
-- | Sum two utilisation records.
292
addUtil :: DynUtil -> DynUtil -> DynUtil
293
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
294
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
295

    
296
-- | Substracts one utilisation record from another.
297
subUtil :: DynUtil -> DynUtil -> DynUtil
298
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
299
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
300

    
301
-- | The description of an instance placement. It contains the
302
-- instance index, the new primary and secondary node, the move being
303
-- performed and the score of the cluster after the move.
304
type Placement = (Idx, Ndx, Ndx, IMove, Score)
305

    
306
-- | An instance move definition.
307
data IMove = Failover                -- ^ Failover the instance (f)
308
           | FailoverToAny Ndx       -- ^ Failover to a random node
309
                                     -- (fa:np), for shared storage
310
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
311
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
312
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
313
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
314
             deriving (Show)
315

    
316
-- | Formatted solution output for one move (involved nodes and
317
-- commands.
318
type MoveJob = ([Ndx], Idx, IMove, [String])
319

    
320
-- | Unknown field in table output.
321
unknownField :: String
322
unknownField = "<unknown field>"
323

    
324
-- | A list of command elements.
325
type JobSet = [MoveJob]
326

    
327
-- | Default max disk usage ratio.
328
defReservedDiskRatio :: Double
329
defReservedDiskRatio = 0
330

    
331
-- | Base memory unit.
332
unitMem :: Int
333
unitMem = 64
334

    
335
-- | Base disk unit.
336
unitDsk :: Int
337
unitDsk = 256
338

    
339
-- | Base vcpus unit.
340
unitCpu :: Int
341
unitCpu = 1
342

    
343
-- | Base spindles unit.
344
unitSpindle :: Int
345
unitSpindle = 1
346

    
347
-- | Reason for an operation's falure.
348
data FailMode = FailMem  -- ^ Failed due to not enough RAM
349
              | FailDisk -- ^ Failed due to not enough disk
350
              | FailCPU  -- ^ Failed due to not enough CPU capacity
351
              | FailN1   -- ^ Failed due to not passing N1 checks
352
              | FailTags -- ^ Failed due to tag exclusion
353
              | FailDiskCount -- ^ Failed due to wrong number of disks
354
              | FailSpindles -- ^ Failed due to wrong/missing spindles
355
              | FailInternal -- ^ Internal error
356
                deriving (Eq, Enum, Bounded, Show)
357

    
358
-- | List with failure statistics.
359
type FailStats = [(FailMode, Int)]
360

    
361
-- | Either-like data-type customized for our failure modes.
362
--
363
-- The failure values for this monad track the specific allocation
364
-- failures, so this is not a general error-monad (compare with the
365
-- 'Result' data type). One downside is that this type cannot encode a
366
-- generic failure mode, hence our way to build a FailMode from string
367
-- will instead raise an exception.
368
type OpResult = GenericResult FailMode
369

    
370
-- | 'Error' instance for 'FailMode' designed to catch unintended
371
-- use as a general monad.
372
instance Error FailMode where
373
  strMsg v = error $ "Programming error: OpResult used as generic monad" ++ v
374

    
375
-- | Conversion from 'OpResult' to 'Result'.
376
opToResult :: OpResult a -> Result a
377
opToResult (Bad f) = Bad $ show f
378
opToResult (Ok v) = Ok v
379

    
380
-- | A generic class for items that have updateable names and indices.
381
class Element a where
382
  -- | Returns the name of the element
383
  nameOf  :: a -> String
384
  -- | Returns all the known names of the element
385
  allNames :: a -> [String]
386
  -- | Returns the index of the element
387
  idxOf   :: a -> Int
388
  -- | Updates the alias of the element
389
  setAlias :: a -> String -> a
390
  -- | Compute the alias by stripping a given suffix (domain) from
391
  -- the name
392
  computeAlias :: String -> a -> a
393
  computeAlias dom e = setAlias e alias
394
    where alias = take (length name - length dom) name
395
          name = nameOf e
396
  -- | Updates the index of the element
397
  setIdx  :: a -> Int -> a
398

    
399
-- | The repair modes for the auto-repair tool.
400
$(THH.declareLADT ''String "AutoRepairType"
401
  -- Order is important here: from least destructive to most.
402
  [ ("ArFixStorage", "fix-storage")
403
  , ("ArMigrate",    "migrate")
404
  , ("ArFailover",   "failover")
405
  , ("ArReinstall",  "reinstall")
406
  ])
407

    
408
-- | The possible auto-repair results.
409
$(THH.declareLADT ''String "AutoRepairResult"
410
  -- Order is important here: higher results take precedence when an object
411
  -- has several result annotations attached.
412
  [ ("ArEnoperm", "enoperm")
413
  , ("ArSuccess", "success")
414
  , ("ArFailure", "failure")
415
  ])
416

    
417
-- | The possible auto-repair policy for a given instance.
418
data AutoRepairPolicy
419
  = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
420
  | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
421
  | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
422
  deriving (Eq, Show)
423

    
424
-- | The suspend timeout for 'ArSuspended'.
425
data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
426
                           | Until ClockTime -- ^ Suspended up to a certain time
427
                           deriving (Eq, Show)
428

    
429
-- | The possible auto-repair states for any given instance.
430
data AutoRepairStatus
431
  = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
432
  | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
433
  | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
434
  | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
435
  deriving (Eq, Show)
436

    
437
-- | The data accompanying a repair operation (future, pending, or failed).
438
data AutoRepairData = AutoRepairData { arType :: AutoRepairType
439
                                     , arUuid :: String
440
                                     , arTime :: ClockTime
441
                                     , arJobs :: [JobId]
442
                                     , arResult :: Maybe AutoRepairResult
443
                                     , arTag :: String
444
                                     }
445
                    deriving (Eq, Show)