Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Types.hs @ 29a30533

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