Statistics
| Branch: | Tag: | Revision:

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

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