Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ bfe6c954

History | View | Annotate | Download (9.8 kB)

1 e4c5beaf Iustin Pop
{-| Some common types.
2 e4c5beaf Iustin Pop
3 e4c5beaf Iustin Pop
-}
4 e4c5beaf Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 2e5eb96a Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 e4c5beaf Iustin Pop
module Ganeti.HTools.Types
27 19f38ee8 Iustin Pop
    ( Idx
28 19f38ee8 Iustin Pop
    , Ndx
29 0dc1bf87 Iustin Pop
    , Gdx
30 19f38ee8 Iustin Pop
    , NameAssoc
31 92e32d76 Iustin Pop
    , Score
32 2180829f Iustin Pop
    , Weight
33 c4d98278 Iustin Pop
    , GroupID
34 0dc1bf87 Iustin Pop
    , AllocPolicy(..)
35 b2ba4669 Iustin Pop
    , apolFromString
36 b2ba4669 Iustin Pop
    , apolToString
37 1f9066c0 Iustin Pop
    , RSpec(..)
38 2180829f Iustin Pop
    , DynUtil(..)
39 2180829f Iustin Pop
    , zeroUtil
40 ee9724b9 Iustin Pop
    , baseUtil
41 2180829f Iustin Pop
    , addUtil
42 2180829f Iustin Pop
    , subUtil
43 f4c0b8c5 Iustin Pop
    , defVcpuRatio
44 f4c0b8c5 Iustin Pop
    , defReservedDiskRatio
45 1e3dccc8 Iustin Pop
    , unitMem
46 1e3dccc8 Iustin Pop
    , unitCpu
47 1e3dccc8 Iustin Pop
    , unitDsk
48 82ea2874 Iustin Pop
    , unknownField
49 92e32d76 Iustin Pop
    , Placement
50 92e32d76 Iustin Pop
    , IMove(..)
51 cc25e437 Iustin Pop
    , DiskTemplate(..)
52 cc25e437 Iustin Pop
    , dtToString
53 cc25e437 Iustin Pop
    , dtFromString
54 0e8ae201 Iustin Pop
    , MoveJob
55 0e8ae201 Iustin Pop
    , JobSet
56 19f38ee8 Iustin Pop
    , Result(..)
57 06fb841e Iustin Pop
    , isOk
58 06fb841e Iustin Pop
    , isBad
59 19f38ee8 Iustin Pop
    , Element(..)
60 f2280553 Iustin Pop
    , FailMode(..)
61 478df686 Iustin Pop
    , FailStats
62 f2280553 Iustin Pop
    , OpResult(..)
63 135a6c6a Iustin Pop
    , connTimeout
64 135a6c6a Iustin Pop
    , queryTimeout
65 1fe412bb Iustin Pop
    , EvacMode(..)
66 19f38ee8 Iustin Pop
    ) where
67 e4c5beaf Iustin Pop
68 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
69 b2ba4669 Iustin Pop
import qualified Text.JSON as JSON
70 2d0ca2c5 Iustin Pop
71 2e5eb96a Iustin Pop
import qualified Ganeti.Constants as C
72 2e5eb96a Iustin Pop
73 9188aeef Iustin Pop
-- | The instance index type.
74 608efcce Iustin Pop
type Idx = Int
75 608efcce Iustin Pop
76 9188aeef Iustin Pop
-- | The node index type.
77 608efcce Iustin Pop
type Ndx = Int
78 608efcce Iustin Pop
79 0dc1bf87 Iustin Pop
-- | The group index type.
80 0dc1bf87 Iustin Pop
type Gdx = Int
81 0dc1bf87 Iustin Pop
82 9188aeef Iustin Pop
-- | The type used to hold name-to-idx mappings.
83 2d0ca2c5 Iustin Pop
type NameAssoc = M.Map String Int
84 e4c5beaf Iustin Pop
85 92e32d76 Iustin Pop
-- | A separate name for the cluster score type.
86 92e32d76 Iustin Pop
type Score = Double
87 92e32d76 Iustin Pop
88 2180829f Iustin Pop
-- | A separate name for a weight metric.
89 2180829f Iustin Pop
type Weight = Double
90 2180829f Iustin Pop
91 0dc1bf87 Iustin Pop
-- | The Group UUID type.
92 c4d98278 Iustin Pop
type GroupID = String
93 c4d98278 Iustin Pop
94 0dc1bf87 Iustin Pop
-- | The Group allocation policy type.
95 73206d0a Iustin Pop
--
96 73206d0a Iustin Pop
-- Note that the order of constructors is important as the automatic
97 73206d0a Iustin Pop
-- Ord instance will order them in the order they are defined, so when
98 73206d0a Iustin Pop
-- changing this data type be careful about the interaction with the
99 73206d0a Iustin Pop
-- desired sorting order.
100 73206d0a Iustin Pop
data AllocPolicy
101 73206d0a Iustin Pop
    = AllocPreferred   -- ^ This is the normal status, the group
