Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 76a20994

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