Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ a8038349

History | View | Annotate | Download (13.1 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
  ) where
76

    
77
import qualified Data.Map as M
78
import Text.JSON (makeObj, readJSON, showJSON)
79

    
80
import qualified Ganeti.Constants as C
81
import qualified Ganeti.THH as THH
82
import Ganeti.BasicTypes
83
import Ganeti.JSON
84

    
85
-- | The instance index type.
86
type Idx = Int
87

    
88
-- | The node index type.
89
type Ndx = Int
90

    
91
-- | The group index type.
92
type Gdx = Int
93

    
94
-- | The type used to hold name-to-idx mappings.
95
type NameAssoc = M.Map String Int
96

    
97
-- | A separate name for the cluster score type.
98
type Score = Double
99

    
100
-- | A separate name for a weight metric.
101
type Weight = Double
102

    
103
-- | The Group UUID type.
104
type GroupID = String
105

    
106
-- | Default group UUID (just a string, not a real UUID).
107
defaultGroupID :: GroupID
108
defaultGroupID = "00000000-0000-0000-0000-000000000000"
109

    
110
-- | Instance disk template type.
111
$(THH.declareSADT "DiskTemplate"
112
       [ ("DTDiskless",   'C.dtDiskless)
113
       , ("DTFile",       'C.dtFile)
114
       , ("DTSharedFile", 'C.dtSharedFile)
115
       , ("DTPlain",      'C.dtPlain)
116
       , ("DTBlock",      'C.dtBlock)
117
       , ("DTDrbd8",      'C.dtDrbd8)
118
       , ("DTRbd",        'C.dtRbd)
119
       ])
120
$(THH.makeJSONInstance ''DiskTemplate)
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, Read)
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

    
138
-- | The Group allocation policy type.
139
--
140
-- Note that the order of constructors is important as the automatic
141
-- Ord instance will order them in the order they are defined, so when
142
-- changing this data type be careful about the interaction with the
143
-- desired sorting order.
144
$(THH.declareSADT "AllocPolicy"
145
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
146
       , ("AllocLastResort",  'C.allocPolicyLastResort)
147
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
148
       ])
149
$(THH.makeJSONInstance ''AllocPolicy)
150

    
151
-- | The Instance real state type.
152
$(THH.declareSADT "InstanceStatus"
153
       [ ("AdminDown", 'C.inststAdmindown)
154
       , ("AdminOffline", 'C.inststAdminoffline)
155
       , ("ErrorDown", 'C.inststErrordown)
156
       , ("ErrorUp", 'C.inststErrorup)
157
       , ("NodeDown", 'C.inststNodedown)
158
       , ("NodeOffline", 'C.inststNodeoffline)
159
       , ("Running", 'C.inststRunning)
160
       , ("WrongNode", 'C.inststWrongnode)
161
       ])
162
$(THH.makeJSONInstance ''InstanceStatus)
163

    
164
-- | The resource spec type.
165
data RSpec = RSpec
166
  { rspecCpu  :: Int  -- ^ Requested VCPUs
167
  , rspecMem  :: Int  -- ^ Requested memory
168
  , rspecDsk  :: Int  -- ^ Requested disk
169
  } deriving (Show, Read, Eq)
170

    
171
-- | Allocation stats type. This is used instead of 'RSpec' (which was
172
-- used at first), because we need to track more stats. The actual
173
-- data can refer either to allocated, or available, etc. values
174
-- depending on the context. See also
175
-- 'Cluster.computeAllocationDelta'.
176
data AllocInfo = AllocInfo
177
  { allocInfoVCpus :: Int    -- ^ VCPUs
178
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
179
  , allocInfoMem   :: Int    -- ^ Memory
180
  , allocInfoDisk  :: Int    -- ^ Disk
181
  } deriving (Show, Read, Eq)
182

    
183
-- | Currently used, possibly to allocate, unallocable.
184
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
185

    
186
-- | Instance specification type.
187
$(THH.buildObject "ISpec" "iSpec"
188
  [ THH.renameField "MemorySize"   $ THH.simpleField C.ispecMemSize      [t| Int |]
189
  , THH.renameField "CpuCount"     $ THH.simpleField C.ispecCpuCount     [t| Int |]
190
  , THH.renameField "DiskSize"     $ THH.simpleField C.ispecDiskSize     [t| Int |]
191
  , THH.renameField "DiskCount"    $ THH.simpleField C.ispecDiskCount    [t| Int |]
192
  , THH.renameField "NicCount"     $ THH.simpleField C.ispecNicCount     [t| Int |]
193
  , THH.renameField "SpindleUse"   $ THH.simpleField C.ispecSpindleUse   [t| Int |]
194
  ])
195

    
196
-- | The default minimum ispec.
197
defMinISpec :: ISpec
198
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinMemorySize
199
                    , iSpecCpuCount   = C.ipolicyDefaultsMinCpuCount
200
                    , iSpecDiskSize   = C.ipolicyDefaultsMinDiskSize
201
                    , iSpecDiskCount  = C.ipolicyDefaultsMinDiskCount
202
                    , iSpecNicCount   = C.ipolicyDefaultsMinNicCount
203
                    , iSpecSpindleUse = C.ipolicyDefaultsMinSpindleUse
204
                    }
205

    
206
-- | The default standard ispec.
207
defStdISpec :: ISpec
208
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
209
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
210
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
211
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
212
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
213
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
214
                    }
215

    
216
-- | The default max ispec.
217
defMaxISpec :: ISpec
218
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMaxMemorySize
219
                    , iSpecCpuCount   = C.ipolicyDefaultsMaxCpuCount
220
                    , iSpecDiskSize   = C.ipolicyDefaultsMaxDiskSize
221
                    , iSpecDiskCount  = C.ipolicyDefaultsMaxDiskCount
222
                    , iSpecNicCount   = C.ipolicyDefaultsMaxNicCount
223
                    , iSpecSpindleUse = C.ipolicyDefaultsMaxSpindleUse
224
                    }
225

    
226
-- | Instance policy type.
227
$(THH.buildObject "IPolicy" "iPolicy"
228
  [ THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
229
  , THH.renameField "MinSpec" $ THH.simpleField C.ispecsMin [t| ISpec |]
230
  , THH.renameField "MaxSpec" $ THH.simpleField C.ispecsMax [t| ISpec |]
231
  , THH.renameField "DiskTemplates" $
232
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
233
  , THH.renameField "VcpuRatio" $
234
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
235
  , THH.renameField "SpindleRatio" $
236
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
237
  ])
238

    
239
-- | Converts an ISpec type to a RSpec one.
240
rspecFromISpec :: ISpec -> RSpec
241
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
242
                             , rspecMem = iSpecMemorySize ispec
243
                             , rspecDsk = iSpecDiskSize ispec
244
                             }
245

    
246
-- | The default instance policy.
247
defIPolicy :: IPolicy
248
defIPolicy = IPolicy { iPolicyStdSpec = defStdISpec
249
                     , iPolicyMinSpec = defMinISpec
250
                     , iPolicyMaxSpec = defMaxISpec
251
                     -- hardcoding here since Constants.hs exports the
252
                     -- string values, not the actual type; and in
253
                     -- htools, we are mostly looking at DRBD
254
                     , iPolicyDiskTemplates = [minBound..maxBound]
255
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
256
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
257
                     }
258

    
259
-- | The dynamic resource specs of a machine (i.e. load or load
260
-- capacity, as opposed to size).
261
data DynUtil = DynUtil
262
  { cpuWeight :: Weight -- ^ Standardised CPU usage
263
  , memWeight :: Weight -- ^ Standardised memory load
264
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
265
  , netWeight :: Weight -- ^ Standardised network usage
266
  } deriving (Show, Read, Eq)
267

    
268
-- | Initial empty utilisation.
269
zeroUtil :: DynUtil
270
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
271
                   , dskWeight = 0, netWeight = 0 }
272

    
273
-- | Base utilisation (used when no actual utilisation data is
274
-- supplied).
275
baseUtil :: DynUtil
276
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
277
                   , dskWeight = 1, netWeight = 1 }
278

    
279
-- | Sum two utilisation records.
280
addUtil :: DynUtil -> DynUtil -> DynUtil
281
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
282
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
283

    
284
-- | Substracts one utilisation record from another.
285
subUtil :: DynUtil -> DynUtil -> DynUtil
286
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
287
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
288

    
289
-- | The description of an instance placement. It contains the
290
-- instance index, the new primary and secondary node, the move being
291
-- performed and the score of the cluster after the move.
292
type Placement = (Idx, Ndx, Ndx, IMove, Score)
293

    
294
-- | An instance move definition.
295
data IMove = Failover                -- ^ Failover the instance (f)
296
           | FailoverToAny Ndx       -- ^ Failover to a random node
297
                                     -- (fa:np), for shared storage
298
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
299
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
300
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
301
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
302
             deriving (Show, Read)
303

    
304
-- | Formatted solution output for one move (involved nodes and
305
-- commands.
306
type MoveJob = ([Ndx], Idx, IMove, [String])
307

    
308
-- | Unknown field in table output.
309
unknownField :: String
310
unknownField = "<unknown field>"
311

    
312
-- | A list of command elements.
313
type JobSet = [MoveJob]
314

    
315
-- | Default max disk usage ratio.
316
defReservedDiskRatio :: Double
317
defReservedDiskRatio = 0
318

    
319
-- | Base memory unit.
320
unitMem :: Int
321
unitMem = 64
322

    
323
-- | Base disk unit.
324
unitDsk :: Int
325
unitDsk = 256
326

    
327
-- | Base vcpus unit.
328
unitCpu :: Int
329
unitCpu = 1
330

    
331
-- | Reason for an operation's falure.
332
data FailMode = FailMem  -- ^ Failed due to not enough RAM
333
              | FailDisk -- ^ Failed due to not enough disk
334
              | FailCPU  -- ^ Failed due to not enough CPU capacity
335
              | FailN1   -- ^ Failed due to not passing N1 checks
336
              | FailTags -- ^ Failed due to tag exclusion
337
                deriving (Eq, Enum, Bounded, Show, Read)
338

    
339
-- | List with failure statistics.
340
type FailStats = [(FailMode, Int)]
341

    
342
-- | Either-like data-type customized for our failure modes.
343
--
344
-- The failure values for this monad track the specific allocation
345
-- failures, so this is not a general error-monad (compare with the
346
-- 'Result' data type). One downside is that this type cannot encode a
347
-- generic failure mode, hence our way to build a FailMode from string
348
-- will instead raise an exception.
349
type OpResult = GenericResult FailMode
350

    
351
-- | 'FromString' instance for 'FailMode' designed to catch unintended
352
-- use as a general monad.
353
instance FromString FailMode where
354
  mkFromString v = error $ "Programming error: OpResult used as generic monad"
355
                           ++ v
356

    
357
-- | Conversion from 'OpResult' to 'Result'.
358
opToResult :: OpResult a -> Result a
359
opToResult (Bad f) = Bad $ show f
360
opToResult (Ok v) = Ok v
361

    
362
-- | A generic class for items that have updateable names and indices.
363
class Element a where
364
  -- | Returns the name of the element
365
  nameOf  :: a -> String
366
  -- | Returns all the known names of the element
367
  allNames :: a -> [String]
368
  -- | Returns the index of the element
369
  idxOf   :: a -> Int
370
  -- | Updates the alias of the element
371
  setAlias :: a -> String -> a
372
  -- | Compute the alias by stripping a given suffix (domain) from
373
  -- the name
374
  computeAlias :: String -> a -> a
375
  computeAlias dom e = setAlias e alias
376
    where alias = take (length name - length dom) name
377
          name = nameOf e
378
  -- | Updates the index of the element
379
  setIdx  :: a -> Int -> a
380

    
381
-- | The iallocator node-evacuate evac_mode type.
382
$(THH.declareSADT "EvacMode"
383
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
384
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
385
       , ("ChangeAll",       'C.iallocatorNevacAll)
386
       ])
387
$(THH.makeJSONInstance ''EvacMode)