Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (12.2 kB)

1 e9aaa3c6 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e9aaa3c6 Iustin Pop
3 e4c5beaf Iustin Pop
{-| Some common types.
4 e4c5beaf Iustin Pop
5 e4c5beaf Iustin Pop
-}
6 e4c5beaf Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 e8fa4ff6 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 e4c5beaf Iustin Pop
module Ganeti.HTools.Types
29 ebf38064 Iustin Pop
  ( Idx
30 ebf38064 Iustin Pop
  , Ndx
31 ebf38064 Iustin Pop
  , Gdx
32 ebf38064 Iustin Pop
  , NameAssoc
33 ebf38064 Iustin Pop
  , Score
34 ebf38064 Iustin Pop
  , Weight
35 ebf38064 Iustin Pop
  , GroupID
36 f3f76ccc Iustin Pop
  , defaultGroupID
37 ebf38064 Iustin Pop
  , AllocPolicy(..)
38 ebf38064 Iustin Pop
  , allocPolicyFromRaw
39 ebf38064 Iustin Pop
  , allocPolicyToRaw
40 ebf38064 Iustin Pop
  , InstanceStatus(..)
41 ebf38064 Iustin Pop
  , instanceStatusFromRaw
42 ebf38064 Iustin Pop
  , instanceStatusToRaw
43 ebf38064 Iustin Pop
  , RSpec(..)
44 76a20994 Iustin Pop
  , AllocInfo(..)
45 80d7d8a1 Iustin Pop
  , AllocStats
46 ebf38064 Iustin Pop
  , DynUtil(..)
47 ebf38064 Iustin Pop
  , zeroUtil
48 ebf38064 Iustin Pop
  , baseUtil
49 ebf38064 Iustin Pop
  , addUtil
50 ebf38064 Iustin Pop
  , subUtil
51 ebf38064 Iustin Pop
  , defReservedDiskRatio
52 ebf38064 Iustin Pop
  , unitMem
53 ebf38064 Iustin Pop
  , unitCpu
54 ebf38064 Iustin Pop
  , unitDsk
55 ebf38064 Iustin Pop
  , unknownField
56 ebf38064 Iustin Pop
  , Placement
57 ebf38064 Iustin Pop
  , IMove(..)
58 ebf38064 Iustin Pop
  , DiskTemplate(..)
59 ebf38064 Iustin Pop
  , diskTemplateToRaw
60 ebf38064 Iustin Pop
  , diskTemplateFromRaw
61 ebf38064 Iustin Pop
  , MoveJob
62 ebf38064 Iustin Pop
  , JobSet
63 ebf38064 Iustin Pop
  , Result(..)
64 ebf38064 Iustin Pop
  , isOk
65 ebf38064 Iustin Pop
  , isBad
66 ebf38064 Iustin Pop
  , eitherToResult
67 f3f76ccc Iustin Pop
  , annotateResult
68 ebf38064 Iustin Pop
  , Element(..)
69 ebf38064 Iustin Pop
  , FailMode(..)
70 ebf38064 Iustin Pop
  , FailStats
71 ebf38064 Iustin Pop
  , OpResult(..)
72 ebf38064 Iustin Pop
  , opToResult
73 ebf38064 Iustin Pop
  , connTimeout
74 ebf38064 Iustin Pop
  , queryTimeout
75 ebf38064 Iustin Pop
  , EvacMode(..)
76 a07343b2 Iustin Pop
  , ISpec(..)
77 a07343b2 Iustin Pop
  , IPolicy(..)
78 d02f941e Iustin Pop
  , defIPolicy
79 304f9292 Iustin Pop
  , rspecFromISpec
80 ebf38064 Iustin Pop
  ) where
