Statistics
| Branch: | Tag: | Revision:

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

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