Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 1fe412bb

History | View | Annotate | Download (8.4 kB)

1
{-| Some common types.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.HTools.Types
27
    ( Idx
28
    , Ndx
29
    , Gdx
30
    , NameAssoc
31
    , Score
32
    , Weight
33
    , GroupID
34
    , AllocPolicy(..)
35
    , apolFromString
36
    , apolToString
37
    , RSpec(..)
38
    , DynUtil(..)
39
    , zeroUtil
40
    , baseUtil
41
    , addUtil
42
    , subUtil
43
    , defVcpuRatio
44
    , defReservedDiskRatio
45
    , unitMem
46
    , unitCpu
47
    , unitDsk
48
    , unknownField
49
    , Placement
50
    , IMove(..)
51
    , MoveJob
52
    , JobSet
53
    , Result(..)
54
    , isOk
55
    , isBad
56
    , Element(..)
57
    , FailMode(..)
58
    , FailStats
59
    , OpResult(..)
60
    , connTimeout
61
    , queryTimeout
62
    , EvacMode(..)
63
    ) where
64

    
65
import qualified Data.Map as M
66
import qualified Text.JSON as JSON
67

    
68
import qualified Ganeti.Constants as C
69

    
70
-- | The instance index type.
71
type Idx = Int
72

    
73
-- | The node index type.
74
type Ndx = Int
75

    
76
-- | The group index type.
77
type Gdx = Int
78

    
79
-- | The type used to hold name-to-idx mappings.
80
type NameAssoc = M.Map String Int
81

    
82
-- | A separate name for the cluster score type.
83
type Score = Double
84

    
85
-- | A separate name for a weight metric.
86
type Weight = Double
87

    
88
-- | The Group UUID type.
89
type GroupID = String
90

    
91
-- | The Group allocation policy type.
92
--
93
-- Note that the order of constructors is important as the automatic
94
-- Ord instance will order them in the order they are defined, so when
95
-- changing this data type be careful about the interaction with the
96
-- desired sorting order.
97
data AllocPolicy
98
    = AllocPreferred   -- ^ This is the normal status, the group
99
                       -- should be used normally during allocations
100
    | AllocLastResort  -- ^ This group should be used only as
101
                       -- last-resort, after the preferred groups
102
    | AllocUnallocable -- ^ This group must not be used for new
103
                       -- allocations
104
      deriving (Show, Read, Eq, Ord)
105

    
106
-- | Convert a string to an alloc policy.
107
apolFromString :: (Monad m) => String -> m AllocPolicy
108
apolFromString s =
109
    case () of
110
      _ | s == C.allocPolicyPreferred -> return AllocPreferred
111
        | s == C.allocPolicyLastResort -> return AllocLastResort
112
        | s == C.allocPolicyUnallocable -> return AllocUnallocable
113
        | otherwise -> fail $ "Invalid alloc policy mode: " ++ s
114

    
115
-- | Convert an alloc policy to the Ganeti string equivalent.
116
apolToString :: AllocPolicy -> String
117
apolToString AllocPreferred   = C.allocPolicyPreferred
118
apolToString AllocLastResort  = C.allocPolicyLastResort
119
apolToString AllocUnallocable = C.allocPolicyUnallocable
120

    
121
instance JSON.JSON AllocPolicy where
122
    showJSON = JSON.showJSON . apolToString
123
    readJSON s = case JSON.readJSON s of
124
                   JSON.Ok s' -> apolFromString s'
125
                   JSON.Error e -> JSON.Error $
126
                                   "Can't parse alloc_policy: " ++ e
127

    
128
-- | The resource spec type.
129
data RSpec = RSpec
130
    { rspecCpu  :: Int  -- ^ Requested VCPUs
131
    , rspecMem  :: Int  -- ^ Requested memory
132
    , rspecDsk  :: Int  -- ^ Requested disk
133
    } deriving (Show, Read, Eq)
134

    
135
-- | The dynamic resource specs of a machine (i.e. load or load
136
-- capacity, as opposed to size).
137
data DynUtil = DynUtil
138
    { cpuWeight :: Weight -- ^ Standardised CPU usage
139
    , memWeight :: Weight -- ^ Standardised memory load
140
    , dskWeight :: Weight -- ^ Standardised disk I\/O usage
141
    , netWeight :: Weight -- ^ Standardised network usage
142
    } deriving (Show, Read, Eq)
143

    
144
-- | Initial empty utilisation.
145
zeroUtil :: DynUtil
146
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
147
                   , dskWeight = 0, netWeight = 0 }
