Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.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 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 b906d7c1 Iustin Pop
  , MirrorType(..)
62 b906d7c1 Iustin Pop
  , templateMirrorType
63 ebf38064 Iustin Pop
  , MoveJob
64 ebf38064 Iustin Pop
  , JobSet
65 ebf38064 Iustin Pop
  , Element(..)
66 ebf38064 Iustin Pop
  , FailMode(..)
67 ebf38064 Iustin Pop
  , FailStats
68 a8038349 Iustin Pop
  , OpResult
69 ebf38064 Iustin Pop
  , opToResult
70 ebf38064 Iustin Pop
  , EvacMode(..)
71 a07343b2 Iustin Pop
  , ISpec(..)
72 a07343b2 Iustin Pop
  , IPolicy(..)
73 d02f941e Iustin Pop
  , defIPolicy
74 304f9292 Iustin Pop
  , rspecFromISpec
75 ebf38064 Iustin Pop
  ) where
76 e4c5beaf Iustin Pop
77 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
78 2d0ca2c5 Iustin Pop
79 2e5eb96a Iustin Pop
import qualified Ganeti.Constants as C
80 e9aaa3c6 Iustin Pop
import qualified Ganeti.THH as THH
81 0c37d1e4 Iustin Pop
import Ganeti.BasicTypes
82 5e9deac0 Iustin Pop
import Ganeti.Types
83 2e5eb96a Iustin Pop
84 9188aeef Iustin Pop
-- | The instance index type.
85 608efcce Iustin Pop
type Idx = Int
86 608efcce Iustin Pop
87 9188aeef Iustin Pop
-- | The node index type.
88 608efcce Iustin Pop
type Ndx = Int
89 608efcce Iustin Pop
90 0dc1bf87 Iustin Pop
-- | The group index type.
91 0dc1bf87 Iustin Pop
type Gdx = Int
92 0dc1bf87 Iustin Pop
93 9188aeef Iustin Pop
-- | The type used to hold name-to-idx mappings.
94 2d0ca2c5 Iustin Pop
type NameAssoc = M.Map String Int
95 e4c5beaf Iustin Pop
96 92e32d76 Iustin Pop
-- | A separate name for the cluster score type.
97 92e32d76 Iustin Pop
type Score = Double
98 92e32d76 Iustin Pop
99 2180829f Iustin Pop
-- | A separate name for a weight metric.
100 2180829f Iustin Pop
type Weight = Double
101 2180829f Iustin Pop
102 0dc1bf87 Iustin Pop
-- | The Group UUID type.
103 c4d98278 Iustin Pop
type GroupID = String
104 c4d98278 Iustin Pop
105 f3f76ccc Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
106 f3f76ccc Iustin Pop
defaultGroupID :: GroupID
107 f3f76ccc Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
108 f3f76ccc Iustin Pop
109 b906d7c1 Iustin Pop
-- | Mirroring type.
110 b906d7c1 Iustin Pop
data MirrorType = MirrorNone     -- ^ No mirroring/movability
111 b906d7c1 Iustin Pop
                | MirrorInternal -- ^ DRBD-type mirroring
112 b906d7c1 Iustin Pop
                | MirrorExternal -- ^ Shared-storage type mirroring
113 139c0683 Iustin Pop
                  deriving (Eq, Show)
