Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 525bfb36

History | View | Annotate | Download (8.2 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
    ) where
63

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

    
67
import qualified Ganeti.Constants as C
68

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
216
{-|
217

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

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

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

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

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

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

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

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

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

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