81 e4c5beaf Iustin Pop
82 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
83 a07343b2 Iustin Pop
import Text.JSON (makeObj, readJSON, showJSON)
84 2d0ca2c5 Iustin Pop
85 2e5eb96a Iustin Pop
import qualified Ganeti.Constants as C
86 e9aaa3c6 Iustin Pop
import qualified Ganeti.THH as THH
87 0c37d1e4 Iustin Pop
import Ganeti.BasicTypes
88 a07343b2 Iustin Pop
import Ganeti.HTools.JSON
89 2e5eb96a Iustin Pop
90 9188aeef Iustin Pop
-- | The instance index type.
91 608efcce Iustin Pop
type Idx = Int
92 608efcce Iustin Pop
93 9188aeef Iustin Pop
-- | The node index type.
94 608efcce Iustin Pop
type Ndx = Int
95 608efcce Iustin Pop
96 0dc1bf87 Iustin Pop
-- | The group index type.
97 0dc1bf87 Iustin Pop
type Gdx = Int
98 0dc1bf87 Iustin Pop
99 9188aeef Iustin Pop
-- | The type used to hold name-to-idx mappings.
100 2d0ca2c5 Iustin Pop
type NameAssoc = M.Map String Int
101 e4c5beaf Iustin Pop
102 92e32d76 Iustin Pop
-- | A separate name for the cluster score type.
103 92e32d76 Iustin Pop
type Score = Double
104 92e32d76 Iustin Pop
105 2180829f Iustin Pop
-- | A separate name for a weight metric.
106 2180829f Iustin Pop
type Weight = Double
107 2180829f Iustin Pop
108 0dc1bf87 Iustin Pop
-- | The Group UUID type.
109 c4d98278 Iustin Pop
type GroupID = String
110 c4d98278 Iustin Pop
111 f3f76ccc Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
112 f3f76ccc Iustin Pop
defaultGroupID :: GroupID
113 f3f76ccc Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
114 f3f76ccc Iustin Pop
115 89c758c6 Iustin Pop
-- | Instance disk template type.
116 89c758c6 Iustin Pop
$(THH.declareSADT "DiskTemplate"
117 89c758c6 Iustin Pop
       [ ("DTDiskless",   'C.dtDiskless)
118 89c758c6 Iustin Pop
       , ("DTFile",       'C.dtFile)
119 89c758c6 Iustin Pop
       , ("DTSharedFile", 'C.dtSharedFile)
120 89c758c6 Iustin Pop
       , ("DTPlain",      'C.dtPlain)
121 89c758c6 Iustin Pop
       , ("DTBlock",      'C.dtBlock)
122 89c758c6 Iustin Pop
       , ("DTDrbd8",      'C.dtDrbd8)
123 bdd6931c Guido Trotter
       , ("DTRbd",        'C.dtRbd)
124 89c758c6 Iustin Pop
       ])
125 89c758c6 Iustin Pop
$(THH.makeJSONInstance ''DiskTemplate)
126 89c758c6 Iustin Pop
127 0dc1bf87 Iustin Pop
-- | The Group allocation policy type.
128 73206d0a Iustin Pop
--
129 73206d0a Iustin Pop
-- Note that the order of constructors is important as the automatic
130 73206d0a Iustin Pop
-- Ord instance will order them in the order they are defined, so when
131 73206d0a Iustin Pop
-- changing this data type be careful about the interaction with the
132 73206d0a Iustin Pop
-- desired sorting order.
133 e9aaa3c6 Iustin Pop
$(THH.declareSADT "AllocPolicy"
134 ebf38064 Iustin Pop
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
135 ebf38064 Iustin Pop
       , ("AllocLastResort",  'C.allocPolicyLastResort)
136 ebf38064 Iustin Pop
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
137 ebf38064 Iustin Pop
       ])
138 e9aaa3c6 Iustin Pop
$(THH.makeJSONInstance ''AllocPolicy)
139 b2ba4669 Iustin Pop
140 3771d104 Agata Murawska
-- | The Instance real state type.
141 3771d104 Agata Murawska
$(THH.declareSADT "InstanceStatus"
142 ebf38064 Iustin Pop
       [ ("AdminDown", 'C.inststAdmindown)
143 ebf38064 Iustin Pop
       , ("AdminOffline", 'C.inststAdminoffline)
144 ebf38064 Iustin Pop
       , ("ErrorDown", 'C.inststErrordown)
145 ebf38064 Iustin Pop
       , ("ErrorUp", 'C.inststErrorup)
146 ebf38064 Iustin Pop
       , ("NodeDown", 'C.inststNodedown)
147 ebf38064 Iustin Pop
       , ("NodeOffline", 'C.inststNodeoffline)
148 ebf38064 Iustin Pop
       , ("Running", 'C.inststRunning)
149 ebf38064 Iustin Pop
       , ("WrongNode", 'C.inststWrongnode)
150 ebf38064 Iustin Pop
       ])
151 3771d104 Agata Murawska
$(THH.makeJSONInstance ''InstanceStatus)
152 3771d104 Agata Murawska
153 1f9066c0 Iustin Pop
-- | The resource spec type.
154 1f9066c0 Iustin Pop
data RSpec = RSpec
155 ebf38064 Iustin Pop
  { rspecCpu  :: Int  -- ^ Requested VCPUs
156 ebf38064 Iustin Pop
  , rspecMem  :: Int  -- ^ Requested memory
157 ebf38064 Iustin Pop
  , rspecDsk  :: Int  -- ^ Requested disk
158 ebf38064 Iustin Pop
  } deriving (Show, Read, Eq)
159 1f9066c0 Iustin Pop
160 76a20994 Iustin Pop
-- | Allocation stats type. This is used instead of 'RSpec' (which was
161 76a20994 Iustin Pop
-- used at first), because we need to track more stats. The actual
162 76a20994 Iustin Pop
-- data can refer either to allocated, or available, etc. values
163 76a20994 Iustin Pop
-- depending on the context. See also
164 76a20994 Iustin Pop
-- 'Cluster.computeAllocationDelta'.
165 76a20994 Iustin Pop
data AllocInfo = AllocInfo
166 76a20994 Iustin Pop
  { allocInfoVCpus :: Int    -- ^ VCPUs
167 76a20994 Iustin Pop
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
168 76a20994 Iustin Pop
  , allocInfoMem   :: Int    -- ^ Memory
169 76a20994 Iustin Pop
  , allocInfoDisk  :: Int    -- ^ Disk
170 76a20994 Iustin Pop
  } deriving (Show, Read, Eq)
171 a07343b2 Iustin Pop
172 80d7d8a1 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
173 80d7d8a1 Iustin Pop
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
174 80d7d8a1 Iustin Pop
175 a07343b2 Iustin Pop
-- | Instance specification type.
176 a07343b2 Iustin Pop
$(THH.buildObject "ISpec" "iSpec"
177 cd79cd83 Iustin Pop
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize   [t| Int |]
178 cd79cd83 Iustin Pop
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount  [t| Int |]
179 cd79cd83 Iustin Pop
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize  [t| Int |]
180 cd79cd83 Iustin Pop
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount [t| Int |]
181 cd79cd83 Iustin Pop
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount  [t| Int |]
182 a07343b2 Iustin Pop
  ])
183 a07343b2 Iustin Pop
184 d02f941e Iustin Pop
-- | The default minimum ispec.
185 d02f941e Iustin Pop
defMinISpec :: ISpec
186 d02f941e Iustin Pop
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinMemorySize
187 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsMinCpuCount
188 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsMinDiskSize
189 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsMinDiskCount
190 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsMinNicCount
191 d02f941e Iustin Pop
                    }
192 d02f941e Iustin Pop
193 d02f941e Iustin Pop
-- | The default standard ispec.
194 d02f941e Iustin Pop
defStdISpec :: ISpec
195 d02f941e Iustin Pop
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
196 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
197 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
198 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
199 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
200 d02f941e Iustin Pop
                    }
201 d02f941e Iustin Pop
202 d02f941e Iustin Pop
-- | The default max ispec.
203 d02f941e Iustin Pop
defMaxISpec :: ISpec
204 d02f941e Iustin Pop
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMaxMemorySize
205 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsMaxCpuCount
206 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsMaxDiskSize
207 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsMaxDiskCount
208 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsMaxNicCount
209 d02f941e Iustin Pop
                    }
210 d02f941e Iustin Pop
211 a07343b2 Iustin Pop
-- | Instance policy type.
212 a07343b2 Iustin Pop
$(THH.buildObject "IPolicy" "iPolicy"
213 cd79cd83 Iustin Pop
  [ THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
214 cd79cd83 Iustin Pop
  , THH.renameField "MinSpec" $ THH.simpleField C.ispecsMin [t| ISpec |]
215 cd79cd83 Iustin Pop
  , THH.renameField "MaxSpec" $ THH.simpleField C.ispecsMax [t| ISpec |]
216 fc42a408 Iustin Pop
  , THH.renameField "DiskTemplates" $
217 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
218 e8fa4ff6 Iustin Pop
  , THH.renameField "VcpuRatio" $
219 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
220 c22d4dd4 Iustin Pop
  , THH.renameField "SpindleRatio" $
221 c22d4dd4 Iustin Pop
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
222 a07343b2 Iustin Pop
  ])
223 a07343b2 Iustin Pop
224 304f9292 Iustin Pop
-- | Converts an ISpec type to a RSpec one.
225 304f9292 Iustin Pop
rspecFromISpec :: ISpec -> RSpec
226 304f9292 Iustin Pop
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
227 304f9292 Iustin Pop
                             , rspecMem = iSpecMemorySize ispec
228 304f9292 Iustin Pop
                             , rspecDsk = iSpecDiskSize ispec
229 304f9292 Iustin Pop
                             }
230 304f9292 Iustin Pop
231 d02f941e Iustin Pop
-- | The default instance policy.
232 d02f941e Iustin Pop
defIPolicy :: IPolicy
233 d02f941e Iustin Pop
defIPolicy = IPolicy { iPolicyStdSpec = defStdISpec
234 d02f941e Iustin Pop
                     , iPolicyMinSpec = defMinISpec
235 d02f941e Iustin Pop
                     , iPolicyMaxSpec = defMaxISpec
236 fc42a408 Iustin Pop
                     -- hardcoding here since Constants.hs exports the
237 fc42a408 Iustin Pop
                     -- string values, not the actual type; and in
238 fc42a408 Iustin Pop
                     -- htools, we are mostly looking at DRBD
239 fc42a408 Iustin Pop
                     , iPolicyDiskTemplates = [DTDrbd8, DTPlain]
240 e8fa4ff6 Iustin Pop
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
241 c22d4dd4 Iustin Pop
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
242 d02f941e Iustin Pop
                     }
243 d02f941e Iustin Pop
244 2180829f Iustin Pop
-- | The dynamic resource specs of a machine (i.e. load or load
245 2180829f Iustin Pop
-- capacity, as opposed to size).
246 2180829f Iustin Pop
data DynUtil = DynUtil
247 ebf38064 Iustin Pop
  { cpuWeight :: Weight -- ^ Standardised CPU usage
248 ebf38064 Iustin Pop
  , memWeight :: Weight -- ^ Standardised memory load
249 ebf38064 Iustin Pop
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
250 ebf38064 Iustin Pop
  , netWeight :: Weight -- ^ Standardised network usage
251 ebf38064 Iustin Pop
  } deriving (Show, Read, Eq)
252 2180829f Iustin Pop
253 525bfb36 Iustin Pop
-- | Initial empty utilisation.
254 2180829f Iustin Pop
zeroUtil :: DynUtil
255 2180829f Iustin Pop
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
256 2180829f Iustin Pop
                   , dskWeight = 0, netWeight = 0 }
257 2180829f Iustin Pop
258 525bfb36 Iustin Pop
-- | Base utilisation (used when no actual utilisation data is
259 525bfb36 Iustin Pop
-- supplied).
260 ee9724b9 Iustin Pop
baseUtil :: DynUtil
261 ee9724b9 Iustin Pop
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
262 ee9724b9 Iustin Pop
                   , dskWeight = 1, netWeight = 1 }
263 ee9724b9 Iustin Pop
264 525bfb36 Iustin Pop
-- | Sum two utilisation records.
265 2180829f Iustin Pop
addUtil :: DynUtil -> DynUtil -> DynUtil
266 2180829f Iustin Pop
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
267 ebf38064 Iustin Pop
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
268 2180829f Iustin Pop
269 525bfb36 Iustin Pop
-- | Substracts one utilisation record from another.
270 2180829f Iustin Pop
subUtil :: DynUtil -> DynUtil -> DynUtil
271 2180829f Iustin Pop
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
272 ebf38064 Iustin Pop
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
273 2180829f Iustin Pop
274 66dac8e0 Iustin Pop
-- | The description of an instance placement. It contains the
275 66dac8e0 Iustin Pop
-- instance index, the new primary and secondary node, the move being
276 66dac8e0 Iustin Pop
-- performed and the score of the cluster after the move.
277 66dac8e0 Iustin Pop
type Placement = (Idx, Ndx, Ndx, IMove, Score)
278 92e32d76 Iustin Pop
279 525bfb36 Iustin Pop
-- | An instance move definition.
280 92e32d76 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
281 92e32d76 Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
282 92e32d76 Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
283 92e32d76 Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
284 92e32d76 Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
285 6bc39970 Iustin Pop
             deriving (Show, Read)
286 92e32d76 Iustin Pop
287 0e8ae201 Iustin Pop
-- | Formatted solution output for one move (involved nodes and
288 525bfb36 Iustin Pop
-- commands.
289 924f9c16 Iustin Pop
type MoveJob = ([Ndx], Idx, IMove, [String])
290 0e8ae201 Iustin Pop
291 525bfb36 Iustin Pop
-- | Unknown field in table output.
292 82ea2874 Iustin Pop
unknownField :: String
293 82ea2874 Iustin Pop
unknownField = "<unknown field>"
294 82ea2874 Iustin Pop
295 525bfb36 Iustin Pop
-- | A list of command elements.
296 0e8ae201 Iustin Pop
type JobSet = [MoveJob]
297 0e8ae201 Iustin Pop
298 135a6c6a Iustin Pop
-- | Connection timeout (when using non-file methods).
299 135a6c6a Iustin Pop
connTimeout :: Int
300 135a6c6a Iustin Pop
connTimeout = 15
301 135a6c6a Iustin Pop
302 135a6c6a Iustin Pop
-- | The default timeout for queries (when using non-file methods).
303 135a6c6a Iustin Pop
queryTimeout :: Int
304 135a6c6a Iustin Pop
queryTimeout = 60
305 135a6c6a Iustin Pop
306 f4c0b8c5 Iustin Pop
-- | Default max disk usage ratio.
307 f4c0b8c5 Iustin Pop
defReservedDiskRatio :: Double
308 f4c0b8c5 Iustin Pop
defReservedDiskRatio = 0
309 f4c0b8c5 Iustin Pop
310 1e3dccc8 Iustin Pop
-- | Base memory unit.
311 1e3dccc8 Iustin Pop
unitMem :: Int
312 1e3dccc8 Iustin Pop
unitMem = 64
313 1e3dccc8 Iustin Pop
314 1e3dccc8 Iustin Pop
-- | Base disk unit.
315 1e3dccc8 Iustin Pop
unitDsk :: Int
316 1e3dccc8 Iustin Pop
unitDsk = 256
317 1e3dccc8 Iustin Pop
318 1e3dccc8 Iustin Pop
-- | Base vcpus unit.
319 1e3dccc8 Iustin Pop
unitCpu :: Int
320 1e3dccc8 Iustin Pop
unitCpu = 1
321 1e3dccc8 Iustin Pop
322 525bfb36 Iustin Pop
-- | Reason for an operation's falure.
323 f2280553 Iustin Pop
data FailMode = FailMem  -- ^ Failed due to not enough RAM
324 f2280553 Iustin Pop
              | FailDisk -- ^ Failed due to not enough disk
325 f2280553 Iustin Pop
              | FailCPU  -- ^ Failed due to not enough CPU capacity
326 f2280553 Iustin Pop
              | FailN1   -- ^ Failed due to not passing N1 checks
327 5f0b9579 Iustin Pop
              | FailTags -- ^ Failed due to tag exclusion
328 6bc39970 Iustin Pop
                deriving (Eq, Enum, Bounded, Show, Read)
329 f2280553 Iustin Pop
330 525bfb36 Iustin Pop
-- | List with failure statistics.
331 478df686 Iustin Pop
type FailStats = [(FailMode, Int)]
332 478df686 Iustin Pop
333 525bfb36 Iustin Pop
-- | Either-like data-type customized for our failure modes.
334 a30b473c Iustin Pop
--
335 a30b473c Iustin Pop
-- The failure values for this monad track the specific allocation
336 a30b473c Iustin Pop
-- failures, so this is not a general error-monad (compare with the
337 a30b473c Iustin Pop
-- 'Result' data type). One downside is that this type cannot encode a
338 a30b473c Iustin Pop
-- generic failure mode, hence 'fail' for this monad is not defined
339 a30b473c Iustin Pop
-- and will cause an exception.
340 f2280553 Iustin Pop
data OpResult a = OpFail FailMode -- ^ Failed operation
341 f2280553 Iustin Pop
                | OpGood a        -- ^ Success operation
342 6bc39970 Iustin Pop
                  deriving (Show, Read)
343 f2280553 Iustin Pop
344 f2280553 Iustin Pop
instance Monad OpResult where
345 ebf38064 Iustin Pop
  (OpGood x) >>= fn = fn x
346 ebf38064 Iustin Pop
  (OpFail y) >>= _ = OpFail y
347 ebf38064 Iustin Pop
  return = OpGood
348 f2280553 Iustin Pop
349 a30b473c Iustin Pop
-- | Conversion from 'OpResult' to 'Result'.
350 a30b473c Iustin Pop
opToResult :: OpResult a -> Result a
351 a30b473c Iustin Pop
opToResult (OpFail f) = Bad $ show f
352 a30b473c Iustin Pop
opToResult (OpGood v) = Ok v
353 a30b473c Iustin Pop
354 9188aeef Iustin Pop
-- | A generic class for items that have updateable names and indices.
355 497e30a1 Iustin Pop
class Element a where
356 ebf38064 Iustin Pop
  -- | Returns the name of the element
357 ebf38064 Iustin Pop
  nameOf  :: a -> String
358 ebf38064 Iustin Pop
  -- | Returns all the known names of the element
359 ebf38064 Iustin Pop
  allNames :: a -> [String]
360 ebf38064 Iustin Pop
  -- | Returns the index of the element
361 ebf38064 Iustin Pop
  idxOf   :: a -> Int
362 ebf38064 Iustin Pop
  -- | Updates the alias of the element
363 ebf38064 Iustin Pop
  setAlias :: a -> String -> a
364 ebf38064 Iustin Pop
  -- | Compute the alias by stripping a given suffix (domain) from
365 ebf38064 Iustin Pop
  -- the name
366 ebf38064 Iustin Pop
  computeAlias :: String -> a -> a
367 ebf38064 Iustin Pop
  computeAlias dom e = setAlias e alias
368 ebf38064 Iustin Pop
    where alias = take (length name - length dom) name
369 ebf38064 Iustin Pop
          name = nameOf e
370 ebf38064 Iustin Pop
  -- | Updates the index of the element
371 ebf38064 Iustin Pop
  setIdx  :: a -> Int -> a
372 1fe412bb Iustin Pop
373 1fe412bb Iustin Pop
-- | The iallocator node-evacuate evac_mode type.
374 e9aaa3c6 Iustin Pop
$(THH.declareSADT "EvacMode"
375 ebf38064 Iustin Pop
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
376 ebf38064 Iustin Pop
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
377 ebf38064 Iustin Pop
       , ("ChangeAll",       'C.iallocatorNevacAll)
378 ebf38064 Iustin Pop
       ])
379 e9aaa3c6 Iustin Pop
$(THH.makeJSONInstance ''EvacMode)