114 b906d7c1 Iustin Pop
115 b906d7c1 Iustin Pop
-- | Correspondence between disk template and mirror type.
116 b906d7c1 Iustin Pop
templateMirrorType :: DiskTemplate -> MirrorType
117 b906d7c1 Iustin Pop
templateMirrorType DTDiskless   = MirrorExternal
118 b906d7c1 Iustin Pop
templateMirrorType DTFile       = MirrorNone
119 b906d7c1 Iustin Pop
templateMirrorType DTSharedFile = MirrorExternal
120 b906d7c1 Iustin Pop
templateMirrorType DTPlain      = MirrorNone
121 b906d7c1 Iustin Pop
templateMirrorType DTBlock      = MirrorExternal
122 b906d7c1 Iustin Pop
templateMirrorType DTDrbd8      = MirrorInternal
123 b906d7c1 Iustin Pop
templateMirrorType DTRbd        = MirrorExternal
124 b906d7c1 Iustin Pop
125 1f9066c0 Iustin Pop
-- | The resource spec type.
126 1f9066c0 Iustin Pop
data RSpec = RSpec
127 ebf38064 Iustin Pop
  { rspecCpu  :: Int  -- ^ Requested VCPUs
128 ebf38064 Iustin Pop
  , rspecMem  :: Int  -- ^ Requested memory
129 ebf38064 Iustin Pop
  , rspecDsk  :: Int  -- ^ Requested disk
130 139c0683 Iustin Pop
  } deriving (Show, Eq)
131 1f9066c0 Iustin Pop
132 76a20994 Iustin Pop
-- | Allocation stats type. This is used instead of 'RSpec' (which was
133 76a20994 Iustin Pop
-- used at first), because we need to track more stats. The actual
134 76a20994 Iustin Pop
-- data can refer either to allocated, or available, etc. values
135 76a20994 Iustin Pop
-- depending on the context. See also
136 76a20994 Iustin Pop
-- 'Cluster.computeAllocationDelta'.
137 76a20994 Iustin Pop
data AllocInfo = AllocInfo
138 76a20994 Iustin Pop
  { allocInfoVCpus :: Int    -- ^ VCPUs
139 76a20994 Iustin Pop
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
140 76a20994 Iustin Pop
  , allocInfoMem   :: Int    -- ^ Memory
141 76a20994 Iustin Pop
  , allocInfoDisk  :: Int    -- ^ Disk
142 139c0683 Iustin Pop
  } deriving (Show, Eq)
143 a07343b2 Iustin Pop
144 80d7d8a1 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
145 80d7d8a1 Iustin Pop
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
146 80d7d8a1 Iustin Pop
147 a07343b2 Iustin Pop
-- | Instance specification type.
148 a07343b2 Iustin Pop
$(THH.buildObject "ISpec" "iSpec"
149 9cda4d6a Iustin Pop
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
150 9cda4d6a Iustin Pop
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
151 9cda4d6a Iustin Pop
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
152 9cda4d6a Iustin Pop
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
153 9cda4d6a Iustin Pop
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
154 9cda4d6a Iustin Pop
  , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
155 a07343b2 Iustin Pop
  ])
156 a07343b2 Iustin Pop
157 d02f941e Iustin Pop
-- | The default minimum ispec.
158 d02f941e Iustin Pop
defMinISpec :: ISpec
159 d02f941e Iustin Pop
defMinISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMinMemorySize
160 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsMinCpuCount
161 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsMinDiskSize
162 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsMinDiskCount
163 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsMinNicCount
164 d953a965 Renรฉ Nussbaumer
                    , iSpecSpindleUse = C.ipolicyDefaultsMinSpindleUse
165 d02f941e Iustin Pop
                    }
166 d02f941e Iustin Pop
167 d02f941e Iustin Pop
-- | The default standard ispec.
168 d02f941e Iustin Pop
defStdISpec :: ISpec
169 d02f941e Iustin Pop
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
170 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
171 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
172 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
173 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
174 d953a965 Renรฉ Nussbaumer
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
175 d02f941e Iustin Pop
                    }
176 d02f941e Iustin Pop
177 d02f941e Iustin Pop
-- | The default max ispec.
178 d02f941e Iustin Pop
defMaxISpec :: ISpec
179 d02f941e Iustin Pop
defMaxISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsMaxMemorySize
180 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsMaxCpuCount
181 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsMaxDiskSize
182 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsMaxDiskCount
183 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsMaxNicCount
184 d953a965 Renรฉ Nussbaumer
                    , iSpecSpindleUse = C.ipolicyDefaultsMaxSpindleUse
