Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 76a20994

History | View | Annotate | Download (11.9 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
  , DynUtil(..)
46
  , zeroUtil
47
  , baseUtil
48
  , addUtil
49
  , subUtil
50
  , defReservedDiskRatio
51
  , unitMem
52
  , unitCpu
53
  , unitDsk
54
  , unknownField
55
  , Placement
56
  , IMove(..)
57
  , DiskTemplate(..)
58
  , diskTemplateToRaw
59
  , diskTemplateFromRaw
60
  , MoveJob
61
  , JobSet
62
  , Result(..)
63
  , isOk
64
  , isBad
65
  , eitherToResult
66
  , annotateResult
67
  , Element(..)
68
  , FailMode(..)
69
  , FailStats
70
  , OpResult(..)
71
  , opToResult
72
  , connTimeout
73
  , queryTimeout
74
  , EvacMode(..)
75
  , ISpec(..)
76
  , IPolicy(..)
77
  , defIPolicy
78
  , rspecFromISpec
79
  ) where
80

    
81
import qualified Data.Map as M
82
import Text.JSON (makeObj, readJSON, showJSON)
83

    
84
import qualified Ganeti.Constants as C
85
import qualified Ganeti.THH as THH
86
import Ganeti.BasicTypes
87
import Ganeti.HTools.JSON
88

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

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

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

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

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

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

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

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

    
114
-- | Instance disk template type.
115
$(THH.declareSADT "DiskTemplate"
116
       [ ("DTDiskless",   'C.dtDiskless)
117
       , ("DTFile",       'C.dtFile)
118
       , ("DTSharedFile", 'C.dtSharedFile)
119
       , ("DTPlain",      'C.dtPlain)
120
       , ("DTBlock",      'C.dtBlock)
121
       , ("DTDrbd8",      'C.dtDrbd8)
122
       ])
123
$(THH.makeJSONInstance ''DiskTemplate)
124

    
125
-- | The Group allocation policy type.
126
--
127
-- Note that the order of constructors is important as the automatic
128
-- Ord instance will order them in the order they are defined, so when
129
-- changing this data type be careful about the interaction with the
130
-- desired sorting order.
131
$(THH.declareSADT "AllocPolicy"
132
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
133
       , ("AllocLastResort",  'C.allocPolicyLastResort)
134
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
135
       ])
136
$(THH.makeJSONInstance ''AllocPolicy)
137

    
138
-- | The Instance real state type.
139
$(THH.declareSADT "InstanceStatus"
140
       [ ("AdminDown", 'C.inststAdmindown)
141
       , ("AdminOffline", 'C.inststAdminoffline)
142
       , ("ErrorDown", 'C.inststErrordown)
143
       , ("ErrorUp", 'C.inststErrorup)
144
       , ("NodeDown", 'C.inststNodedown)
145
       , ("NodeOffline", 'C.inststNodeoffline)
146
       , ("Running", 'C.inststRunning)
147
       , ("WrongNode", 'C.inststWrongnode)
148
       ])
149
$(THH.makeJSONInstance ''InstanceStatus)
150

    
151
-- | The resource spec type.
152
data RSpec = RSpec
153
  { rspecCpu  :: Int  -- ^ Requested VCPUs
154
  , rspecMem  :: Int  -- ^ Requested memory
155
  , rspecDsk  :: Int  -- ^ Requested disk
156
  } deriving (Show, Read, Eq)
157

    
158
-- | Allocation stats type. This is used instead of 'RSpec' (which was
159
-- used at first), because we need to track more stats. The actual
160
-- data can refer either to allocated, or available, etc. values
161
-- depending on the context. See also
162
-- 'Cluster.computeAllocationDelta'.
163
data AllocInfo = AllocInfo
164
  { allocInfoVCpus :: Int    -- ^ VCPUs
165
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
166
  , allocInfoMem   :: Int    -- ^ Memory
167
  , allocInfoDisk  :: Int    -- ^ Disk
168
  } deriving (Show, Read, Eq)
169

    
170
-- | Instance specification type.
171
$(THH.buildObject "ISpec" "iSpec"
172
  [ THH.renameField "MemorySize" $ THH.simpleField "memory-size" [t| Int |]
173
  , THH.renameField "CpuCount"   $ THH.simpleField "cpu-count"   [t| Int |]
174
  , THH.renameField "DiskSize"   $ THH.simpleField "disk-size"   [t| Int |]
175
  , THH.renameField "DiskCount"  $ THH.simpleField "disk-count"  [t| Int |]
176
  , THH.renameField "NicCount"   $ THH.simpleField "nic-count"   [t| Int |]
177
  ])
178

    
179
-- | The default minimum ispec.
180
defMinISpec :: ISpec
181
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinMemorySize
182
                    , iSpecCpuCount   = C.ipolicyDefaultsMinCpuCount
183
                    , iSpecDiskSize   = C.ipolicyDefaultsMinDiskSize
184
                    , iSpecDiskCount  = C.ipolicyDefaultsMinDiskCount
185
                    , iSpecNicCount   = C.ipolicyDefaultsMinNicCount
186
                    }
187

    
188
-- | The default standard ispec.
189
defStdISpec :: ISpec
190
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
191
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
192
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
193
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
194
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
195
                    }
196

    
197
-- | The default max ispec.
198
defMaxISpec :: ISpec
199
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMaxMemorySize
200
                    , iSpecCpuCount   = C.ipolicyDefaultsMaxCpuCount
201
                    , iSpecDiskSize   = C.ipolicyDefaultsMaxDiskSize
202
                    , iSpecDiskCount  = C.ipolicyDefaultsMaxDiskCount
203
                    , iSpecNicCount   = C.ipolicyDefaultsMaxNicCount
204
                    }
205

    
206
-- | Instance policy type.
207
$(THH.buildObject "IPolicy" "iPolicy"
208
  [ THH.renameField "StdSpec" $ THH.simpleField "std" [t| ISpec |]
209
  , THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
210
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
211
  , THH.renameField "DiskTemplates" $
212
      THH.simpleField "disk_templates" [t| [DiskTemplate] |]
213
  , THH.renameField "VcpuRatio" $
214
      THH.simpleField "vcpu_ratio" [t| Double |]
215
  ])
216

    
217
-- | Converts an ISpec type to a RSpec one.
218
rspecFromISpec :: ISpec -> RSpec
219
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
220
                             , rspecMem = iSpecMemorySize ispec
221
                             , rspecDsk = iSpecDiskSize ispec
222
                             }
223

    
224
-- | The default instance policy.
225
defIPolicy :: IPolicy
226
defIPolicy = IPolicy { iPolicyStdSpec = defStdISpec
227
                     , iPolicyMinSpec = defMinISpec
228
                     , iPolicyMaxSpec = defMaxISpec
229
                     -- hardcoding here since Constants.hs exports the
230
                     -- string values, not the actual type; and in
231
                     -- htools, we are mostly looking at DRBD
232
                     , iPolicyDiskTemplates = [DTDrbd8, DTPlain]
233
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
234
                     }
235

    
236
-- | The dynamic resource specs of a machine (i.e. load or load
237
-- capacity, as opposed to size).
238
data DynUtil = DynUtil
239
  { cpuWeight :: Weight -- ^ Standardised CPU usage
240
  , memWeight :: Weight -- ^ Standardised memory load
241
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
242
  , netWeight :: Weight -- ^ Standardised network usage
243
  } deriving (Show, Read, Eq)
244

    
245
-- | Initial empty utilisation.
246
zeroUtil :: DynUtil
247
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
248
                   , dskWeight = 0, netWeight = 0 }
249

    
250
-- | Base utilisation (used when no actual utilisation data is
251
-- supplied).
252
baseUtil :: DynUtil
253
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
254
                   , dskWeight = 1, netWeight = 1 }
255

    
256
-- | Sum two utilisation records.
257
addUtil :: DynUtil -> DynUtil -> DynUtil
258
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
259
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
260

    
261
-- | Substracts one utilisation record from another.
262
subUtil :: DynUtil -> DynUtil -> DynUtil
263
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
264
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
265

    
266
-- | The description of an instance placement. It contains the
267
-- instance index, the new primary and secondary node, the move being
268
-- performed and the score of the cluster after the move.
269
type Placement = (Idx, Ndx, Ndx, IMove, Score)
270

    
271
-- | An instance move definition.
272
data IMove = Failover                -- ^ Failover the instance (f)
273
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
274
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
275
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
276
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
277
             deriving (Show, Read)
278

    
279
-- | Formatted solution output for one move (involved nodes and
280
-- commands.
281
type MoveJob = ([Ndx], Idx, IMove, [String])
282

    
283
-- | Unknown field in table output.
284
unknownField :: String
285
unknownField = "<unknown field>"
286

    
287
-- | A list of command elements.
288
type JobSet = [MoveJob]
289

    
290
-- | Connection timeout (when using non-file methods).
291
connTimeout :: Int
292
connTimeout = 15
293

    
294
-- | The default timeout for queries (when using non-file methods).
295
queryTimeout :: Int
296
queryTimeout = 60
297

    
298
-- | Default max disk usage ratio.
299
defReservedDiskRatio :: Double
300
defReservedDiskRatio = 0
301

    
302
-- | Base memory unit.
303
unitMem :: Int
304
unitMem = 64
305

    
306
-- | Base disk unit.
307
unitDsk :: Int
308
unitDsk = 256
309

    
310
-- | Base vcpus unit.
311
unitCpu :: Int
312
unitCpu = 1
313

    
314
-- | Reason for an operation's falure.
315
data FailMode = FailMem  -- ^ Failed due to not enough RAM
316
              | FailDisk -- ^ Failed due to not enough disk
317
              | FailCPU  -- ^ Failed due to not enough CPU capacity
318
              | FailN1   -- ^ Failed due to not passing N1 checks
319
              | FailTags -- ^ Failed due to tag exclusion
320
                deriving (Eq, Enum, Bounded, Show, Read)
321

    
322
-- | List with failure statistics.
323
type FailStats = [(FailMode, Int)]
324

    
325
-- | Either-like data-type customized for our failure modes.
326
--
327
-- The failure values for this monad track the specific allocation
328
-- failures, so this is not a general error-monad (compare with the
329
-- 'Result' data type). One downside is that this type cannot encode a
330
-- generic failure mode, hence 'fail' for this monad is not defined
331
-- and will cause an exception.
332
data OpResult a = OpFail FailMode -- ^ Failed operation
333
                | OpGood a        -- ^ Success operation
334
                  deriving (Show, Read)
335

    
336
instance Monad OpResult where
337
  (OpGood x) >>= fn = fn x
338
  (OpFail y) >>= _ = OpFail y
339
  return = OpGood
340

    
341
-- | Conversion from 'OpResult' to 'Result'.
342
opToResult :: OpResult a -> Result a
343
opToResult (OpFail f) = Bad $ show f
344
opToResult (OpGood v) = Ok v
345

    
346
-- | A generic class for items that have updateable names and indices.
347
class Element a where
348
  -- | Returns the name of the element
349
  nameOf  :: a -> String
350
  -- | Returns all the known names of the element
351
  allNames :: a -> [String]
352
  -- | Returns the index of the element
353
  idxOf   :: a -> Int
354
  -- | Updates the alias of the element
355
  setAlias :: a -> String -> a
356
  -- | Compute the alias by stripping a given suffix (domain) from
357
  -- the name
358
  computeAlias :: String -> a -> a
359
  computeAlias dom e = setAlias e alias
360
    where alias = take (length name - length dom) name
361
          name = nameOf e
362
  -- | Updates the index of the element
363
  setIdx  :: a -> Int -> a
364

    
365
-- | The iallocator node-evacuate evac_mode type.
366
$(THH.declareSADT "EvacMode"
367
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
368
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
369
       , ("ChangeAll",       'C.iallocatorNevacAll)
370
       ])
371
$(THH.makeJSONInstance ''EvacMode)