Statistics
| Branch: | Tag: | Revision:

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

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