185 d02f941e Iustin Pop
                    }
186 d02f941e Iustin Pop
187 a07343b2 Iustin Pop
-- | Instance policy type.
188 a07343b2 Iustin Pop
$(THH.buildObject "IPolicy" "iPolicy"
189 cd79cd83 Iustin Pop
  [ THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
190 cd79cd83 Iustin Pop
  , THH.renameField "MinSpec" $ THH.simpleField C.ispecsMin [t| ISpec |]
191 cd79cd83 Iustin Pop
  , THH.renameField "MaxSpec" $ THH.simpleField C.ispecsMax [t| ISpec |]
192 fc42a408 Iustin Pop
  , THH.renameField "DiskTemplates" $
193 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
194 e8fa4ff6 Iustin Pop
  , THH.renameField "VcpuRatio" $
195 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
196 c22d4dd4 Iustin Pop
  , THH.renameField "SpindleRatio" $
197 c22d4dd4 Iustin Pop
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
198 a07343b2 Iustin Pop
  ])
199 a07343b2 Iustin Pop
200 304f9292 Iustin Pop
-- | Converts an ISpec type to a RSpec one.
201 304f9292 Iustin Pop
rspecFromISpec :: ISpec -> RSpec
202 304f9292 Iustin Pop
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
203 304f9292 Iustin Pop
                             , rspecMem = iSpecMemorySize ispec
204 304f9292 Iustin Pop
                             , rspecDsk = iSpecDiskSize ispec
205 304f9292 Iustin Pop
                             }
206 304f9292 Iustin Pop
207 d02f941e Iustin Pop
-- | The default instance policy.
208 d02f941e Iustin Pop
defIPolicy :: IPolicy
209 d02f941e Iustin Pop
defIPolicy = IPolicy { iPolicyStdSpec = defStdISpec
210 d02f941e Iustin Pop
                     , iPolicyMinSpec = defMinISpec
211 d02f941e Iustin Pop
                     , iPolicyMaxSpec = defMaxISpec
212 fc42a408 Iustin Pop
                     -- hardcoding here since Constants.hs exports the
213 fc42a408 Iustin Pop
                     -- string values, not the actual type; and in
214 fc42a408 Iustin Pop
                     -- htools, we are mostly looking at DRBD
215 810d051f Iustin Pop
                     , iPolicyDiskTemplates = [minBound..maxBound]
216 e8fa4ff6 Iustin Pop
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
217 c22d4dd4 Iustin Pop
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
218 d02f941e Iustin Pop
                     }
219 d02f941e Iustin Pop
220 2180829f Iustin Pop
-- | The dynamic resource specs of a machine (i.e. load or load
221 2180829f Iustin Pop
-- capacity, as opposed to size).
222 2180829f Iustin Pop
data DynUtil = DynUtil
223 ebf38064 Iustin Pop
  { cpuWeight :: Weight -- ^ Standardised CPU usage
224 ebf38064 Iustin Pop
  , memWeight :: Weight -- ^ Standardised memory load
225 ebf38064 Iustin Pop
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
226 ebf38064 Iustin Pop
  , netWeight :: Weight -- ^ Standardised network usage
227 139c0683 Iustin Pop
  } deriving (Show, Eq)
228 2180829f Iustin Pop
229 525bfb36 Iustin Pop
-- | Initial empty utilisation.
230 2180829f Iustin Pop
zeroUtil :: DynUtil
231 2180829f Iustin Pop
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
232 2180829f Iustin Pop
                   , dskWeight = 0, netWeight = 0 }
233 2180829f Iustin Pop
234 525bfb36 Iustin Pop
-- | Base utilisation (used when no actual utilisation data is
235 525bfb36 Iustin Pop
-- supplied).
236 ee9724b9 Iustin Pop
baseUtil :: DynUtil
237 ee9724b9 Iustin Pop
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
238 ee9724b9 Iustin Pop
                   , dskWeight = 1, netWeight = 1 }
