Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 3e77a36c

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