Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 3e77a36c

History | View | Annotate | Download (12.4 kB)

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
  ) where
82

    
83
import qualified Data.Map as M
84

    
85
import qualified Ganeti.Constants as C
86
import qualified Ganeti.THH as THH
87
import Ganeti.BasicTypes
88
import Ganeti.Types
89

    
90
-- | The instance index type.
91
type Idx = Int
92

    
93
-- | The node index type.
94
type Ndx = Int
95

    
96
-- | The group index type.
97
type Gdx = Int
98

    
99
-- | The type used to hold name-to-idx mappings.
100
type NameAssoc = M.Map String Int
101

    
102
-- | A separate name for the cluster score type.
103
type Score = Double
104

    
105
-- | A separate name for a weight metric.
106
type Weight = Double
107

    
108
-- | The Group UUID type.
109
type GroupID = String
110

    
111
-- | Default group UUID (just a string, not a real UUID).
112
defaultGroupID :: GroupID
113
defaultGroupID = "00000000-0000-0000-0000-000000000000"
114

    
115
-- | Mirroring type.
116
data MirrorType = MirrorNone     -- ^ No mirroring/movability
117
                | MirrorInternal -- ^ DRBD-type mirroring
118
                | MirrorExternal -- ^ Shared-storage type mirroring
119
                  deriving (Eq, Show)
120

    
121
-- | Correspondence between disk template and mirror type.
122
templateMirrorType :: DiskTemplate -> MirrorType
123
templateMirrorType DTDiskless   = MirrorExternal
124
templateMirrorType DTFile       = MirrorNone
125
templateMirrorType DTSharedFile = MirrorExternal
126
templateMirrorType DTPlain      = MirrorNone
127
templateMirrorType DTBlock      = MirrorExternal
128
templateMirrorType DTDrbd8      = MirrorInternal
129
templateMirrorType DTRbd        = MirrorExternal
130
templateMirrorType DTExt        = MirrorExternal
131

    
132
-- | The resource spec type.
133
data RSpec = RSpec
134
  { rspecCpu  :: Int  -- ^ Requested VCPUs
135
  , rspecMem  :: Int  -- ^ Requested memory
136
  , rspecDsk  :: Int  -- ^ Requested disk
137
  } deriving (Show, Eq)
138

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

    
151
-- | Currently used, possibly to allocate, unallocable.
152
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
153

    
154
-- | Instance specification type.
155
$(THH.buildObject "ISpec" "iSpec"
156
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
157
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
158
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
159
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
160
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
161
  , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
162
  ])
163

    
164
-- | The default minimum ispec.
165
defMinISpec :: ISpec
166
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinMemorySize
167
                    , iSpecCpuCount   = C.ipolicyDefaultsMinCpuCount
168
                    , iSpecDiskSize   = C.ipolicyDefaultsMinDiskSize
169
                    , iSpecDiskCount  = C.ipolicyDefaultsMinDiskCount
170
                    , iSpecNicCount   = C.ipolicyDefaultsMinNicCount
171
                    , iSpecSpindleUse = C.ipolicyDefaultsMinSpindleUse
172
                    }
173

    
174
-- | The default standard ispec.
175
defStdISpec :: ISpec
176
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
177
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
178
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
179
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
180
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
181
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
182
                    }
183

    
184
-- | The default max ispec.
185
defMaxISpec :: ISpec
186
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMaxMemorySize
187
                    , iSpecCpuCount   = C.ipolicyDefaultsMaxCpuCount
188
                    , iSpecDiskSize   = C.ipolicyDefaultsMaxDiskSize
189
                    , iSpecDiskCount  = C.ipolicyDefaultsMaxDiskCount
190
                    , iSpecNicCount   = C.ipolicyDefaultsMaxNicCount
191
                    , iSpecSpindleUse = C.ipolicyDefaultsMaxSpindleUse
192
                    }
193

    
194
-- | Instance policy type.
195
$(THH.buildObject "IPolicy" "iPolicy"
196
  [ THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
197
  , THH.renameField "MinSpec" $ THH.simpleField C.ispecsMin [t| ISpec |]
198
  , THH.renameField "MaxSpec" $ THH.simpleField C.ispecsMax [t| ISpec |]
199
  , THH.renameField "DiskTemplates" $
200
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
201
  , THH.renameField "VcpuRatio" $
202
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
203
  , THH.renameField "SpindleRatio" $
204
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
205
  ])
206

    
207
-- | Converts an ISpec type to a RSpec one.
208
rspecFromISpec :: ISpec -> RSpec
209
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
210
                             , rspecMem = iSpecMemorySize ispec
211
                             , rspecDsk = iSpecDiskSize ispec
212
                             }
213

    
214
-- | The default instance policy.
215
defIPolicy :: IPolicy
216
defIPolicy = IPolicy { iPolicyStdSpec = defStdISpec
217
                     , iPolicyMinSpec = defMinISpec
218
                     , iPolicyMaxSpec = defMaxISpec
219
                     -- hardcoding here since Constants.hs exports the
220
                     -- string values, not the actual type; and in
221
                     -- htools, we are mostly looking at DRBD
222
                     , iPolicyDiskTemplates = [minBound..maxBound]
223
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
224
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
225
                     }