239 ee9724b9 Iustin Pop
240 525bfb36 Iustin Pop
-- | Sum two utilisation records.
241 2180829f Iustin Pop
addUtil :: DynUtil -> DynUtil -> DynUtil
242 2180829f Iustin Pop
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
243 ebf38064 Iustin Pop
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
244 2180829f Iustin Pop
245 525bfb36 Iustin Pop
-- | Substracts one utilisation record from another.
246 2180829f Iustin Pop
subUtil :: DynUtil -> DynUtil -> DynUtil
247 2180829f Iustin Pop
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
248 ebf38064 Iustin Pop
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
249 2180829f Iustin Pop
250 66dac8e0 Iustin Pop
-- | The description of an instance placement. It contains the
251 66dac8e0 Iustin Pop
-- instance index, the new primary and secondary node, the move being
252 66dac8e0 Iustin Pop
-- performed and the score of the cluster after the move.
253 66dac8e0 Iustin Pop
type Placement = (Idx, Ndx, Ndx, IMove, Score)
254 92e32d76 Iustin Pop
255 525bfb36 Iustin Pop
-- | An instance move definition.
256 92e32d76 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
257 0c8cef35 Iustin Pop
           | FailoverToAny Ndx       -- ^ Failover to a random node
258 0c8cef35 Iustin Pop
                                     -- (fa:np), for shared storage
259 92e32d76 Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
260 92e32d76 Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
261 92e32d76 Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
262 92e32d76 Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
263 139c0683 Iustin Pop
             deriving (Show)
