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