Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 5f828ce4

History | View | Annotate | Download (8.9 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
    , AllocPolicy(..)
37
    , allocPolicyFromRaw
38
    , allocPolicyToRaw
39
    , RSpec(..)
40
    , DynUtil(..)
41
    , zeroUtil
42
    , baseUtil
43
    , addUtil
44
    , subUtil
45
    , defVcpuRatio
46
    , defReservedDiskRatio
47
    , unitMem
48
    , unitCpu
49
    , unitDsk
50
    , unknownField
51
    , Placement
52
    , IMove(..)
53
    , DiskTemplate(..)
54
    , diskTemplateToRaw
55
    , diskTemplateFromRaw
56
    , MoveJob
57
    , JobSet
58
    , Result(..)
59
    , isOk
60
    , isBad
61
    , eitherToResult
62
    , Element(..)
63
    , FailMode(..)
64
    , FailStats
65
    , OpResult(..)
66
    , opToResult
67
    , connTimeout
68
    , queryTimeout
69
    , EvacMode(..)
70
    ) where
71

    
72
import Control.Monad
73
import qualified Data.Map as M
74
import qualified Text.JSON as JSON
75

    
76
import qualified Ganeti.Constants as C
77
import qualified Ganeti.THH as THH
78

    
79
-- | The instance index type.
80
type Idx = Int
81

    
82
-- | The node index type.
83
type Ndx = Int
84

    
85
-- | The group index type.
86
type Gdx = Int
87

    
88
-- | The type used to hold name-to-idx mappings.
89
type NameAssoc = M.Map String Int
90

    
91
-- | A separate name for the cluster score type.
92
type Score = Double
93

    
94
-- | A separate name for a weight metric.
95
type Weight = Double
96

    
97
-- | The Group UUID type.
98
type GroupID = String
99

    
100
-- | The Group allocation policy type.
101
--
102
-- Note that the order of constructors is important as the automatic
103
-- Ord instance will order them in the order they are defined, so when
104
-- changing this data type be careful about the interaction with the
105
-- desired sorting order.
106
$(THH.declareSADT "AllocPolicy"
107
         [ ("AllocPreferred",   'C.allocPolicyPreferred)
108
         , ("AllocLastResort",  'C.allocPolicyLastResort)
109
         , ("AllocUnallocable", 'C.allocPolicyUnallocable)
110
         ])
111
$(THH.makeJSONInstance ''AllocPolicy)
112

    
113
-- | The resource spec type.
114
data RSpec = RSpec
115
    { rspecCpu  :: Int  -- ^ Requested VCPUs
116
    , rspecMem  :: Int  -- ^ Requested memory
117
    , rspecDsk  :: Int  -- ^ Requested disk
118
    } deriving (Show, Read, Eq)
119

    
120
-- | The dynamic resource specs of a machine (i.e. load or load
121
-- capacity, as opposed to size).
122
data DynUtil = DynUtil
123
    { cpuWeight :: Weight -- ^ Standardised CPU usage
124
    , memWeight :: Weight -- ^ Standardised memory load
125
    , dskWeight :: Weight -- ^ Standardised disk I\/O usage
126
    , netWeight :: Weight -- ^ Standardised network usage
127
    } deriving (Show, Read, Eq)
128

    
129
-- | Initial empty utilisation.
130
zeroUtil :: DynUtil
131
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
132
                   , dskWeight = 0, netWeight = 0 }
133

    
134
-- | Base utilisation (used when no actual utilisation data is
135
-- supplied).
136
baseUtil :: DynUtil
137
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
138
                   , dskWeight = 1, netWeight = 1 }
139

    
140
-- | Sum two utilisation records.
141
addUtil :: DynUtil -> DynUtil -> DynUtil
142
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
143
    DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
144

    
145
-- | Substracts one utilisation record from another.
146
subUtil :: DynUtil -> DynUtil -> DynUtil
147
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
148
    DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
149

    
150
-- | The description of an instance placement. It contains the
151
-- instance index, the new primary and secondary node, the move being
152
-- performed and the score of the cluster after the move.
153
type Placement = (Idx, Ndx, Ndx, IMove, Score)
154

    
155
-- | An instance move definition.
156
data IMove = Failover                -- ^ Failover the instance (f)
157
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
158
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
159
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
160
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
161
             deriving (Show, Read)
162

    
163
-- | Instance disk template type.
164
$(THH.declareSADT "DiskTemplate"
165
     [ ("DTDiskless",   'C.dtDiskless)
166
     , ("DTFile",       'C.dtFile)
167
     , ("DTSharedFile", 'C.dtSharedFile)
168
     , ("DTPlain",      'C.dtPlain)
169
     , ("DTBlock",      'C.dtBlock)
170
     , ("DTDrbd8",      'C.dtDrbd8)
171
     ])
172
$(THH.makeJSONInstance ''DiskTemplate)
173

    
174
-- | Formatted solution output for one move (involved nodes and
175
-- commands.
176
type MoveJob = ([Ndx], Idx, IMove, [String])
177

    
178
-- | Unknown field in table output.
179
unknownField :: String
180
unknownField = "<unknown field>"
181

    
182
-- | A list of command elements.
183
type JobSet = [MoveJob]
184

    
185
-- | Connection timeout (when using non-file methods).
186
connTimeout :: Int
187
connTimeout = 15
188

    
189
-- | The default timeout for queries (when using non-file methods).
190
queryTimeout :: Int
191
queryTimeout = 60
192

    
193
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
194
defVcpuRatio :: Double
195
defVcpuRatio = 64
196

    
197
-- | Default max disk usage ratio.
198
defReservedDiskRatio :: Double
199
defReservedDiskRatio = 0
200

    
201
-- | Base memory unit.
202
unitMem :: Int
203
unitMem = 64
204

    
205
-- | Base disk unit.
206
unitDsk :: Int
207
unitDsk = 256
208

    
209
-- | Base vcpus unit.
210
unitCpu :: Int
211
unitCpu = 1
212

    
213
-- | This is similar to the JSON library Result type - /very/ similar,
214
-- but we want to use it in multiple places, so we abstract it into a
215
-- mini-library here.
216
--
217
-- The failure value for this monad is simply a string.
218
data Result a
219
    = Bad String
220
    | Ok a
221
    deriving (Show, Read, Eq)
222

    
223
instance Monad Result where
224
    (>>=) (Bad x) _ = Bad x
225
    (>>=) (Ok x) fn = fn x
226
    return = Ok
227
    fail = Bad
228

    
229
instance MonadPlus Result where
230
    mzero = Bad "zero Result when used as MonadPlus"
231
    -- for mplus, when we 'add' two Bad values, we concatenate their
232
    -- error descriptions
233
    (Bad x) `mplus` (Bad y) = Bad (x ++ "; " ++ y)
234
    (Bad _) `mplus` x = x
235
    x@(Ok _) `mplus` _ = x
236

    
237
-- | Simple checker for whether a 'Result' is OK.
238
isOk :: Result a -> Bool
239
isOk (Ok _) = True
240
isOk _ = False
241

    
242
-- | Simple checker for whether a 'Result' is a failure.
243
isBad :: Result a  -> Bool
244
isBad = not . isOk
245

    
246
-- | Converter from Either String to 'Result'.
247
eitherToResult :: Either String a -> Result a
248
eitherToResult (Left s) = Bad s
249
eitherToResult (Right v) = Ok v
250

    
251
-- | Reason for an operation's falure.
252
data FailMode = FailMem  -- ^ Failed due to not enough RAM
253
              | FailDisk -- ^ Failed due to not enough disk
254
              | FailCPU  -- ^ Failed due to not enough CPU capacity
255
              | FailN1   -- ^ Failed due to not passing N1 checks
256
              | FailTags -- ^ Failed due to tag exclusion
257
                deriving (Eq, Enum, Bounded, Show, Read)
258

    
259
-- | List with failure statistics.
260
type FailStats = [(FailMode, Int)]
261

    
262
-- | Either-like data-type customized for our failure modes.
263
--
264
-- The failure values for this monad track the specific allocation
265
-- failures, so this is not a general error-monad (compare with the
266
-- 'Result' data type). One downside is that this type cannot encode a
267
-- generic failure mode, hence 'fail' for this monad is not defined
268
-- and will cause an exception.
269
data OpResult a = OpFail FailMode -- ^ Failed operation
270
                | OpGood a        -- ^ Success operation
271
                  deriving (Show, Read)
272

    
273
instance Monad OpResult where
274
    (OpGood x) >>= fn = fn x
275
    (OpFail y) >>= _ = OpFail y
276
    return = OpGood
277

    
278
-- | Conversion from 'OpResult' to 'Result'.
279
opToResult :: OpResult a -> Result a
280
opToResult (OpFail f) = Bad $ show f
281
opToResult (OpGood v) = Ok v
282

    
283
-- | A generic class for items that have updateable names and indices.
284
class Element a where
285
    -- | Returns the name of the element
286
    nameOf  :: a -> String
287
    -- | Returns all the known names of the element
288
    allNames :: a -> [String]
289
    -- | Returns the index of the element
290
    idxOf   :: a -> Int
291
    -- | Updates the alias of the element
292
    setAlias :: a -> String -> a
293
    -- | Compute the alias by stripping a given suffix (domain) from
294
    -- the name
295
    computeAlias :: String -> a -> a
296
    computeAlias dom e = setAlias e alias
297
        where alias = take (length name - length dom) name
298
              name = nameOf e
299
    -- | Updates the index of the element
300
    setIdx  :: a -> Int -> a
301

    
302
-- | The iallocator node-evacuate evac_mode type.
303
$(THH.declareSADT "EvacMode"
304
     [ ("ChangePrimary",   'C.iallocatorNevacPri)
305
     , ("ChangeSecondary", 'C.iallocatorNevacSec)
306
     , ("ChangeAll",       'C.iallocatorNevacAll)
307
     ])
308
$(THH.makeJSONInstance ''EvacMode)