Statistics
| Branch: | Tag: | Revision:

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
157

    
158
-- | Instance specification type.
159
$(THH.buildObject "ISpec" "iSpec"
160
  [ THH.renameField "MemorySize" $ THH.simpleField "memory-size" [t| Int |]
161
  , THH.renameField "CpuCount"   $ THH.simpleField "cpu-count"   [t| Int |]
162
  , THH.renameField "DiskSize"   $ THH.simpleField "disk-size"   [t| Int |]
163
  , THH.renameField "DiskCount"  $ THH.simpleField "disk-count"  [t| Int |]
164
  , THH.renameField "NicCount"   $ THH.simpleField "nic-count"   [t| Int |]
165
  ])
166

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

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

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

    
194
-- | Instance policy type.
195
$(THH.buildObject "IPolicy" "iPolicy"
196
  [ THH.renameField "StdSpec" $ THH.simpleField "std" [t| ISpec |]
197
  , THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
198
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
199
  , THH.renameField "DiskTemplates" $
200
      THH.simpleField "disk_templates" [t| [DiskTemplate] |]
201
  , THH.renameField "VcpuRatio" $
202
      THH.simpleField "vcpu_ratio" [t| Double |]
203
  ])
204

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

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

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

    
233
-- | Initial empty utilisation.
234
zeroUtil :: DynUtil
235
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
236
                   , dskWeight = 0, netWeight = 0 }
237

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

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

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

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

    
259
-- | An instance move definition.
260
data IMove = Failover                -- ^ Failover the instance (f)
261
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
262
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
263
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
264
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
265
             deriving (Show, Read)
266

    
267
-- | Formatted solution output for one move (involved nodes and
268
-- commands.
269
type MoveJob = ([Ndx], Idx, IMove, [String])
270

    
271
-- | Unknown field in table output.
272
unknownField :: String
273
unknownField = "<unknown field>"
274

    
275
-- | A list of command elements.
276
type JobSet = [MoveJob]
277

    
278
-- | Connection timeout (when using non-file methods).
279
connTimeout :: Int
280
connTimeout = 15
281

    
282
-- | The default timeout for queries (when using non-file methods).
283
queryTimeout :: Int
284
queryTimeout = 60
285

    
286
-- | Default max disk usage ratio.
287
defReservedDiskRatio :: Double
288
defReservedDiskRatio = 0
289

    
290
-- | Base memory unit.
291
unitMem :: Int
292
unitMem = 64
293

    
294
-- | Base disk unit.
295
unitDsk :: Int
296
unitDsk = 256
297

    
298
-- | Base vcpus unit.
299
unitCpu :: Int
300
unitCpu = 1
301

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

    
310
-- | List with failure statistics.
311
type FailStats = [(FailMode, Int)]
312

    
313
-- | Either-like data-type customized for our failure modes.
314
--
315
-- The failure values for this monad track the specific allocation
316
-- failures, so this is not a general error-monad (compare with the
317
-- 'Result' data type). One downside is that this type cannot encode a
318
-- generic failure mode, hence 'fail' for this monad is not defined
319
-- and will cause an exception.
320
data OpResult a = OpFail FailMode -- ^ Failed operation
321
                | OpGood a        -- ^ Success operation
322
                  deriving (Show, Read)
323

    
324
instance Monad OpResult where
325
  (OpGood x) >>= fn = fn x
326
  (OpFail y) >>= _ = OpFail y
327
  return = OpGood
328

    
329
-- | Conversion from 'OpResult' to 'Result'.
330
opToResult :: OpResult a -> Result a
331
opToResult (OpFail f) = Bad $ show f
332
opToResult (OpGood v) = Ok v
333

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

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