102 73206d0a Iustin Pop
                       -- should be used normally during allocations
103 73206d0a Iustin Pop
    | AllocLastResort  -- ^ This group should be used only as
104 73206d0a Iustin Pop
                       -- last-resort, after the preferred groups
105 73206d0a Iustin Pop
    | AllocUnallocable -- ^ This group must not be used for new
106 73206d0a Iustin Pop
                       -- allocations
107 3c002a13 Iustin Pop
      deriving (Show, Read, Eq, Ord, Enum, Bounded)
108 0dc1bf87 Iustin Pop
109 525bfb36 Iustin Pop
-- | Convert a string to an alloc policy.
110 b2ba4669 Iustin Pop
apolFromString :: (Monad m) => String -> m AllocPolicy
111 b2ba4669 Iustin Pop
apolFromString s =
112 2e5eb96a Iustin Pop
    case () of
113 2e5eb96a Iustin Pop
      _ | s == C.allocPolicyPreferred -> return AllocPreferred
114 2e5eb96a Iustin Pop
        | s == C.allocPolicyLastResort -> return AllocLastResort
115 2e5eb96a Iustin Pop
        | s == C.allocPolicyUnallocable -> return AllocUnallocable
116 2e5eb96a Iustin Pop
        | otherwise -> fail $ "Invalid alloc policy mode: " ++ s
117 b2ba4669 Iustin Pop
118 525bfb36 Iustin Pop
-- | Convert an alloc policy to the Ganeti string equivalent.
119 b2ba4669 Iustin Pop
apolToString :: AllocPolicy -> String
120 2e5eb96a Iustin Pop
apolToString AllocPreferred   = C.allocPolicyPreferred
121 2e5eb96a Iustin Pop
apolToString AllocLastResort  = C.allocPolicyLastResort
122 2e5eb96a Iustin Pop
apolToString AllocUnallocable = C.allocPolicyUnallocable
123 b2ba4669 Iustin Pop
124 b2ba4669 Iustin Pop
instance JSON.JSON AllocPolicy where
125 b2ba4669 Iustin Pop
    showJSON = JSON.showJSON . apolToString
126 b2ba4669 Iustin Pop
    readJSON s = case JSON.readJSON s of
127 b2ba4669 Iustin Pop
                   JSON.Ok s' -> apolFromString s'
128 b2ba4669 Iustin Pop
                   JSON.Error e -> JSON.Error $
129 b2ba4669 Iustin Pop
                                   "Can't parse alloc_policy: " ++ e
130 b2ba4669 Iustin Pop
131 1f9066c0 Iustin Pop
-- | The resource spec type.
132 1f9066c0 Iustin Pop
data RSpec = RSpec
133 1f9066c0 Iustin Pop
    { rspecCpu  :: Int  -- ^ Requested VCPUs
134 1f9066c0 Iustin Pop
    , rspecMem  :: Int  -- ^ Requested memory
135 1f9066c0 Iustin Pop
    , rspecDsk  :: Int  -- ^ Requested disk
136 6bc39970 Iustin Pop
    } deriving (Show, Read, Eq)
137 1f9066c0 Iustin Pop
138 2180829f Iustin Pop
-- | The dynamic resource specs of a machine (i.e. load or load
139 2180829f Iustin Pop
-- capacity, as opposed to size).
140 2180829f Iustin Pop
data DynUtil = DynUtil
141 2180829f Iustin Pop
    { cpuWeight :: Weight -- ^ Standardised CPU usage
142 2180829f Iustin Pop
    , memWeight :: Weight -- ^ Standardised memory load
143 c4ef235b Iustin Pop
    , dskWeight :: Weight -- ^ Standardised disk I\/O usage
144 2180829f Iustin Pop
    , netWeight :: Weight -- ^ Standardised network usage
145 6bc39970 Iustin Pop
    } deriving (Show, Read, Eq)
