Statistics
| Branch: | Tag: | Revision:

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

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

    
88
import qualified Data.Map as M
89
import System.Time (ClockTime)
90

    
91
import qualified Ganeti.Constants as C
92
import qualified Ganeti.THH as THH
93
import Ganeti.BasicTypes
94
import Ganeti.Types
95

    
96
-- | The instance index type.
97
type Idx = Int
98

    
99
-- | The node index type.
100
type Ndx = Int
101

    
102
-- | The group index type.
103
type Gdx = Int
104

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

    
108
-- | A separate name for the cluster score type.
109
type Score = Double
110

    
111
-- | A separate name for a weight metric.
112
type Weight = Double
113

    
114
-- | The Group UUID type.
115
type GroupID = String
116

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

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

    
127
-- | Correspondence between disk template and mirror type.
128
templateMirrorType :: DiskTemplate -> MirrorType
129
templateMirrorType DTDiskless   = MirrorExternal
130
templateMirrorType DTFile       = MirrorNone
131
templateMirrorType DTSharedFile = MirrorExternal
132
templateMirrorType DTPlain      = MirrorNone
133
templateMirrorType DTBlock      = MirrorExternal
134
templateMirrorType DTDrbd8      = MirrorInternal
135
templateMirrorType DTRbd        = MirrorExternal
136
templateMirrorType DTExt        = MirrorExternal
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, Eq)
144

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

    
157
-- | Currently used, possibly to allocate, unallocable.
158
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
159

    
160
-- | Instance specification type.
161
$(THH.buildObject "ISpec" "iSpec"
162
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
163
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
164
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
165
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
166
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
167
  , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
168
  ])
169

    
170
-- | The default minimum ispec.
171
defMinISpec :: ISpec
172
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinmaxMinMemorySize
173
                    , iSpecCpuCount   = C.ipolicyDefaultsMinmaxMinCpuCount
174
                    , iSpecDiskSize   = C.ipolicyDefaultsMinmaxMinDiskSize
175
                    , iSpecDiskCount  = C.ipolicyDefaultsMinmaxMinDiskCount
176
                    , iSpecNicCount   = C.ipolicyDefaultsMinmaxMinNicCount
177
                    , iSpecSpindleUse = C.ipolicyDefaultsMinmaxMinSpindleUse
178
                    }
179

    
180
-- | The default standard ispec.
181
defStdISpec :: ISpec
182
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
183
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
184
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
185
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
186
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
187
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
188
                    }
189

    
190
-- | The default max ispec.
191
defMaxISpec :: ISpec
192
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinmaxMaxMemorySize
193
                    , iSpecCpuCount   = C.ipolicyDefaultsMinmaxMaxCpuCount
194
                    , iSpecDiskSize   = C.ipolicyDefaultsMinmaxMaxDiskSize
195
                    , iSpecDiskCount  = C.ipolicyDefaultsMinmaxMaxDiskCount
196
                    , iSpecNicCount   = C.ipolicyDefaultsMinmaxMaxNicCount
197
                    , iSpecSpindleUse = C.ipolicyDefaultsMinmaxMaxSpindleUse
198
                    }
199

    
200
-- | Minimum and maximum instance specs type.
201
$(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
202
  [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
203
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
204
  ])
205

    
206
-- | Defult minimum and maximum instance specs.
207
defMinMaxISpecs :: MinMaxISpecs
208
defMinMaxISpecs = MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
209
                               , minMaxISpecsMaxSpec = defMaxISpec
210
                               }
211

    
212
-- | Instance policy type.
213
$(THH.buildObject "IPolicy" "iPolicy"
214
  [ THH.renameField "MinMaxISpecs" $
215
      THH.simpleField C.ispecsMinmax [t| MinMaxISpecs |]
216
  , THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
217
  , THH.renameField "DiskTemplates" $
218
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
219
  , THH.renameField "VcpuRatio" $
220
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
221
  , THH.renameField "SpindleRatio" $
222
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
223
  ])
224

    
225
-- | Converts an ISpec type to a RSpec one.
226
rspecFromISpec :: ISpec -> RSpec
227
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
228
                             , rspecMem = iSpecMemorySize ispec
229
                             , rspecDsk = iSpecDiskSize ispec
230
                             }
231

    
232
-- | The default instance policy.
233
defIPolicy :: IPolicy
234
defIPolicy = IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
235
                     , iPolicyStdSpec = defStdISpec
236
                     -- hardcoding here since Constants.hs exports the
237
                     -- string values, not the actual type; and in
238
                     -- htools, we are mostly looking at DRBD
239
                     , iPolicyDiskTemplates = [minBound..maxBound]
240
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
241
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
242
                     }
243

    
244
-- | The dynamic resource specs of a machine (i.e. load or load
245
-- capacity, as opposed to size).
246
data DynUtil = DynUtil
247
  { cpuWeight :: Weight -- ^ Standardised CPU usage
248
  , memWeight :: Weight -- ^ Standardised memory load
249
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
250
  , netWeight :: Weight -- ^ Standardised network usage
251
  } deriving (Show, Eq)
252

    
253
-- | Initial empty utilisation.
254
zeroUtil :: DynUtil
255
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
256
                   , dskWeight = 0, netWeight = 0 }
257

    
258
-- | Base utilisation (used when no actual utilisation data is
259
-- supplied).
260
baseUtil :: DynUtil
261
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
262
                   , dskWeight = 1, netWeight = 1 }
