Merge 'EvacNode' and 'NodeEvacMode'
[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   , MinMaxISpecs(..)
74   , IPolicy(..)
75   , defIPolicy
76   , rspecFromISpec
77   , AutoRepairType(..)
78   , autoRepairTypeToRaw
79   , autoRepairTypeFromRaw
80   , AutoRepairResult(..)
81   , autoRepairResultToRaw
82   , autoRepairResultFromRaw
83   , AutoRepairPolicy(..)
84   , AutoRepairSuspendTime(..)
85   , AutoRepairData(..)
86   , AutoRepairStatus(..)
87   ) where
88
89 import qualified Data.Map as M
90 import System.Time (ClockTime)
91
92 import qualified Ganeti.Constants as C
93 import qualified Ganeti.THH as THH
94 import Ganeti.BasicTypes
95 import Ganeti.Types
96
97 -- | The instance index type.
98 type Idx = Int
99
100 -- | The node index type.
101 type Ndx = Int
102
103 -- | The group index type.
104 type Gdx = Int
105
106 -- | The type used to hold name-to-idx mappings.
107 type NameAssoc = M.Map String Int
108
109 -- | A separate name for the cluster score type.
110 type Score = Double
111
112 -- | A separate name for a weight metric.
113 type Weight = Double
114
115 -- | The Group UUID type.
116 type GroupID = String
117
118 -- | Default group UUID (just a string, not a real UUID).
119 defaultGroupID :: GroupID
120 defaultGroupID = "00000000-0000-0000-0000-000000000000"
121
122 -- | Mirroring type.
123 data MirrorType = MirrorNone     -- ^ No mirroring/movability
124                 | MirrorInternal -- ^ DRBD-type mirroring
125                 | MirrorExternal -- ^ Shared-storage type mirroring
126                   deriving (Eq, Show)
127
128 -- | Correspondence between disk template and mirror type.
129 templateMirrorType :: DiskTemplate -> MirrorType
130 templateMirrorType DTDiskless   = MirrorExternal
131 templateMirrorType DTFile       = MirrorNone
132 templateMirrorType DTSharedFile = MirrorExternal
133 templateMirrorType DTPlain      = MirrorNone
134 templateMirrorType DTBlock      = MirrorExternal
135 templateMirrorType DTDrbd8      = MirrorInternal
136 templateMirrorType DTRbd        = MirrorExternal
137 templateMirrorType DTExt        = MirrorExternal
138
139 -- | The resource spec type.
140 data RSpec = RSpec
141   { rspecCpu  :: Int  -- ^ Requested VCPUs
142   , rspecMem  :: Int  -- ^ Requested memory
143   , rspecDsk  :: Int  -- ^ Requested disk
144   , rspecSpn  :: Int  -- ^ Requested spindles
145   } deriving (Show, Eq)
146
147 -- | Allocation stats type. This is used instead of 'RSpec' (which was
148 -- used at first), because we need to track more stats. The actual
149 -- data can refer either to allocated, or available, etc. values
150 -- depending on the context. See also
151 -- 'Cluster.computeAllocationDelta'.
152 data AllocInfo = AllocInfo
153   { allocInfoVCpus :: Int    -- ^ VCPUs
154   , allocInfoNCpus :: Double -- ^ Normalised CPUs
155   , allocInfoMem   :: Int    -- ^ Memory
156   , allocInfoDisk  :: Int    -- ^ Disk
157   , allocInfoSpn   :: Int    -- ^ Spindles
158   } deriving (Show, Eq)
159
160 -- | Currently used, possibly to allocate, unallocable.
161 type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
162
163 -- | The network UUID type.
164 type NetworkID = String
165
166 -- | Instance specification type.
167 $(THH.buildObject "ISpec" "iSpec"
168   [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
169   , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
170   , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
171   , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
172   , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
173   , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
174   ])
175
176 -- | The default minimum ispec.
177 defMinISpec :: ISpec
178 defMinISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMinMemorySize
179                     , iSpecCpuCount   = C.ispecsMinmaxDefaultsMinCpuCount
180                     , iSpecDiskSize   = C.ispecsMinmaxDefaultsMinDiskSize
181                     , iSpecDiskCount  = C.ispecsMinmaxDefaultsMinDiskCount
182                     , iSpecNicCount   = C.ispecsMinmaxDefaultsMinNicCount
183                     , iSpecSpindleUse = C.ispecsMinmaxDefaultsMinSpindleUse
184                     }
185
186 -- | The default standard ispec.
187 defStdISpec :: ISpec
188 defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
189                     , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
190                     , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
191                     , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
192                     , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
193                     , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
194                     }
195
196 -- | The default max ispec.
197 defMaxISpec :: ISpec
198 defMaxISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMaxMemorySize
199                     , iSpecCpuCount   = C.ispecsMinmaxDefaultsMaxCpuCount
200                     , iSpecDiskSize   = C.ispecsMinmaxDefaultsMaxDiskSize
201                     , iSpecDiskCount  = C.ispecsMinmaxDefaultsMaxDiskCount
202                     , iSpecNicCount   = C.ispecsMinmaxDefaultsMaxNicCount
203                     , iSpecSpindleUse = C.ispecsMinmaxDefaultsMaxSpindleUse
204                     }
205
206 -- | Minimum and maximum instance specs type.
207 $(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
208   [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
209   , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
210   ])
211
212 -- | Defult minimum and maximum instance specs.
213 defMinMaxISpecs :: [MinMaxISpecs]
214 defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
215                                 , minMaxISpecsMaxSpec = defMaxISpec
216                                 }]
217
218 -- | Instance policy type.
219 $(THH.buildObject "IPolicy" "iPolicy"
220   [ THH.renameField "MinMaxISpecs" $
221       THH.simpleField C.ispecsMinmax [t| [MinMaxISpecs] |]
222   , THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
223   , THH.renameField "DiskTemplates" $
224       THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
225   , THH.renameField "VcpuRatio" $
226       THH.simpleField C.ipolicyVcpuRatio [t| Double |]
227   , THH.renameField "SpindleRatio" $
228       THH.simpleField C.ipolicySpindleRatio [t| Double |]
229   ])
230
231 -- | Converts an ISpec type to a RSpec one.
232 rspecFromISpec :: ISpec -> RSpec
233 rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
234                              , rspecMem = iSpecMemorySize ispec
235                              , rspecDsk = iSpecDiskSize ispec
236                              , rspecSpn = iSpecSpindleUse ispec
237                              }
238
239 -- | The default instance policy.
240 defIPolicy :: IPolicy
241 defIPolicy = IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
242                      , iPolicyStdSpec = defStdISpec
243                      -- hardcoding here since Constants.hs exports the
244                      -- string values, not the actual type; and in
245                      -- htools, we are mostly looking at DRBD
246                      , iPolicyDiskTemplates = [minBound..maxBound]
247                      , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
248                      , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
249                      }
250
251 -- | The dynamic resource specs of a machine (i.e. load or load
252 -- capacity, as opposed to size).
253 data DynUtil = DynUtil
254   { cpuWeight :: Weight -- ^ Standardised CPU usage
255   , memWeight :: Weight -- ^ Standardised memory load
256   , dskWeight :: Weight -- ^ Standardised disk I\/O usage
257   , netWeight :: Weight -- ^ Standardised network usage
258   } deriving (Show, Eq)
259
260 -- | Initial empty utilisation.
261 zeroUtil :: DynUtil
262 zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
263                    , dskWeight = 0, netWeight = 0 }
264
265 -- | Base utilisation (used when no actual utilisation data is
266 -- supplied).
267 baseUtil :: DynUtil
268 baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
269                    , dskWeight = 1, netWeight = 1 }
270
271 -- | Sum two utilisation records.
272 addUtil :: DynUtil -> DynUtil -> DynUtil
273 addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
274   DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
275
276 -- | Substracts one utilisation record from another.
277 subUtil :: DynUtil -> DynUtil -> DynUtil
278 subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
279   DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
280
281 -- | The description of an instance placement. It contains the
282 -- instance index, the new primary and secondary node, the move being
283 -- performed and the score of the cluster after the move.
284 type Placement = (Idx, Ndx, Ndx, IMove, Score)
285
286 -- | An instance move definition.
287 data IMove = Failover                -- ^ Failover the instance (f)
288            | FailoverToAny Ndx       -- ^ Failover to a random node
289                                      -- (fa:np), for shared storage
290            | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
291            | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
292            | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
293            | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
294              deriving (Show)
295
296 -- | Formatted solution output for one move (involved nodes and
297 -- commands.
298 type MoveJob = ([Ndx], Idx, IMove, [String])
299
300 -- | Unknown field in table output.
301 unknownField :: String
302 unknownField = "<unknown field>"
303
304 -- | A list of command elements.
305 type JobSet = [MoveJob]
306
307 -- | Default max disk usage ratio.
308 defReservedDiskRatio :: Double
309 defReservedDiskRatio = 0
310
311 -- | Base memory unit.
312 unitMem :: Int
313 unitMem = 64
314
315 -- | Base disk unit.
316 unitDsk :: Int
317 unitDsk = 256
318
319 -- | Base vcpus unit.
320 unitCpu :: Int
321 unitCpu = 1
322
323 -- | Base spindles unit.
324 unitSpindle :: Int
325 unitSpindle = 1
326
327 -- | Reason for an operation's falure.
328 data FailMode = FailMem  -- ^ Failed due to not enough RAM
329               | FailDisk -- ^ Failed due to not enough disk
330               | FailCPU  -- ^ Failed due to not enough CPU capacity
331               | FailN1   -- ^ Failed due to not passing N1 checks
332               | FailTags -- ^ Failed due to tag exclusion
333               | FailDiskCount -- ^ Failed due to wrong number of disks
334               | FailSpindles -- ^ Failed due to wrong/missing spindles
335               | FailInternal -- ^ Internal error
336                 deriving (Eq, Enum, Bounded, Show)
337
338 -- | List with failure statistics.
339 type FailStats = [(FailMode, Int)]
340
341 -- | Either-like data-type customized for our failure modes.
342 --
343 -- The failure values for this monad track the specific allocation
344 -- failures, so this is not a general error-monad (compare with the
345 -- 'Result' data type). One downside is that this type cannot encode a
346 -- generic failure mode, hence our way to build a FailMode from string
347 -- will instead raise an exception.
348 type OpResult = GenericResult FailMode
349
350 -- | 'FromString' instance for 'FailMode' designed to catch unintended
351 -- use as a general monad.
352 instance FromString FailMode where
353   mkFromString v = error $ "Programming error: OpResult used as generic monad"
354                            ++ v
355
356 -- | Conversion from 'OpResult' to 'Result'.
357 opToResult :: OpResult a -> Result a
358 opToResult (Bad f) = Bad $ show f
359 opToResult (Ok v) = Ok v
360
361 -- | A generic class for items that have updateable names and indices.
362 class Element a where
363   -- | Returns the name of the element
364   nameOf  :: a -> String
365   -- | Returns all the known names of the element
366   allNames :: a -> [String]
367   -- | Returns the index of the element
368   idxOf   :: a -> Int
369   -- | Updates the alias of the element
370   setAlias :: a -> String -> a
371   -- | Compute the alias by stripping a given suffix (domain) from
372   -- the name
373   computeAlias :: String -> a -> a
374   computeAlias dom e = setAlias e alias
375     where alias = take (length name - length dom) name
376           name = nameOf e
377   -- | Updates the index of the element
378   setIdx  :: a -> Int -> a
379
380 -- | The repair modes for the auto-repair tool.
381 $(THH.declareSADT "AutoRepairType"
382        -- Order is important here: from least destructive to most.
383        [ ("ArFixStorage", 'C.autoRepairFixStorage)
384        , ("ArMigrate",    'C.autoRepairMigrate)
385        , ("ArFailover",   'C.autoRepairFailover)
386        , ("ArReinstall",  'C.autoRepairReinstall)
387        ])
388
389 -- | The possible auto-repair results.
390 $(THH.declareSADT "AutoRepairResult"
391        -- Order is important here: higher results take precedence when an object
392        -- has several result annotations attached.
393        [ ("ArEnoperm", 'C.autoRepairEnoperm)
394        , ("ArSuccess", 'C.autoRepairSuccess)
395        , ("ArFailure", 'C.autoRepairFailure)
396        ])
397
398 -- | The possible auto-repair policy for a given instance.
399 data AutoRepairPolicy
400   = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
401   | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
402   | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
403   deriving (Eq, Show)
404
405 -- | The suspend timeout for 'ArSuspended'.
406 data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
407                            | Until ClockTime -- ^ Suspended up to a certain time
408                            deriving (Eq, Show)
409
410 -- | The possible auto-repair states for any given instance.
411 data AutoRepairStatus
412   = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
413   | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
414   | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
415   | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
416   deriving (Eq, Show)
417
418 -- | The data accompanying a repair operation (future, pending, or failed).
419 data AutoRepairData = AutoRepairData { arType :: AutoRepairType
420                                      , arUuid :: String
421                                      , arTime :: ClockTime
422                                      , arJobs :: [JobId]
423                                      , arResult :: Maybe AutoRepairResult
424                                      , arTag :: String
425                                      }
426                     deriving (Eq, Show)