146 2180829f Iustin Pop
147 525bfb36 Iustin Pop
-- | Initial empty utilisation.
148 2180829f Iustin Pop
zeroUtil :: DynUtil
149 2180829f Iustin Pop
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
150 2180829f Iustin Pop
                   , dskWeight = 0, netWeight = 0 }
151 2180829f Iustin Pop
152 525bfb36 Iustin Pop
-- | Base utilisation (used when no actual utilisation data is
153 525bfb36 Iustin Pop
-- supplied).
154 ee9724b9 Iustin Pop
baseUtil :: DynUtil
155 ee9724b9 Iustin Pop
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
156 ee9724b9 Iustin Pop
                   , dskWeight = 1, netWeight = 1 }
157 ee9724b9 Iustin Pop
158 525bfb36 Iustin Pop
-- | Sum two utilisation records.
159 2180829f Iustin Pop
addUtil :: DynUtil -> DynUtil -> DynUtil
160 2180829f Iustin Pop
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
161 2180829f Iustin Pop
    DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
162 2180829f Iustin Pop
163 525bfb36 Iustin Pop
-- | Substracts one utilisation record from another.
164 2180829f Iustin Pop
subUtil :: DynUtil -> DynUtil -> DynUtil
165 2180829f Iustin Pop
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
166 2180829f Iustin Pop
    DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
167 2180829f Iustin Pop
168 66dac8e0 Iustin Pop
-- | The description of an instance placement. It contains the
169 66dac8e0 Iustin Pop
-- instance index, the new primary and secondary node, the move being
170 66dac8e0 Iustin Pop
-- performed and the score of the cluster after the move.
171 66dac8e0 Iustin Pop
type Placement = (Idx, Ndx, Ndx, IMove, Score)
172 92e32d76 Iustin Pop
173 525bfb36 Iustin Pop
-- | An instance move definition.
174 92e32d76 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
175 92e32d76 Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
176 92e32d76 Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
177 92e32d76 Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
178 92e32d76 Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
179 6bc39970 Iustin Pop
             deriving (Show, Read)
180 92e32d76 Iustin Pop
181 cc25e437 Iustin Pop
-- | Instance disk template type
182 cc25e437 Iustin Pop
data DiskTemplate = DTDiskless
183 cc25e437 Iustin Pop
                  | DTFile
184 cc25e437 Iustin Pop
                  | DTSharedFile
185 cc25e437 Iustin Pop
                  | DTPlain
186 cc25e437 Iustin Pop
                  | DTBlock
187 cc25e437 Iustin Pop
                  | DTDrbd8
188 3c002a13 Iustin Pop
                    deriving (Show, Read, Eq, Enum, Bounded)
189 cc25e437 Iustin Pop
190 cc25e437 Iustin Pop
-- | Converts a DiskTemplate to String
191 cc25e437 Iustin Pop
dtToString :: DiskTemplate -> String
192 cc25e437 Iustin Pop
dtToString DTDiskless   = C.dtDiskless
193 cc25e437 Iustin Pop
dtToString DTFile       = C.dtFile
194 cc25e437 Iustin Pop
dtToString DTSharedFile = C.dtSharedFile
195 cc25e437 Iustin Pop
dtToString DTPlain      = C.dtPlain
196 cc25e437 Iustin Pop
dtToString DTBlock      = C.dtBlock
197 cc25e437 Iustin Pop
dtToString DTDrbd8      = C.dtDrbd8
198 cc25e437 Iustin Pop
199 cc25e437 Iustin Pop
-- | Converts a DiskTemplate from String
200 cc25e437 Iustin Pop
dtFromString :: (Monad m) => String -> m DiskTemplate
201 cc25e437 Iustin Pop
dtFromString s =
202 cc25e437 Iustin Pop
    case () of
203 cc25e437 Iustin Pop
      _ | s == C.dtDiskless   -> return DTDiskless
204 cc25e437 Iustin Pop
        | s == C.dtFile       -> return DTFile
205 cc25e437 Iustin Pop
        | s == C.dtSharedFile -> return DTSharedFile
206 cc25e437 Iustin Pop
        | s == C.dtPlain      -> return DTPlain
207 cc25e437 Iustin Pop
        | s == C.dtBlock      -> return DTBlock
