Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 7c14b50a

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