Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Types.hs @ 6bc39970

History | View | Annotate | Download (7.9 kB)

1
{-| Some common types.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010 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
-- | The instance index type.
68
type Idx = Int
69

    
70
-- | The node index type.
71
type Ndx = Int
72

    
73
-- | The group index type.
74
type Gdx = Int
75

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

    
79
-- | A separate name for the cluster score type.
80
type Score = Double
81

    
82
-- | A separate name for a weight metric.
83
type Weight = Double
84

    
85
-- | The Group UUID type.
86
type GroupID = String
87

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

    
103
-- | Convert a string to an alloc policy
104
apolFromString :: (Monad m) => String -> m AllocPolicy
105
apolFromString s =
106
    case s of
107
      "preferred"   -> return AllocPreferred
108
      "last_resort" -> return AllocLastResort
109
      "unallocable" -> return AllocUnallocable
110
      o -> fail $ "Invalid alloc policy mode: " ++ o
111

    
112
-- | Convert an alloc policy to the Ganeti string equivalent
113
apolToString :: AllocPolicy -> String
114
apolToString AllocPreferred   = "preferred"
115
apolToString AllocLastResort  = "last_resort"
116
apolToString AllocUnallocable = "unallocable"
117

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

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

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

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

    
146
baseUtil :: DynUtil
147
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
148
                   , dskWeight = 1, netWeight = 1 }
149

    
150
addUtil :: DynUtil -> DynUtil -> DynUtil
151
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
152
    DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
153

    
154
subUtil :: DynUtil -> DynUtil -> DynUtil
155
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
156
    DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
157

    
158
-- | The description of an instance placement. It contains the
159
-- instance index, the new primary and secondary node, the move being
160
-- performed and the score of the cluster after the move.
161
type Placement = (Idx, Ndx, Ndx, IMove, Score)
162

    
163
-- | An instance move definition
164
data IMove = Failover                -- ^ Failover the instance (f)
165
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
166
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
167
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
168
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
169
             deriving (Show, Read)
170

    
171
-- | Formatted solution output for one move (involved nodes and
172
-- commands
173
type MoveJob = ([Ndx], Idx, IMove, [String])
174

    
175
-- | Unknown field in table output
176
unknownField :: String
177
unknownField = "<unknown field>"
178

    
179
-- | A list of command elements
180
type JobSet = [MoveJob]
181

    
182
-- | Connection timeout (when using non-file methods).
183
connTimeout :: Int
184
connTimeout = 15
185

    
186
-- | The default timeout for queries (when using non-file methods).
187
queryTimeout :: Int
188
queryTimeout = 60
189

    
190
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
191
defVcpuRatio :: Double
192
defVcpuRatio = 64
193

    
194
-- | Default max disk usage ratio.
195
defReservedDiskRatio :: Double
196
defReservedDiskRatio = 0
197

    
198
-- | Base memory unit.
199
unitMem :: Int
200
unitMem = 64
201

    
202
-- | Base disk unit.
203
unitDsk :: Int
204
unitDsk = 256
205

    
206
-- | Base vcpus unit.
207
unitCpu :: Int
208
unitCpu = 1
209

    
210
{-|
211

    
212
This is similar to the JSON library Result type - *very* similar, but
213
we want to use it in multiple places, so we abstract it into a
214
mini-library here
215

    
216
-}
217
data Result a
218
    = Bad String
219
    | Ok a
220
    deriving (Show, Read)
221

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

    
228
-- | Simple checker for whether Result is OK
229
isOk :: Result a -> Bool
230
isOk (Ok _) = True
231
isOk _ = False
232

    
233
-- | Simple checker for whether Result is a failure
234
isBad :: Result a  -> Bool
235
isBad = not . isOk
236

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

    
245
-- | List with failure statistics
246
type FailStats = [(FailMode, Int)]
247

    
248
-- | Either-like data-type customized for our failure modes
249
data OpResult a = OpFail FailMode -- ^ Failed operation
250
                | OpGood a        -- ^ Success operation
251
                  deriving (Show, Read)
252

    
253
instance Monad OpResult where
254
    (OpGood x) >>= fn = fn x
255
    (OpFail y) >>= _ = OpFail y
256
    return = OpGood
257

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