208 cc25e437 Iustin Pop
        | s == C.dtDrbd8      -> return DTDrbd8
209 cc25e437 Iustin Pop
        | otherwise           -> fail $ "Invalid disk template: " ++ s
210 cc25e437 Iustin Pop
211 cc25e437 Iustin Pop
instance JSON.JSON DiskTemplate where
212 cc25e437 Iustin Pop
    showJSON = JSON.showJSON . dtToString
213 cc25e437 Iustin Pop
    readJSON s = case JSON.readJSON s of
214 cc25e437 Iustin Pop
                   JSON.Ok s' -> dtFromString s'
215 cc25e437 Iustin Pop
                   JSON.Error e -> JSON.Error $
216 cc25e437 Iustin Pop
                                   "Can't parse disk_template as string: " ++ e
217 cc25e437 Iustin Pop
218 0e8ae201 Iustin Pop
-- | Formatted solution output for one move (involved nodes and
219 525bfb36 Iustin Pop
-- commands.
220 924f9c16 Iustin Pop
type MoveJob = ([Ndx], Idx, IMove, [String])
221 0e8ae201 Iustin Pop
222 525bfb36 Iustin Pop
-- | Unknown field in table output.
223 82ea2874 Iustin Pop
unknownField :: String
224 82ea2874 Iustin Pop
unknownField = "<unknown field>"
225 82ea2874 Iustin Pop
226 525bfb36 Iustin Pop
-- | A list of command elements.
227 0e8ae201 Iustin Pop
type JobSet = [MoveJob]
228 0e8ae201 Iustin Pop
229 135a6c6a Iustin Pop
-- | Connection timeout (when using non-file methods).
230 135a6c6a Iustin Pop
connTimeout :: Int
231 135a6c6a Iustin Pop
connTimeout = 15
232 135a6c6a Iustin Pop
233 135a6c6a Iustin Pop
-- | The default timeout for queries (when using non-file methods).
234 135a6c6a Iustin Pop
queryTimeout :: Int
235 135a6c6a Iustin Pop
queryTimeout = 60
236 135a6c6a Iustin Pop
237 f4c0b8c5 Iustin Pop
-- | Default vcpu-to-pcpu ratio (randomly chosen value).
238 f4c0b8c5 Iustin Pop
defVcpuRatio :: Double
239 f4c0b8c5 Iustin Pop
defVcpuRatio = 64
240 f4c0b8c5 Iustin Pop
241 f4c0b8c5 Iustin Pop
-- | Default max disk usage ratio.
242 f4c0b8c5 Iustin Pop
defReservedDiskRatio :: Double
243 f4c0b8c5 Iustin Pop
defReservedDiskRatio = 0
244 f4c0b8c5 Iustin Pop
245 1e3dccc8 Iustin Pop
-- | Base memory unit.
246 1e3dccc8 Iustin Pop
unitMem :: Int
247 1e3dccc8 Iustin Pop
unitMem = 64
248 1e3dccc8 Iustin Pop
249 1e3dccc8 Iustin Pop
-- | Base disk unit.
250 1e3dccc8 Iustin Pop
unitDsk :: Int
251 1e3dccc8 Iustin Pop
unitDsk = 256
252 1e3dccc8 Iustin Pop
253 1e3dccc8 Iustin Pop
-- | Base vcpus unit.
254 1e3dccc8 Iustin Pop
unitCpu :: Int
255 1e3dccc8 Iustin Pop
unitCpu = 1
256 1e3dccc8 Iustin Pop
257 262a08a2 Iustin Pop
{-|
258 e4c5beaf Iustin Pop
259 525bfb36 Iustin Pop
This is similar to the JSON library Result type - /very/ similar, but
260 e4c5beaf Iustin Pop
we want to use it in multiple places, so we abstract it into a
261 e4c5beaf Iustin Pop
mini-library here
262 e4c5beaf Iustin Pop
263 e4c5beaf Iustin Pop
-}
264 e4c5beaf Iustin Pop
data Result a
265 e4c5beaf Iustin Pop
    = Bad String
266 e4c5beaf Iustin Pop
    | Ok a
267 6bc39970 Iustin Pop
    deriving (Show, Read)
268 e4c5beaf Iustin Pop
269 e4c5beaf Iustin Pop
instance Monad Result where
270 e4c5beaf Iustin Pop
    (>>=) (Bad x) _ = Bad x
271 e4c5beaf Iustin Pop
    (>>=) (Ok x) fn = fn x
272 e4c5beaf Iustin Pop
    return = Ok
273 e4c5beaf Iustin Pop
    fail = Bad
274 497e30a1 Iustin Pop
275 525bfb36 Iustin Pop
-- | Simple checker for whether a 'Result' is OK.
276 06fb841e Iustin Pop
isOk :: Result a -> Bool
277 06fb841e Iustin Pop
isOk (Ok _) = True
278 06fb841e Iustin Pop
isOk _ = False
279 06fb841e Iustin Pop
280 525bfb36 Iustin Pop
-- | Simple checker for whether a 'Result' is a failure.
281 06fb841e Iustin Pop
isBad :: Result a  -> Bool
282 06fb841e Iustin Pop
isBad = not . isOk
283 06fb841e Iustin Pop
284 525bfb36 Iustin Pop
-- | Reason for an operation's falure.
285 f2280553 Iustin Pop
data FailMode = FailMem  -- ^ Failed due to not enough RAM
286 f2280553 Iustin Pop
              | FailDisk -- ^ Failed due to not enough disk
287 f2280553 Iustin Pop
              | FailCPU  -- ^ Failed due to not enough CPU capacity
288 f2280553 Iustin Pop
              | FailN1   -- ^ Failed due to not passing N1 checks
289 5f0b9579 Iustin Pop
              | FailTags -- ^ Failed due to tag exclusion
290 6bc39970 Iustin Pop
                deriving (Eq, Enum, Bounded, Show, Read)
291 f2280553 Iustin Pop
292 525bfb36 Iustin Pop
-- | List with failure statistics.
293 478df686 Iustin Pop
type FailStats = [(FailMode, Int)]
294 478df686 Iustin Pop
295 525bfb36 Iustin Pop
-- | Either-like data-type customized for our failure modes.
296 f2280553 Iustin Pop
data OpResult a = OpFail FailMode -- ^ Failed operation
297 f2280553 Iustin Pop
                | OpGood a        -- ^ Success operation
298 6bc39970 Iustin Pop
                  deriving (Show, Read)
299 f2280553 Iustin Pop
300 f2280553 Iustin Pop
instance Monad OpResult where
301 f2280553 Iustin Pop
    (OpGood x) >>= fn = fn x
302 f2280553 Iustin Pop
    (OpFail y) >>= _ = OpFail y
303 f2280553 Iustin Pop
    return = OpGood
304 f2280553 Iustin Pop
305 9188aeef Iustin Pop
-- | A generic class for items that have updateable names and indices.
306 497e30a1 Iustin Pop
class Element a where
307 9188aeef Iustin Pop
    -- | Returns the name of the element
308 262a08a2 Iustin Pop
    nameOf  :: a -> String
309 c854092b Iustin Pop
    -- | Returns all the known names of the element
310 c854092b Iustin Pop
    allNames :: a -> [String]
311 9188aeef Iustin Pop
    -- | Returns the index of the element
312 262a08a2 Iustin Pop
    idxOf   :: a -> Int
313 3e4480e0 Iustin Pop
    -- | Updates the alias of the element
314 3e4480e0 Iustin Pop
    setAlias :: a -> String -> a
315 3e4480e0 Iustin Pop
    -- | Compute the alias by stripping a given suffix (domain) from
316 525bfb36 Iustin Pop
    -- the name
317 3e4480e0 Iustin Pop
    computeAlias :: String -> a -> a
318 3e4480e0 Iustin Pop
    computeAlias dom e = setAlias e alias
319 3e4480e0 Iustin Pop
        where alias = take (length name - length dom) name
320 3e4480e0 Iustin Pop
              name = nameOf e
321 9188aeef Iustin Pop
    -- | Updates the index of the element
322 497e30a1 Iustin Pop
    setIdx  :: a -> Int -> a
323 1fe412bb Iustin Pop
324 1fe412bb Iustin Pop
-- | The iallocator node-evacuate evac_mode type.
325 1fe412bb Iustin Pop
data EvacMode = ChangePrimary
326 1fe412bb Iustin Pop
              | ChangeSecondary
327 1fe412bb Iustin Pop
              | ChangeAll
328 1fe412bb Iustin Pop
                deriving (Show, Read)