226

    
227
-- | The dynamic resource specs of a machine (i.e. load or load
228
-- capacity, as opposed to size).
229
data DynUtil = DynUtil
230
  { cpuWeight :: Weight -- ^ Standardised CPU usage
231
  , memWeight :: Weight -- ^ Standardised memory load
232
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
233
  , netWeight :: Weight -- ^ Standardised network usage
234
  } deriving (Show, Eq)
235

    
236
-- | Initial empty utilisation.
237
zeroUtil :: DynUtil
238
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
239
                   , dskWeight = 0, netWeight = 0 }
240

    
241
-- | Base utilisation (used when no actual utilisation data is
242
-- supplied).
243
baseUtil :: DynUtil
244
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
245
                   , dskWeight = 1, netWeight = 1 }
246

    
247
-- | Sum two utilisation records.
248
addUtil :: DynUtil -> DynUtil -> DynUtil
249
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
250
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
251

    
252
-- | Substracts one utilisation record from another.
253
subUtil :: DynUtil -> DynUtil -> DynUtil
254
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
255
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
256

    
257
-- | The description of an instance placement. It contains the
258
-- instance index, the new primary and secondary node, the move being
259
-- performed and the score of the cluster after the move.
260
type Placement = (Idx, Ndx, Ndx, IMove, Score)
261

    
262
-- | An instance move definition.
263
data IMove = Failover                -- ^ Failover the instance (f)
264
           | FailoverToAny Ndx       -- ^ Failover to a random node
265
                                     -- (fa:np), for shared storage
266
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
267
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
268
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
269
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
270
             deriving (Show)
271

    
272
-- | Formatted solution output for one move (involved nodes and
273
-- commands.
274
type MoveJob = ([Ndx], Idx, IMove, [String])
275

    
276
-- | Unknown field in table output.
277
unknownField :: String
278
unknownField = "<unknown field>"
279

    
280
-- | A list of command elements.
281
type JobSet = [MoveJob]
282

    
283
-- | Default max disk usage ratio.
284
defReservedDiskRatio :: Double
285
defReservedDiskRatio = 0
286

    
287
-- | Base memory unit.
288
unitMem :: Int
289
unitMem = 64
290

    
291
-- | Base disk unit.
292
unitDsk :: Int
293
unitDsk = 256
294

    
295
-- | Base vcpus unit.
296
unitCpu :: Int
297
unitCpu = 1
298

    
299
-- | Reason for an operation's falure.
300
data FailMode = FailMem  -- ^ Failed due to not enough RAM
301
              | FailDisk -- ^ Failed due to not enough disk
302
              | FailCPU  -- ^ Failed due to not enough CPU capacity
303
              | FailN1   -- ^ Failed due to not passing N1 checks
304
              | FailTags -- ^ Failed due to tag exclusion
305
                deriving (Eq, Enum, Bounded, Show)
306

    
307
-- | List with failure statistics.
308
type FailStats = [(FailMode, Int)]
309

    
310
-- | Either-like data-type customized for our failure modes.
311
--
312
-- The failure values for this monad track the specific allocation
313
-- failures, so this is not a general error-monad (compare with the
314
-- 'Result' data type). One downside is that this type cannot encode a
315
-- generic failure mode, hence our way to build a FailMode from string
316
-- will instead raise an exception.
317
type OpResult = GenericResult FailMode
318

    
319
-- | 'FromString' instance for 'FailMode' designed to catch unintended
320
-- use as a general monad.
321
instance FromString FailMode where
322
  mkFromString v = error $ "Programming error: OpResult used as generic monad"
323
                           ++ v
324

    
325
-- | Conversion from 'OpResult' to 'Result'.
326
opToResult :: OpResult a -> Result a
327
opToResult (Bad f) = Bad $ show f
328
opToResult (Ok v) = Ok v
329

    
330
-- | A generic class for items that have updateable names and indices.
331
class Element a where
332
  -- | Returns the name of the element
333
  nameOf  :: a -> String
334
  -- | Returns all the known names of the element
335
  allNames :: a -> [String]
336
  -- | Returns the index of the element
337
  idxOf   :: a -> Int
338
  -- | Updates the alias of the element
339
  setAlias :: a -> String -> a
340
  -- | Compute the alias by stripping a given suffix (domain) from
341
  -- the name
342
  computeAlias :: String -> a -> a
343
  computeAlias dom e = setAlias e alias
344
    where alias = take (length name - length dom) name
345
          name = nameOf e
346
  -- | Updates the index of the element
347
  setIdx  :: a -> Int -> a
348

    
349
-- | The iallocator node-evacuate evac_mode type.
350
$(THH.declareSADT "EvacMode"
351
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
352
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
353
       , ("ChangeAll",       'C.iallocatorNevacAll)
354
       ])
355
$(THH.makeJSONInstance ''EvacMode)
356

    
357
-- | The repair modes for the auto-repair tool.
358
$(THH.declareSADT "AutoRepairType"
359
       -- Order is important here: from least destructive to most.
360
       [ ("ArFixStorage", 'C.autoRepairFixStorage)
361
       , ("ArMigrate",    'C.autoRepairMigrate)
362
       , ("ArFailover",   'C.autoRepairFailover)
363
       , ("ArReinstall",  'C.autoRepairReinstall)
364
       ])
365

    
366
-- | The possible auto-repair results.
367
$(THH.declareSADT "AutoRepairResult"
368
       [ ("ArSuccess", 'C.autoRepairSuccess)
369
       , ("ArFailure", 'C.autoRepairFailure)
370
       , ("ArEnoperm", 'C.autoRepairEnoperm)
371
       ])