Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (8.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common types.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011 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
  , defVcpuRatio
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
  ) where
76

    
77
import qualified Data.Map as M
78
import qualified Text.JSON as JSON
79

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

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

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

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

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

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

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

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

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

    
109
-- | The Group allocation policy type.
110
--
111
-- Note that the order of constructors is important as the automatic
112
-- Ord instance will order them in the order they are defined, so when
113
-- changing this data type be careful about the interaction with the
114
-- desired sorting order.
115
$(THH.declareSADT "AllocPolicy"
116
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
117
       , ("AllocLastResort",  'C.allocPolicyLastResort)
118
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
119
       ])
120
$(THH.makeJSONInstance ''AllocPolicy)
121

    
122
-- | The Instance real state type.
123
$(THH.declareSADT "InstanceStatus"
124
       [ ("AdminDown", 'C.inststAdmindown)
125
       , ("AdminOffline", 'C.inststAdminoffline)
126
       , ("ErrorDown", 'C.inststErrordown)
127
       , ("ErrorUp", 'C.inststErrorup)
128
       , ("NodeDown", 'C.inststNodedown)
129
       , ("NodeOffline", 'C.inststNodeoffline)
130
       , ("Running", 'C.inststRunning)
131
       , ("WrongNode", 'C.inststWrongnode)
132
       ])
133
$(THH.makeJSONInstance ''InstanceStatus)
134

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

    
142
-- | The dynamic resource specs of a machine (i.e. load or load
143
-- capacity, as opposed to size).
144
data DynUtil = DynUtil
145
  { cpuWeight :: Weight -- ^ Standardised CPU usage
146
  , memWeight :: Weight -- ^ Standardised memory load
147
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
148
  , netWeight :: Weight -- ^ Standardised network usage
149
  } deriving (Show, Read, Eq)
150

    
151
-- | Initial empty utilisation.
152
zeroUtil :: DynUtil
153
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
154
                   , dskWeight = 0, netWeight = 0 }
155

    
156
-- | Base utilisation (used when no actual utilisation data is
157
-- supplied).
158
baseUtil :: DynUtil
159
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
160
                   , dskWeight = 1, netWeight = 1 }
161

    
162
-- | Sum two utilisation records.
163
addUtil :: DynUtil -> DynUtil -> DynUtil
164
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
165
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
166

    
167
-- | Substracts one utilisation record from another.
168
subUtil :: DynUtil -> DynUtil -> DynUtil
169
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
170
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
171

    
172
-- | The description of an instance placement. It contains the
173
-- instance index, the new primary and secondary node, the move being
174
-- performed and the score of the cluster after the move.
175
type Placement = (Idx, Ndx, Ndx, IMove, Score)
176

    
177
-- | An instance move definition.
178
data IMove = Failover                -- ^ Failover the instance (f)
179
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
180
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
181
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
182
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
183
             deriving (Show, Read)
184

    
185
-- | Instance disk template type.
186
$(THH.declareSADT "DiskTemplate"
187
       [ ("DTDiskless",   'C.dtDiskless)
188
       , ("DTFile",       'C.dtFile)
189
       , ("DTSharedFile", 'C.dtSharedFile)
190
       , ("DTPlain",      'C.dtPlain)
191
       , ("DTBlock",      'C.dtBlock)
192
       , ("DTDrbd8",      'C.dtDrbd8)
193
       ])
194
$(THH.makeJSONInstance ''DiskTemplate)
195

    
196
-- | Formatted solution output for one move (involved nodes and
197
-- commands.
198
type MoveJob = ([Ndx], Idx, IMove, [String])
199

    
200
-- | Unknown field in table output.
201
unknownField :: String
202
unknownField = "<unknown field>"
203

    
204
-- | A list of command elements.
205
type JobSet = [MoveJob]
206

    
207
-- | Connection timeout (when using non-file methods).
208
connTimeout :: Int
209
connTimeout = 15
210

    
211
-- | The default timeout for queries (when using non-file methods).
212
queryTimeout :: Int
213
queryTimeout = 60
214

    
215
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
216
defVcpuRatio :: Double
217
defVcpuRatio = 64
218

    
219
-- | Default max disk usage ratio.
220
defReservedDiskRatio :: Double
221
defReservedDiskRatio = 0
222

    
223
-- | Base memory unit.
224
unitMem :: Int
225
unitMem = 64
226

    
227
-- | Base disk unit.
228
unitDsk :: Int
229
unitDsk = 256
230

    
231
-- | Base vcpus unit.
232
unitCpu :: Int
233
unitCpu = 1
234

    
235
-- | Reason for an operation's falure.
236
data FailMode = FailMem  -- ^ Failed due to not enough RAM
237
              | FailDisk -- ^ Failed due to not enough disk
238
              | FailCPU  -- ^ Failed due to not enough CPU capacity
239
              | FailN1   -- ^ Failed due to not passing N1 checks
240
              | FailTags -- ^ Failed due to tag exclusion
241
                deriving (Eq, Enum, Bounded, Show, Read)
242

    
243
-- | List with failure statistics.
244
type FailStats = [(FailMode, Int)]
245

    
246
-- | Either-like data-type customized for our failure modes.
247
--
248
-- The failure values for this monad track the specific allocation
249
-- failures, so this is not a general error-monad (compare with the
250
-- 'Result' data type). One downside is that this type cannot encode a
251
-- generic failure mode, hence 'fail' for this monad is not defined
252
-- and will cause an exception.
253
data OpResult a = OpFail FailMode -- ^ Failed operation
254
                | OpGood a        -- ^ Success operation
255
                  deriving (Show, Read)
256

    
257
instance Monad OpResult where
258
  (OpGood x) >>= fn = fn x
259
  (OpFail y) >>= _ = OpFail y
260
  return = OpGood
261

    
262
-- | Conversion from 'OpResult' to 'Result'.
263
opToResult :: OpResult a -> Result a
264
opToResult (OpFail f) = Bad $ show f
265
opToResult (OpGood v) = Ok v
266

    
267
-- | A generic class for items that have updateable names and indices.
268
class Element a where
269
  -- | Returns the name of the element
270
  nameOf  :: a -> String
271
  -- | Returns all the known names of the element
272
  allNames :: a -> [String]
273
  -- | Returns the index of the element
274
  idxOf   :: a -> Int
275
  -- | Updates the alias of the element
276
  setAlias :: a -> String -> a
277
  -- | Compute the alias by stripping a given suffix (domain) from
278
  -- the name
279
  computeAlias :: String -> a -> a
280
  computeAlias dom e = setAlias e alias
281
    where alias = take (length name - length dom) name
282
          name = nameOf e
283
  -- | Updates the index of the element
284
  setIdx  :: a -> Int -> a
285

    
286
-- | The iallocator node-evacuate evac_mode type.
287
$(THH.declareSADT "EvacMode"
288
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
289
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
290
       , ("ChangeAll",       'C.iallocatorNevacAll)
291
       ])
292
$(THH.makeJSONInstance ''EvacMode)