htools: simplify select tests
[ganeti-local] / htools / Ganeti / HTools / Types.hs
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     , DiskTemplate(..)
52     , dtToString
53     , dtFromString
54     , MoveJob
55     , JobSet
56     , Result(..)
57     , isOk
58     , isBad
59     , Element(..)
60     , FailMode(..)
61     , FailStats
62     , OpResult(..)
63     , connTimeout
64     , queryTimeout
65     , EvacMode(..)
66     ) where
67
68 import qualified Data.Map as M
69 import qualified Text.JSON as JSON
70
71 import qualified Ganeti.Constants as C
72
73 -- | The instance index type.
74 type Idx = Int
75
76 -- | The node index type.
77 type Ndx = Int
78
79 -- | The group index type.
80 type Gdx = Int
81
82 -- | The type used to hold name-to-idx mappings.
83 type NameAssoc = M.Map String Int
84
85 -- | A separate name for the cluster score type.
86 type Score = Double
87
88 -- | A separate name for a weight metric.
89 type Weight = Double
90
91 -- | The Group UUID type.
92 type GroupID = String
93
94 -- | The Group allocation policy type.
95 --
96 -- Note that the order of constructors is important as the automatic
97 -- Ord instance will order them in the order they are defined, so when
98 -- changing this data type be careful about the interaction with the
99 -- desired sorting order.
100 data AllocPolicy
101     = AllocPreferred   -- ^ This is the normal status, the group
102                        -- should be used normally during allocations
103     | AllocLastResort  -- ^ This group should be used only as
104                        -- last-resort, after the preferred groups
105     | AllocUnallocable -- ^ This group must not be used for new
106                        -- allocations
107       deriving (Show, Read, Eq, Ord, Enum, Bounded)
108
109 -- | Convert a string to an alloc policy.
110 apolFromString :: (Monad m) => String -> m AllocPolicy
111 apolFromString s =
112     case () of
113       _ | s == C.allocPolicyPreferred -> return AllocPreferred
114         | s == C.allocPolicyLastResort -> return AllocLastResort
115         | s == C.allocPolicyUnallocable -> return AllocUnallocable
116         | otherwise -> fail $ "Invalid alloc policy mode: " ++ s
117
118 -- | Convert an alloc policy to the Ganeti string equivalent.
119 apolToString :: AllocPolicy -> String
120 apolToString AllocPreferred   = C.allocPolicyPreferred
121 apolToString AllocLastResort  = C.allocPolicyLastResort
122 apolToString AllocUnallocable = C.allocPolicyUnallocable
123
124 instance JSON.JSON AllocPolicy where
125     showJSON = JSON.showJSON . apolToString
126     readJSON s = case JSON.readJSON s of
127                    JSON.Ok s' -> apolFromString s'
128                    JSON.Error e -> JSON.Error $
129                                    "Can't parse alloc_policy: " ++ e
130
131 -- | The resource spec type.
132 data RSpec = RSpec
133     { rspecCpu  :: Int  -- ^ Requested VCPUs
134     , rspecMem  :: Int  -- ^ Requested memory
135     , rspecDsk  :: Int  -- ^ Requested disk
136     } deriving (Show, Read, Eq)
137
138 -- | The dynamic resource specs of a machine (i.e. load or load
139 -- capacity, as opposed to size).
140 data DynUtil = DynUtil
141     { cpuWeight :: Weight -- ^ Standardised CPU usage
142     , memWeight :: Weight -- ^ Standardised memory load
143     , dskWeight :: Weight -- ^ Standardised disk I\/O usage
144     , netWeight :: Weight -- ^ Standardised network usage
145     } deriving (Show, Read, Eq)
146
147 -- | Initial empty utilisation.
148 zeroUtil :: DynUtil
149 zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
150                    , dskWeight = 0, netWeight = 0 }
151
152 -- | Base utilisation (used when no actual utilisation data is
153 -- supplied).
154 baseUtil :: DynUtil
155 baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
156                    , dskWeight = 1, netWeight = 1 }
157
158 -- | Sum two utilisation records.
159 addUtil :: DynUtil -> DynUtil -> DynUtil
160 addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
161     DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
162
163 -- | Substracts one utilisation record from another.
164 subUtil :: DynUtil -> DynUtil -> DynUtil
165 subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
166     DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
167
168 -- | The description of an instance placement. It contains the
169 -- instance index, the new primary and secondary node, the move being
170 -- performed and the score of the cluster after the move.
171 type Placement = (Idx, Ndx, Ndx, IMove, Score)
172
173 -- | An instance move definition.
174 data IMove = Failover                -- ^ Failover the instance (f)
175            | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
176            | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
177            | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
178            | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
179              deriving (Show, Read)
180
181 -- | Instance disk template type
182 data DiskTemplate = DTDiskless
183                   | DTFile
184                   | DTSharedFile
185                   | DTPlain
186                   | DTBlock
187                   | DTDrbd8
188                     deriving (Show, Read, Eq, Enum, Bounded)
189
190 -- | Converts a DiskTemplate to String
191 dtToString :: DiskTemplate -> String
192 dtToString DTDiskless   = C.dtDiskless
193 dtToString DTFile       = C.dtFile
194 dtToString DTSharedFile = C.dtSharedFile
195 dtToString DTPlain      = C.dtPlain
196 dtToString DTBlock      = C.dtBlock
197 dtToString DTDrbd8      = C.dtDrbd8
198
199 -- | Converts a DiskTemplate from String
200 dtFromString :: (Monad m) => String -> m DiskTemplate
201 dtFromString s =
202     case () of
203       _ | s == C.dtDiskless   -> return DTDiskless
204         | s == C.dtFile       -> return DTFile
205         | s == C.dtSharedFile -> return DTSharedFile
206         | s == C.dtPlain      -> return DTPlain
207         | s == C.dtBlock      -> return DTBlock
208         | s == C.dtDrbd8      -> return DTDrbd8
209         | otherwise           -> fail $ "Invalid disk template: " ++ s
210
211 instance JSON.JSON DiskTemplate where
212     showJSON = JSON.showJSON . dtToString
213     readJSON s = case JSON.readJSON s of
214                    JSON.Ok s' -> dtFromString s'
215                    JSON.Error e -> JSON.Error $
216                                    "Can't parse disk_template as string: " ++ e
217
218 -- | Formatted solution output for one move (involved nodes and
219 -- commands.
220 type MoveJob = ([Ndx], Idx, IMove, [String])
221
222 -- | Unknown field in table output.
223 unknownField :: String
224 unknownField = "<unknown field>"
225
226 -- | A list of command elements.
227 type JobSet = [MoveJob]
228
229 -- | Connection timeout (when using non-file methods).
230 connTimeout :: Int
231 connTimeout = 15
232
233 -- | The default timeout for queries (when using non-file methods).
234 queryTimeout :: Int
235 queryTimeout = 60
236
237 -- | Default vcpu-to-pcpu ratio (randomly chosen value).
238 defVcpuRatio :: Double
239 defVcpuRatio = 64
240
241 -- | Default max disk usage ratio.
242 defReservedDiskRatio :: Double
243 defReservedDiskRatio = 0
244
245 -- | Base memory unit.
246 unitMem :: Int
247 unitMem = 64
248
249 -- | Base disk unit.
250 unitDsk :: Int
251 unitDsk = 256
252
253 -- | Base vcpus unit.
254 unitCpu :: Int
255 unitCpu = 1
256
257 {-|
258
259 This is similar to the JSON library Result type - /very/ similar, but
260 we want to use it in multiple places, so we abstract it into a
261 mini-library here
262
263 -}
264 data Result a
265     = Bad String
266     | Ok a
267     deriving (Show, Read)
268
269 instance Monad Result where
270     (>>=) (Bad x) _ = Bad x
271     (>>=) (Ok x) fn = fn x
272     return = Ok
273     fail = Bad
274
275 -- | Simple checker for whether a 'Result' is OK.
276 isOk :: Result a -> Bool
277 isOk (Ok _) = True
278 isOk _ = False
279
280 -- | Simple checker for whether a 'Result' is a failure.
281 isBad :: Result a  -> Bool
282 isBad = not . isOk
283
284 -- | Reason for an operation's falure.
285 data FailMode = FailMem  -- ^ Failed due to not enough RAM
286               | FailDisk -- ^ Failed due to not enough disk
287               | FailCPU  -- ^ Failed due to not enough CPU capacity
288               | FailN1   -- ^ Failed due to not passing N1 checks
289               | FailTags -- ^ Failed due to tag exclusion
290                 deriving (Eq, Enum, Bounded, Show, Read)
291
292 -- | List with failure statistics.
293 type FailStats = [(FailMode, Int)]
294
295 -- | Either-like data-type customized for our failure modes.
296 data OpResult a = OpFail FailMode -- ^ Failed operation
297                 | OpGood a        -- ^ Success operation
298                   deriving (Show, Read)
299
300 instance Monad OpResult where
301     (OpGood x) >>= fn = fn x
302     (OpFail y) >>= _ = OpFail y
303     return = OpGood
304
305 -- | A generic class for items that have updateable names and indices.
306 class Element a where
307     -- | Returns the name of the element
308     nameOf  :: a -> String
309     -- | Returns all the known names of the element
310     allNames :: a -> [String]
311     -- | Returns the index of the element
312     idxOf   :: a -> Int
313     -- | Updates the alias of the element
314     setAlias :: a -> String -> a
315     -- | Compute the alias by stripping a given suffix (domain) from
316     -- the name
317     computeAlias :: String -> a -> a
318     computeAlias dom e = setAlias e alias
319         where alias = take (length name - length dom) name
320               name = nameOf e
321     -- | Updates the index of the element
322     setIdx  :: a -> Int -> a
323
324 -- | The iallocator node-evacuate evac_mode type.
325 data EvacMode = ChangePrimary
326               | ChangeSecondary
327               | ChangeAll
328                 deriving (Show, Read)