148

    
149
-- | Base utilisation (used when no actual utilisation data is
150
-- supplied).
151
baseUtil :: DynUtil
152
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
153
                   , dskWeight = 1, netWeight = 1 }
154

    
155
-- | Sum two utilisation records.
156
addUtil :: DynUtil -> DynUtil -> DynUtil
157
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
158
    DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
159

    
160
-- | Substracts one utilisation record from another.
161
subUtil :: DynUtil -> DynUtil -> DynUtil
162
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
163
    DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
164

    
165
-- | The description of an instance placement. It contains the
166
-- instance index, the new primary and secondary node, the move being
167
-- performed and the score of the cluster after the move.
168
type Placement = (Idx, Ndx, Ndx, IMove, Score)
169

    
170
-- | An instance move definition.
171
data IMove = Failover                -- ^ Failover the instance (f)
172
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
173
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
174
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
175
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
176
             deriving (Show, Read)
177

    
178
-- | Formatted solution output for one move (involved nodes and
179
-- commands.
180
type MoveJob = ([Ndx], Idx, IMove, [String])
181

    
182
-- | Unknown field in table output.
183
unknownField :: String
184
unknownField = "<unknown field>"
185

    
186
-- | A list of command elements.
187
type JobSet = [MoveJob]
188

    
189
-- | Connection timeout (when using non-file methods).
190
connTimeout :: Int
191
connTimeout = 15
192

    
193
-- | The default timeout for queries (when using non-file methods).
194
queryTimeout :: Int
195
queryTimeout = 60
196

    
197
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
198
defVcpuRatio :: Double
199
defVcpuRatio = 64
200

    
201
-- | Default max disk usage ratio.
202
defReservedDiskRatio :: Double
203
defReservedDiskRatio = 0
204

    
205
-- | Base memory unit.
206
unitMem :: Int
207
unitMem = 64
208

    
209
-- | Base disk unit.
210
unitDsk :: Int
211
unitDsk = 256
212

    
213
-- | Base vcpus unit.
214
unitCpu :: Int
215
unitCpu = 1
216

    
217
{-|
218

    
219
This is similar to the JSON library Result type - /very/ similar, but
220
we want to use it in multiple places, so we abstract it into a
221
mini-library here
222

    
223
-}
224
data Result a
225
    = Bad String
226
    | Ok a
227
    deriving (Show, Read)
228

    
229
instance Monad Result where
230
    (>>=) (Bad x) _ = Bad x
231
    (>>=) (Ok x) fn = fn x
232
    return = Ok
233
    fail = Bad
234

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

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

    
244
-- | Reason for an operation's falure.
245
data FailMode = FailMem  -- ^ Failed due to not enough RAM
246
              | FailDisk -- ^ Failed due to not enough disk
247
              | FailCPU  -- ^ Failed due to not enough CPU capacity
248
              | FailN1   -- ^ Failed due to not passing N1 checks
249
              | FailTags -- ^ Failed due to tag exclusion
250
                deriving (Eq, Enum, Bounded, Show, Read)
251

    
252
-- | List with failure statistics.
253
type FailStats = [(FailMode, Int)]
254

    
255
-- | Either-like data-type customized for our failure modes.
256
data OpResult a = OpFail FailMode -- ^ Failed operation
257
                | OpGood a        -- ^ Success operation
258
                  deriving (Show, Read)
259

    
260
instance Monad OpResult where
261
    (OpGood x) >>= fn = fn x
262
    (OpFail y) >>= _ = OpFail y
263
    return = OpGood
264

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

    
284
-- | The iallocator node-evacuate evac_mode type.
285
data EvacMode = ChangePrimary
286
              | ChangeSecondary
287
              | ChangeAll
288
                deriving (Show, Read)