Merge branch 'stable-2.9' into stable-2.10
[ganeti-local] / src / Ganeti / HTools / Types.hs
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
144 -- | The resource spec type.
145 data RSpec = RSpec
146   { rspecCpu  :: Int  -- ^ Requested VCPUs
147   , rspecMem  :: Int  -- ^ Requested memory
148   , rspecDsk  :: Int  -- ^ Requested disk
149   , rspecSpn  :: Int  -- ^ Requested spindles
150   } deriving (Show, Eq)
151
152 -- | Allocation stats type. This is used instead of 'RSpec' (which was
153 -- used at first), because we need to track more stats. The actual
154 -- data can refer either to allocated, or available, etc. values
155 -- depending on the context. See also
156 -- 'Cluster.computeAllocationDelta'.
157 data AllocInfo = AllocInfo
158   { allocInfoVCpus :: Int    -- ^ VCPUs
159   , allocInfoNCpus :: Double -- ^ Normalised CPUs
160   , allocInfoMem   :: Int    -- ^ Memory
161   , allocInfoDisk  :: Int    -- ^ Disk
162   , allocInfoSpn   :: Int    -- ^ Spindles
163   } deriving (Show, Eq)
164
165 -- | Currently used, possibly to allocate, unallocable.
166 type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
167
168 -- | The network UUID type.
169 type NetworkID = String
170
171 -- | Instance specification type.
172 $(THH.buildObject "ISpec" "iSpec"
173   [ THH.renameField "MemorySize" $
174     THH.simpleField ConstantUtils.ispecMemSize    [t| Int |]
175   , THH.renameField "CpuCount"   $
176     THH.simpleField ConstantUtils.ispecCpuCount   [t| Int |]
177   , THH.renameField "DiskSize"   $
178     THH.simpleField ConstantUtils.ispecDiskSize   [t| Int |]
179   , THH.renameField "DiskCount"  $
180     THH.simpleField ConstantUtils.ispecDiskCount  [t| Int |]
181   , THH.renameField "NicCount"   $
182     THH.simpleField ConstantUtils.ispecNicCount   [t| Int |]
183   , THH.renameField "SpindleUse" $
184     THH.simpleField ConstantUtils.ispecSpindleUse [t| Int |]
185   ])
186
187 -- | The default minimum ispec.
188 defMinISpec :: ISpec
189 defMinISpec = ISpec { iSpecMemorySize = 128
190                     , iSpecCpuCount   = 1
191                     , iSpecDiskCount  = 1
192                     , iSpecDiskSize   = 1024
193                     , iSpecNicCount   = 1
194                     , iSpecSpindleUse = 1
195                     }
196
197 -- | The default standard ispec.
198 defStdISpec :: ISpec
199 defStdISpec = ISpec { iSpecMemorySize = 128
200                     , iSpecCpuCount   = 1
201                     , iSpecDiskCount  = 1
202                     , iSpecDiskSize   = 1024
203                     , iSpecNicCount   = 1
204                     , iSpecSpindleUse = 1
205                     }
206
207 maxDisks :: Int
208 maxDisks = 16
209
210 maxNics :: Int
211 maxNics = 8
212
213 -- | The default max ispec.
214 defMaxISpec :: ISpec
215 defMaxISpec = ISpec { iSpecMemorySize = 32768
216                     , iSpecCpuCount   = 8
217                     , iSpecDiskCount  = maxDisks
218                     , iSpecDiskSize   = 1024 * 1024
219                     , iSpecNicCount   = maxNics
220                     , iSpecSpindleUse = 12
221                     }
222
223 -- | Minimum and maximum instance specs type.
224 $(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
225   [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
226   , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
227   ])
228
229 -- | Defult minimum and maximum instance specs.
230 defMinMaxISpecs :: [MinMaxISpecs]
231 defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
232                                 , minMaxISpecsMaxSpec = defMaxISpec
233                                 }]
234
235 -- | Instance policy type.
236 $(THH.buildObject "IPolicy" "iPolicy"
237   [ THH.renameField "MinMaxISpecs" $
238       THH.simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
239   , THH.renameField "StdSpec" $
240       THH.simpleField ConstantUtils.ispecsStd [t| ISpec |]
241   , THH.renameField "DiskTemplates" $
242       THH.simpleField ConstantUtils.ipolicyDts [t| [DiskTemplate] |]
243   , THH.renameField "VcpuRatio" $
244       THH.simpleField ConstantUtils.ipolicyVcpuRatio [t| Double |]
245   , THH.renameField "SpindleRatio" $
246       THH.simpleField ConstantUtils.ipolicySpindleRatio [t| Double |]
247   ])
248
249 -- | Converts an ISpec type to a RSpec one.
250 rspecFromISpec :: ISpec -> RSpec
251 rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
252                              , rspecMem = iSpecMemorySize ispec
253                              , rspecDsk = iSpecDiskSize ispec
254                              , rspecSpn = iSpecSpindleUse ispec
255                              }
256
257 -- | The default instance policy.
258 defIPolicy :: IPolicy
259 defIPolicy =
260   IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
261           , iPolicyStdSpec = defStdISpec
262           -- hardcoding here since Constants.hs exports the
263           -- string values, not the actual type; and in
264           -- htools, we are mostly looking at DRBD
265           , iPolicyDiskTemplates = [minBound..maxBound]
266           , iPolicyVcpuRatio = ConstantUtils.ipolicyDefaultsVcpuRatio
267           , iPolicySpindleRatio = ConstantUtils.ipolicyDefaultsSpindleRatio
268           }
269
270 -- | The dynamic resource specs of a machine (i.e. load or load
271 -- capacity, as opposed to size).
272 data DynUtil = DynUtil
273   { cpuWeight :: Weight -- ^ Standardised CPU usage
274   , memWeight :: Weight -- ^ Standardised memory load
275   , dskWeight :: Weight -- ^ Standardised disk I\/O usage
276   , netWeight :: Weight -- ^ Standardised network usage
277   } deriving (Show, Eq)
278
279 -- | Initial empty utilisation.
280 zeroUtil :: DynUtil
281 zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
282                    , dskWeight = 0, netWeight = 0 }
283
284 -- | Base utilisation (used when no actual utilisation data is
285 -- supplied).
286 baseUtil :: DynUtil
287 baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
288                    , dskWeight = 1, netWeight = 1 }
289
290 -- | Sum two utilisation records.
291 addUtil :: DynUtil -> DynUtil -> DynUtil
292 addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
293   DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
294
295 -- | Substracts one utilisation record from another.
296 subUtil :: DynUtil -> DynUtil -> DynUtil
297 subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
298   DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
299
300 -- | The description of an instance placement. It contains the
301 -- instance index, the new primary and secondary node, the move being
302 -- performed and the score of the cluster after the move.
303 type Placement = (Idx, Ndx, Ndx, IMove, Score)
304
305 -- | An instance move definition.
306 data IMove = Failover                -- ^ Failover the instance (f)
307            | FailoverToAny Ndx       -- ^ Failover to a random node
308                                      -- (fa:np), for shared storage
309            | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
310            | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
311            | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
312            | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
313              deriving (Show)
314
315 -- | Formatted solution output for one move (involved nodes and
316 -- commands.
317 type MoveJob = ([Ndx], Idx, IMove, [String])
318
319 -- | Unknown field in table output.
320 unknownField :: String
321 unknownField = "<unknown field>"
322
323 -- | A list of command elements.
324 type JobSet = [MoveJob]
325
326 -- | Default max disk usage ratio.
327 defReservedDiskRatio :: Double
328 defReservedDiskRatio = 0
329
330 -- | Base memory unit.
331 unitMem :: Int
332 unitMem = 64
333
334 -- | Base disk unit.
335 unitDsk :: Int
336 unitDsk = 256
337
338 -- | Base vcpus unit.
339 unitCpu :: Int
340 unitCpu = 1
341
342 -- | Base spindles unit.
343 unitSpindle :: Int
344 unitSpindle = 1
345
346 -- | Reason for an operation's falure.
347 data FailMode = FailMem  -- ^ Failed due to not enough RAM
348               | FailDisk -- ^ Failed due to not enough disk
349               | FailCPU  -- ^ Failed due to not enough CPU capacity
350               | FailN1   -- ^ Failed due to not passing N1 checks
351               | FailTags -- ^ Failed due to tag exclusion
352               | FailDiskCount -- ^ Failed due to wrong number of disks
353               | FailSpindles -- ^ Failed due to wrong/missing spindles
354               | FailInternal -- ^ Internal error
355                 deriving (Eq, Enum, Bounded, Show)
356
357 -- | List with failure statistics.
358 type FailStats = [(FailMode, Int)]
359
360 -- | Either-like data-type customized for our failure modes.
361 --
362 -- The failure values for this monad track the specific allocation
363 -- failures, so this is not a general error-monad (compare with the
364 -- 'Result' data type). One downside is that this type cannot encode a
365 -- generic failure mode, hence our way to build a FailMode from string
366 -- will instead raise an exception.
367 type OpResult = GenericResult FailMode
368
369 -- | 'FromString' instance for 'FailMode' designed to catch unintended
370 -- use as a general monad.
371 instance FromString FailMode where
372   mkFromString v = error $ "Programming error: OpResult used as generic monad"
373                            ++ 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)