263

    
264
-- | Sum two utilisation records.
265
addUtil :: DynUtil -> DynUtil -> DynUtil
266
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
267
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
268

    
269
-- | Substracts one utilisation record from another.
270
subUtil :: DynUtil -> DynUtil -> DynUtil
271
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
272
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
273

    
274
-- | The description of an instance placement. It contains the
275
-- instance index, the new primary and secondary node, the move being
276
-- performed and the score of the cluster after the move.
277
type Placement = (Idx, Ndx, Ndx, IMove, Score)
278

    
279
-- | An instance move definition.
280
data IMove = Failover                -- ^ Failover the instance (f)
281
           | FailoverToAny Ndx       -- ^ Failover to a random node
282
                                     -- (fa:np), for shared storage
283
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
284
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
285
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
286
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
287
             deriving (Show)
288

    
289
-- | Formatted solution output for one move (involved nodes and
290
-- commands.
291
type MoveJob = ([Ndx], Idx, IMove, [String])
292

    
293
-- | Unknown field in table output.
294
unknownField :: String
295
unknownField = "<unknown field>"
296

    
297
-- | A list of command elements.
298
type JobSet = [MoveJob]
299

    
300
-- | Default max disk usage ratio.
301
defReservedDiskRatio :: Double
302
defReservedDiskRatio = 0
303

    
304
-- | Base memory unit.
305
unitMem :: Int
306
unitMem = 64
307

    
308
-- | Base disk unit.
309
unitDsk :: Int
310
unitDsk = 256
311

    
312
-- | Base vcpus unit.
313
unitCpu :: Int
314
unitCpu = 1
315

    
316
-- | Reason for an operation's falure.
317
data FailMode = FailMem  -- ^ Failed due to not enough RAM
318
              | FailDisk -- ^ Failed due to not enough disk
319
              | FailCPU  -- ^ Failed due to not enough CPU capacity
320
              | FailN1   -- ^ Failed due to not passing N1 checks
321
              | FailTags -- ^ Failed due to tag exclusion
322
                deriving (Eq, Enum, Bounded, Show)
323

    
324
-- | List with failure statistics.
325
type FailStats = [(FailMode, Int)]
326

    
327
-- | Either-like data-type customized for our failure modes.
328
--
329
-- The failure values for this monad track the specific allocation
330
-- failures, so this is not a general error-monad (compare with the
331
-- 'Result' data type). One downside is that this type cannot encode a
332
-- generic failure mode, hence our way to build a FailMode from string
333
-- will instead raise an exception.
334
type OpResult = GenericResult FailMode
335

    
336
-- | 'FromString' instance for 'FailMode' designed to catch unintended
337
-- use as a general monad.
338
instance FromString FailMode where
339
  mkFromString v = error $ "Programming error: OpResult used as generic monad"
340
                           ++ v
341

    
342
-- | Conversion from 'OpResult' to 'Result'.
343
opToResult :: OpResult a -> Result a
344
opToResult (Bad f) = Bad $ show f
345
opToResult (Ok v) = Ok v
346

    
347
-- | A generic class for items that have updateable names and indices.
348
class Element a where
349
  -- | Returns the name of the element
350
  nameOf  :: a -> String
351
  -- | Returns all the known names of the element
352
  allNames :: a -> [String]
353
  -- | Returns the index of the element
354
  idxOf   :: a -> Int
355
  -- | Updates the alias of the element
356
  setAlias :: a -> String -> a
357
  -- | Compute the alias by stripping a given suffix (domain) from
358
  -- the name
359
  computeAlias :: String -> a -> a
360
  computeAlias dom e = setAlias e alias
361
    where alias = take (length name - length dom) name
362
          name = nameOf e
363
  -- | Updates the index of the element
364
  setIdx  :: a -> Int -> a
365

    
366
-- | The iallocator node-evacuate evac_mode type.
367
$(THH.declareSADT "EvacMode"
368
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
369
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
370
       , ("ChangeAll",       'C.iallocatorNevacAll)
371
       ])
372
$(THH.makeJSONInstance ''EvacMode)
373

    
374
-- | The repair modes for the auto-repair tool.
375
$(THH.declareSADT "AutoRepairType"
376
       -- Order is important here: from least destructive to most.
377
       [ ("ArFixStorage", 'C.autoRepairFixStorage)
378
       , ("ArMigrate",    'C.autoRepairMigrate)
379
       , ("ArFailover",   'C.autoRepairFailover)
380
       , ("ArReinstall",  'C.autoRepairReinstall)
381
       ])
382

    
383
-- | The possible auto-repair results.
384
$(THH.declareSADT "AutoRepairResult"
385
       -- Order is important here: higher results take precedence when an object
386
       -- has several result annotations attached.
387
       [ ("ArEnoperm", 'C.autoRepairEnoperm)
388
       , ("ArSuccess", 'C.autoRepairSuccess)
389
       , ("ArFailure", 'C.autoRepairFailure)
390
       ])
391

    
392
-- | The possible auto-repair policy for a given instance.
393
data AutoRepairPolicy
394
  = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
395
  | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
396
  | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
397
  deriving (Eq, Show)
398

    
399
-- | The suspend timeout for 'ArSuspended'.
400
data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
401
                           | Until ClockTime -- ^ Suspended up to a certain time
402
                           deriving (Eq, Show)
403

    
404
-- | The possible auto-repair states for any given instance.
405
data AutoRepairStatus
406
  = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
407
  | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
408
  | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
409
  | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
410
  deriving (Eq, Show)
411

    
412
-- | The data accompanying a repair operation (future, pending, or failed).
413
data AutoRepairData = AutoRepairData { arType :: AutoRepairType
414
                                     , arUuid :: String
415
                                     , arTime :: ClockTime
416
                                     , arJobs :: [JobId]
417
                                     , arResult :: Maybe AutoRepairResult
418
                                     , arTag :: String
419
                                     }
420
                    deriving (Eq, Show)