264 92e32d76 Iustin Pop
265 0e8ae201 Iustin Pop
-- | Formatted solution output for one move (involved nodes and
266 525bfb36 Iustin Pop
-- commands.
267 924f9c16 Iustin Pop
type MoveJob = ([Ndx], Idx, IMove, [String])
268 0e8ae201 Iustin Pop
269 525bfb36 Iustin Pop
-- | Unknown field in table output.
270 82ea2874 Iustin Pop
unknownField :: String
271 82ea2874 Iustin Pop
unknownField = "<unknown field>"
272 82ea2874 Iustin Pop
273 525bfb36 Iustin Pop
-- | A list of command elements.
274 0e8ae201 Iustin Pop
type JobSet = [MoveJob]
275 0e8ae201 Iustin Pop
276 f4c0b8c5 Iustin Pop
-- | Default max disk usage ratio.
277 f4c0b8c5 Iustin Pop
defReservedDiskRatio :: Double
278 f4c0b8c5 Iustin Pop
defReservedDiskRatio = 0
279 f4c0b8c5 Iustin Pop
280 1e3dccc8 Iustin Pop
-- | Base memory unit.
281 1e3dccc8 Iustin Pop
unitMem :: Int
282 1e3dccc8 Iustin Pop
unitMem = 64
283 1e3dccc8 Iustin Pop
284 1e3dccc8 Iustin Pop
-- | Base disk unit.
285 1e3dccc8 Iustin Pop
unitDsk :: Int
286 1e3dccc8 Iustin Pop
unitDsk = 256
287 1e3dccc8 Iustin Pop
288 1e3dccc8 Iustin Pop
-- | Base vcpus unit.
289 1e3dccc8 Iustin Pop
unitCpu :: Int
290 1e3dccc8 Iustin Pop
unitCpu = 1
291 1e3dccc8 Iustin Pop
292 525bfb36 Iustin Pop
-- | Reason for an operation's falure.
293 f2280553 Iustin Pop
data FailMode = FailMem  -- ^ Failed due to not enough RAM
294 f2280553 Iustin Pop
              | FailDisk -- ^ Failed due to not enough disk
295 f2280553 Iustin Pop
              | FailCPU  -- ^ Failed due to not enough CPU capacity
296 f2280553 Iustin Pop
              | FailN1   -- ^ Failed due to not passing N1 checks
297 5f0b9579 Iustin Pop
              | FailTags -- ^ Failed due to tag exclusion
298 139c0683 Iustin Pop
                deriving (Eq, Enum, Bounded, Show)
299 f2280553 Iustin Pop
300 525bfb36 Iustin Pop
-- | List with failure statistics.
301 478df686 Iustin Pop
type FailStats = [(FailMode, Int)]
302 478df686 Iustin Pop
303 525bfb36 Iustin Pop
-- | Either-like data-type customized for our failure modes.
304 a30b473c Iustin Pop
--
305 a30b473c Iustin Pop
-- The failure values for this monad track the specific allocation
306 a30b473c Iustin Pop
-- failures, so this is not a general error-monad (compare with the
307 a30b473c Iustin Pop
-- 'Result' data type). One downside is that this type cannot encode a
308 a8038349 Iustin Pop
-- generic failure mode, hence our way to build a FailMode from string
309 a8038349 Iustin Pop
-- will instead raise an exception.
310 a8038349 Iustin Pop
type OpResult = GenericResult FailMode
311 f2280553 Iustin Pop
312 a8038349 Iustin Pop
-- | 'FromString' instance for 'FailMode' designed to catch unintended
313 a8038349 Iustin Pop
-- use as a general monad.
314 a8038349 Iustin Pop
instance FromString FailMode where
315 a8038349 Iustin Pop
  mkFromString v = error $ "Programming error: OpResult used as generic monad"
316 a8038349 Iustin Pop
                           ++ v
317 f2280553 Iustin Pop
318 a30b473c Iustin Pop
-- | Conversion from 'OpResult' to 'Result'.
319 a30b473c Iustin Pop
opToResult :: OpResult a -> Result a
320 a8038349 Iustin Pop
opToResult (Bad f) = Bad $ show f
321 a8038349 Iustin Pop
opToResult (Ok v) = Ok v
322 a30b473c Iustin Pop
323 9188aeef Iustin Pop
-- | A generic class for items that have updateable names and indices.
324 497e30a1 Iustin Pop
class Element a where
325 ebf38064 Iustin Pop
  -- | Returns the name of the element
326 ebf38064 Iustin Pop
  nameOf  :: a -> String
327 ebf38064 Iustin Pop
  -- | Returns all the known names of the element
328 ebf38064 Iustin Pop
  allNames :: a -> [String]
329 ebf38064 Iustin Pop
  -- | Returns the index of the element
330 ebf38064 Iustin Pop
  idxOf   :: a -> Int
331 ebf38064 Iustin Pop
  -- | Updates the alias of the element
332 ebf38064 Iustin Pop
  setAlias :: a -> String -> a
333 ebf38064 Iustin Pop
  -- | Compute the alias by stripping a given suffix (domain) from
334 ebf38064 Iustin Pop
  -- the name
335 ebf38064 Iustin Pop
  computeAlias :: String -> a -> a
336 ebf38064 Iustin Pop
  computeAlias dom e = setAlias e alias
337 ebf38064 Iustin Pop
    where alias = take (length name - length dom) name
338 ebf38064 Iustin Pop
          name = nameOf e
339 ebf38064 Iustin Pop
  -- | Updates the index of the element
340 ebf38064 Iustin Pop
  setIdx  :: a -> Int -> a
341 1fe412bb Iustin Pop
342 1fe412bb Iustin Pop
-- | The iallocator node-evacuate evac_mode type.
343 e9aaa3c6 Iustin Pop
$(THH.declareSADT "EvacMode"
344 ebf38064 Iustin Pop
       [ ("ChangePrimary",   'C.iallocatorNevacPri)
345 ebf38064 Iustin Pop
       , ("ChangeSecondary", 'C.iallocatorNevacSec)
346 ebf38064 Iustin Pop
       , ("ChangeAll",       'C.iallocatorNevacAll)
347 ebf38064 Iustin Pop
       ])
348 e9aaa3c6 Iustin Pop
$(THH.makeJSONInstance ''EvacMode)