Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 0efada2a

History | View | Annotate | Download (14.5 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 da5f09ef Bernardo Dal Seno
Copyright (C) 2009, 2010, 2011, 2012, 2013 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 c8b199db Thomas Thrainer
  , NetworkID
41 ebf38064 Iustin Pop
  , InstanceStatus(..)
42 ebf38064 Iustin Pop
  , instanceStatusFromRaw
43 ebf38064 Iustin Pop
  , instanceStatusToRaw
44 ebf38064 Iustin Pop
  , RSpec(..)
45 76a20994 Iustin Pop
  , AllocInfo(..)
46 80d7d8a1 Iustin Pop
  , AllocStats
47 ebf38064 Iustin Pop
  , DynUtil(..)
48 ebf38064 Iustin Pop
  , zeroUtil
49 ebf38064 Iustin Pop
  , baseUtil
50 ebf38064 Iustin Pop
  , addUtil
51 ebf38064 Iustin Pop
  , subUtil
52 ebf38064 Iustin Pop
  , defReservedDiskRatio
53 ebf38064 Iustin Pop
  , unitMem
54 ebf38064 Iustin Pop
  , unitCpu
55 ebf38064 Iustin Pop
  , unitDsk
56 fcfc0c2d Bernardo Dal Seno
  , unitSpindle
57 ebf38064 Iustin Pop
  , unknownField
58 ebf38064 Iustin Pop
  , Placement
59 ebf38064 Iustin Pop
  , IMove(..)
60 ebf38064 Iustin Pop
  , DiskTemplate(..)
61 ebf38064 Iustin Pop
  , diskTemplateToRaw
62 ebf38064 Iustin Pop
  , diskTemplateFromRaw
63 b906d7c1 Iustin Pop
  , MirrorType(..)
64 b906d7c1 Iustin Pop
  , templateMirrorType
65 ebf38064 Iustin Pop
  , MoveJob
66 ebf38064 Iustin Pop
  , JobSet
67 ebf38064 Iustin Pop
  , Element(..)
68 ebf38064 Iustin Pop
  , FailMode(..)
69 ebf38064 Iustin Pop
  , FailStats
70 a8038349 Iustin Pop
  , OpResult
71 ebf38064 Iustin Pop
  , opToResult
72 a07343b2 Iustin Pop
  , ISpec(..)
73 8397ffde Jose A. Lopes
  , defMinISpec
74 8397ffde Jose A. Lopes
  , defStdISpec
75 8397ffde Jose A. Lopes
  , maxDisks
76 8397ffde Jose A. Lopes
  , maxNics
77 8397ffde Jose A. Lopes
  , defMaxISpec
78 da5f09ef Bernardo Dal Seno
  , MinMaxISpecs(..)
79 a07343b2 Iustin Pop
  , IPolicy(..)
80 d02f941e Iustin Pop
  , defIPolicy
81 304f9292 Iustin Pop
  , rspecFromISpec
82 3e77a36c Dato Simó
  , AutoRepairType(..)
83 3e77a36c Dato Simó
  , autoRepairTypeToRaw
84 3e77a36c Dato Simó
  , autoRepairTypeFromRaw
85 3e77a36c Dato Simó
  , AutoRepairResult(..)
86 3e77a36c Dato Simó
  , autoRepairResultToRaw
87 3e77a36c Dato Simó
  , autoRepairResultFromRaw
88 7ec2f76b Dato Simó
  , AutoRepairPolicy(..)
89 7ec2f76b Dato Simó
  , AutoRepairSuspendTime(..)
90 7ec2f76b Dato Simó
  , AutoRepairData(..)
91 7ec2f76b Dato Simó
  , AutoRepairStatus(..)
92 ebf38064 Iustin Pop
  ) where
93 e4c5beaf Iustin Pop
94 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
95 7ec2f76b Dato Simó
import System.Time (ClockTime)
96 2d0ca2c5 Iustin Pop
97 8397ffde Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
98 e9aaa3c6 Iustin Pop
import qualified Ganeti.THH as THH
99 0c37d1e4 Iustin Pop
import Ganeti.BasicTypes
100 5e9deac0 Iustin Pop
import Ganeti.Types
101 2e5eb96a Iustin Pop
102 9188aeef Iustin Pop
-- | The instance index type.
103 608efcce Iustin Pop
type Idx = Int
104 608efcce Iustin Pop
105 9188aeef Iustin Pop
-- | The node index type.
106 608efcce Iustin Pop
type Ndx = Int
107 608efcce Iustin Pop
108 0dc1bf87 Iustin Pop
-- | The group index type.
109 0dc1bf87 Iustin Pop
type Gdx = Int
110 0dc1bf87 Iustin Pop
111 9188aeef Iustin Pop
-- | The type used to hold name-to-idx mappings.
112 2d0ca2c5 Iustin Pop
type NameAssoc = M.Map String Int
113 e4c5beaf Iustin Pop
114 92e32d76 Iustin Pop
-- | A separate name for the cluster score type.
115 92e32d76 Iustin Pop
type Score = Double
116 92e32d76 Iustin Pop
117 2180829f Iustin Pop
-- | A separate name for a weight metric.
118 2180829f Iustin Pop
type Weight = Double
119 2180829f Iustin Pop
120 0dc1bf87 Iustin Pop
-- | The Group UUID type.
121 c4d98278 Iustin Pop
type GroupID = String
122 c4d98278 Iustin Pop
123 f3f76ccc Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
124 f3f76ccc Iustin Pop
defaultGroupID :: GroupID
125 f3f76ccc Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
126 f3f76ccc Iustin Pop
127 b906d7c1 Iustin Pop
-- | Mirroring type.
128 b906d7c1 Iustin Pop
data MirrorType = MirrorNone     -- ^ No mirroring/movability
129 b906d7c1 Iustin Pop
                | MirrorInternal -- ^ DRBD-type mirroring
130 b906d7c1 Iustin Pop
                | MirrorExternal -- ^ Shared-storage type mirroring
131 139c0683 Iustin Pop
                  deriving (Eq, Show)
132 b906d7c1 Iustin Pop
133 b906d7c1 Iustin Pop
-- | Correspondence between disk template and mirror type.
134 b906d7c1 Iustin Pop
templateMirrorType :: DiskTemplate -> MirrorType
135 b906d7c1 Iustin Pop
templateMirrorType DTDiskless   = MirrorExternal
136 b906d7c1 Iustin Pop
templateMirrorType DTFile       = MirrorNone
137 b906d7c1 Iustin Pop
templateMirrorType DTSharedFile = MirrorExternal
138 b906d7c1 Iustin Pop
templateMirrorType DTPlain      = MirrorNone
139 b906d7c1 Iustin Pop
templateMirrorType DTBlock      = MirrorExternal
140 b906d7c1 Iustin Pop
templateMirrorType DTDrbd8      = MirrorInternal
141 b906d7c1 Iustin Pop
templateMirrorType DTRbd        = MirrorExternal
142 277a2ec9 Constantinos Venetsanopoulos
templateMirrorType DTExt        = MirrorExternal
143 8106dd64 Santi Raffa
templateMirrorType DTGluster    = MirrorExternal
144 b906d7c1 Iustin Pop
145 1f9066c0 Iustin Pop
-- | The resource spec type.
146 1f9066c0 Iustin Pop
data RSpec = RSpec
147 ebf38064 Iustin Pop
  { rspecCpu  :: Int  -- ^ Requested VCPUs
148 ebf38064 Iustin Pop
  , rspecMem  :: Int  -- ^ Requested memory
149 ebf38064 Iustin Pop
  , rspecDsk  :: Int  -- ^ Requested disk
150 914c6df4 Bernardo Dal Seno
  , rspecSpn  :: Int  -- ^ Requested spindles
151 139c0683 Iustin Pop
  } deriving (Show, Eq)
152 1f9066c0 Iustin Pop
153 76a20994 Iustin Pop
-- | Allocation stats type. This is used instead of 'RSpec' (which was
154 76a20994 Iustin Pop
-- used at first), because we need to track more stats. The actual
155 76a20994 Iustin Pop
-- data can refer either to allocated, or available, etc. values
156 76a20994 Iustin Pop
-- depending on the context. See also
157 76a20994 Iustin Pop
-- 'Cluster.computeAllocationDelta'.
158 76a20994 Iustin Pop
data AllocInfo = AllocInfo
159 76a20994 Iustin Pop
  { allocInfoVCpus :: Int    -- ^ VCPUs
160 76a20994 Iustin Pop
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
161 76a20994 Iustin Pop
  , allocInfoMem   :: Int    -- ^ Memory
162 76a20994 Iustin Pop
  , allocInfoDisk  :: Int    -- ^ Disk
163 0cc3d742 Bernardo Dal Seno
  , allocInfoSpn   :: Int    -- ^ Spindles
164 139c0683 Iustin Pop
  } deriving (Show, Eq)
165 a07343b2 Iustin Pop
166 80d7d8a1 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
167 80d7d8a1 Iustin Pop
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
168 80d7d8a1 Iustin Pop
169 c8b199db Thomas Thrainer
-- | The network UUID type.
170 c8b199db Thomas Thrainer
type NetworkID = String
171 c8b199db Thomas Thrainer
172 a07343b2 Iustin Pop
-- | Instance specification type.
173 a07343b2 Iustin Pop
$(THH.buildObject "ISpec" "iSpec"
174 8397ffde Jose A. Lopes
  [ THH.renameField "MemorySize" $
175 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecMemSize    [t| Int |]
176 8397ffde Jose A. Lopes
  , THH.renameField "CpuCount"   $
177 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecCpuCount   [t| Int |]
178 8397ffde Jose A. Lopes
  , THH.renameField "DiskSize"   $
179 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecDiskSize   [t| Int |]
180 8397ffde Jose A. Lopes
  , THH.renameField "DiskCount"  $
181 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecDiskCount  [t| Int |]
182 8397ffde Jose A. Lopes
  , THH.renameField "NicCount"   $
183 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecNicCount   [t| Int |]
184 8397ffde Jose A. Lopes
  , THH.renameField "SpindleUse" $
185 8397ffde Jose A. Lopes
    THH.simpleField ConstantUtils.ispecSpindleUse [t| Int |]
186 a07343b2 Iustin Pop
  ])
187 a07343b2 Iustin Pop
188 d02f941e Iustin Pop
-- | The default minimum ispec.
189 d02f941e Iustin Pop
defMinISpec :: ISpec
190 8397ffde Jose A. Lopes
defMinISpec = ISpec { iSpecMemorySize = 128
191 8397ffde Jose A. Lopes
                    , iSpecCpuCount   = 1
192 8397ffde Jose A. Lopes
                    , iSpecDiskCount  = 1
193 8397ffde Jose A. Lopes
                    , iSpecDiskSize   = 1024
194 8397ffde Jose A. Lopes
                    , iSpecNicCount   = 1
195 8397ffde Jose A. Lopes
                    , iSpecSpindleUse = 1
196 d02f941e Iustin Pop
                    }
197 d02f941e Iustin Pop
198 d02f941e Iustin Pop
-- | The default standard ispec.
199 d02f941e Iustin Pop
defStdISpec :: ISpec
200 8397ffde Jose A. Lopes
defStdISpec = ISpec { iSpecMemorySize = 128
201 8397ffde Jose A. Lopes
                    , iSpecCpuCount   = 1
202 8397ffde Jose A. Lopes
                    , iSpecDiskCount  = 1
203 8397ffde Jose A. Lopes
                    , iSpecDiskSize   = 1024
204 8397ffde Jose A. Lopes
                    , iSpecNicCount   = 1
205 8397ffde Jose A. Lopes
                    , iSpecSpindleUse = 1
206 d02f941e Iustin Pop
                    }
207 d02f941e Iustin Pop
208 8397ffde Jose A. Lopes
maxDisks :: Int
209 8397ffde Jose A. Lopes
maxDisks = 16
210 8397ffde Jose A. Lopes
211 8397ffde Jose A. Lopes
maxNics :: Int
212 8397ffde Jose A. Lopes
maxNics = 8
213 8397ffde Jose A. Lopes
214 d02f941e Iustin Pop
-- | The default max ispec.
215 d02f941e Iustin Pop
defMaxISpec :: ISpec
216 8397ffde Jose A. Lopes
defMaxISpec = ISpec { iSpecMemorySize = 32768
217 8397ffde Jose A. Lopes
                    , iSpecCpuCount   = 8
218 8397ffde Jose A. Lopes
                    , iSpecDiskCount  = maxDisks
219 8397ffde Jose A. Lopes
                    , iSpecDiskSize   = 1024 * 1024
220 8397ffde Jose A. Lopes
                    , iSpecNicCount   = maxNics
221 8397ffde Jose A. Lopes
                    , iSpecSpindleUse = 12
222 d02f941e Iustin Pop
                    }
223 d02f941e Iustin Pop
224 da5f09ef Bernardo Dal Seno
-- | Minimum and maximum instance specs type.
225 da5f09ef Bernardo Dal Seno
$(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
226 da5f09ef Bernardo Dal Seno
  [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
227 da5f09ef Bernardo Dal Seno
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
228 da5f09ef Bernardo Dal Seno
  ])
229 da5f09ef Bernardo Dal Seno
230 da5f09ef Bernardo Dal Seno
-- | Defult minimum and maximum instance specs.
231 41044e04 Bernardo Dal Seno
defMinMaxISpecs :: [MinMaxISpecs]
232 41044e04 Bernardo Dal Seno
defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
233 41044e04 Bernardo Dal Seno
                                , minMaxISpecsMaxSpec = defMaxISpec
234 41044e04 Bernardo Dal Seno
                                }]
235 da5f09ef Bernardo Dal Seno
236 a07343b2 Iustin Pop
-- | Instance policy type.
237 a07343b2 Iustin Pop
$(THH.buildObject "IPolicy" "iPolicy"
238 da5f09ef Bernardo Dal Seno
  [ THH.renameField "MinMaxISpecs" $
239 8397ffde Jose A. Lopes
      THH.simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
240 8397ffde Jose A. Lopes
  , THH.renameField "StdSpec" $
241 8397ffde Jose A. Lopes
      THH.simpleField ConstantUtils.ispecsStd [t| ISpec |]
242 fc42a408 Iustin Pop
  , THH.renameField "DiskTemplates" $
243 8397ffde Jose A. Lopes
      THH.simpleField ConstantUtils.ipolicyDts [t| [DiskTemplate] |]
244 e8fa4ff6 Iustin Pop
  , THH.renameField "VcpuRatio" $
245 8397ffde Jose A. Lopes
      THH.simpleField ConstantUtils.ipolicyVcpuRatio [t| Double |]
246 c22d4dd4 Iustin Pop
  , THH.renameField "SpindleRatio" $
247 8397ffde Jose A. Lopes
      THH.simpleField ConstantUtils.ipolicySpindleRatio [t| Double |]
248 a07343b2 Iustin Pop
  ])
249 a07343b2 Iustin Pop
250 304f9292 Iustin Pop
-- | Converts an ISpec type to a RSpec one.
251 304f9292 Iustin Pop
rspecFromISpec :: ISpec -> RSpec
252 304f9292 Iustin Pop
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
253 304f9292 Iustin Pop
                             , rspecMem = iSpecMemorySize ispec
254 304f9292 Iustin Pop
                             , rspecDsk = iSpecDiskSize ispec
255 914c6df4 Bernardo Dal Seno
                             , rspecSpn = iSpecSpindleUse ispec
256 304f9292 Iustin Pop
                             }
257 304f9292 Iustin Pop
258 d02f941e Iustin Pop
-- | The default instance policy.
259 d02f941e Iustin Pop
defIPolicy :: IPolicy
260 8397ffde Jose A. Lopes
defIPolicy =
261 8397ffde Jose A. Lopes
  IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
262 8397ffde Jose A. Lopes
          , iPolicyStdSpec = defStdISpec
263 8397ffde Jose A. Lopes
          -- hardcoding here since Constants.hs exports the
264 8397ffde Jose A. Lopes
          -- string values, not the actual type; and in
265 8397ffde Jose A. Lopes
          -- htools, we are mostly looking at DRBD
266 8397ffde Jose A. Lopes
          , iPolicyDiskTemplates = [minBound..maxBound]
267 8397ffde Jose A. Lopes
          , iPolicyVcpuRatio = ConstantUtils.ipolicyDefaultsVcpuRatio
268 8397ffde Jose A. Lopes
          , iPolicySpindleRatio = ConstantUtils.ipolicyDefaultsSpindleRatio
269 8397ffde Jose A. Lopes
          }
270 d02f941e Iustin Pop
271 2180829f Iustin Pop
-- | The dynamic resource specs of a machine (i.e. load or load
272 2180829f Iustin Pop
-- capacity, as opposed to size).
273 2180829f Iustin Pop
data DynUtil = DynUtil
274 ebf38064 Iustin Pop
  { cpuWeight :: Weight -- ^ Standardised CPU usage
275 ebf38064 Iustin Pop
  , memWeight :: Weight -- ^ Standardised memory load
276 ebf38064 Iustin Pop
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
277 ebf38064 Iustin Pop
  , netWeight :: Weight -- ^ Standardised network usage
278 139c0683 Iustin Pop
  } deriving (Show, Eq)
279 2180829f Iustin Pop
280 525bfb36 Iustin Pop
-- | Initial empty utilisation.
281 2180829f Iustin Pop
zeroUtil :: DynUtil
282 2180829f Iustin Pop
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
283 2180829f Iustin Pop
                   , dskWeight = 0, netWeight = 0 }
284 2180829f Iustin Pop
285 525bfb36 Iustin Pop
-- | Base utilisation (used when no actual utilisation data is
286 525bfb36 Iustin Pop
-- supplied).
287 ee9724b9 Iustin Pop
baseUtil :: DynUtil
288 ee9724b9 Iustin Pop
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
289 ee9724b9 Iustin Pop
                   , dskWeight = 1, netWeight = 1 }
290 ee9724b9 Iustin Pop
291 525bfb36 Iustin Pop
-- | Sum two utilisation records.
292 2180829f Iustin Pop
addUtil :: DynUtil -> DynUtil -> DynUtil
293 2180829f Iustin Pop
addUtil (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 525bfb36 Iustin Pop
-- | Substracts one utilisation record from another.
297 2180829f Iustin Pop
subUtil :: DynUtil -> DynUtil -> DynUtil
298 2180829f Iustin Pop
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
299 ebf38064 Iustin Pop
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
300 2180829f Iustin Pop
301 66dac8e0 Iustin Pop
-- | The description of an instance placement. It contains the
302 66dac8e0 Iustin Pop
-- instance index, the new primary and secondary node, the move being
303 66dac8e0 Iustin Pop
-- performed and the score of the cluster after the move.
304 66dac8e0 Iustin Pop
type Placement = (Idx, Ndx, Ndx, IMove, Score)
305 92e32d76 Iustin Pop
306 525bfb36 Iustin Pop
-- | An instance move definition.
307 92e32d76 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
308 0c8cef35 Iustin Pop
           | FailoverToAny Ndx       -- ^ Failover to a random node
309 0c8cef35 Iustin Pop
                                     -- (fa:np), for shared storage
310 92e32d76 Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
311 92e32d76 Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
312 92e32d76 Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
313 92e32d76 Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
314 139c0683 Iustin Pop
             deriving (Show)
315 92e32d76 Iustin Pop
316 0e8ae201 Iustin Pop
-- | Formatted solution output for one move (involved nodes and
317 525bfb36 Iustin Pop
-- commands.
318 924f9c16 Iustin Pop
type MoveJob = ([Ndx], Idx, IMove, [String])
319 0e8ae201 Iustin Pop
320 525bfb36 Iustin Pop
-- | Unknown field in table output.
321 82ea2874 Iustin Pop
unknownField :: String
322 82ea2874 Iustin Pop
unknownField = "<unknown field>"
323 82ea2874 Iustin Pop
324 525bfb36 Iustin Pop
-- | A list of command elements.
325 0e8ae201 Iustin Pop
type JobSet = [MoveJob]
326 0e8ae201 Iustin Pop
327 f4c0b8c5 Iustin Pop
-- | Default max disk usage ratio.
328 f4c0b8c5 Iustin Pop
defReservedDiskRatio :: Double
329 f4c0b8c5 Iustin Pop
defReservedDiskRatio = 0
330 f4c0b8c5 Iustin Pop
331 1e3dccc8 Iustin Pop
-- | Base memory unit.
332 1e3dccc8 Iustin Pop
unitMem :: Int
333 1e3dccc8 Iustin Pop
unitMem = 64
334 1e3dccc8 Iustin Pop
335 1e3dccc8 Iustin Pop
-- | Base disk unit.
336 1e3dccc8 Iustin Pop
unitDsk :: Int
337 1e3dccc8 Iustin Pop
unitDsk = 256
338 1e3dccc8 Iustin Pop
339 1e3dccc8 Iustin Pop
-- | Base vcpus unit.
340 1e3dccc8 Iustin Pop
unitCpu :: Int
341 1e3dccc8 Iustin Pop
unitCpu = 1
342 1e3dccc8 Iustin Pop
343 fcfc0c2d Bernardo Dal Seno
-- | Base spindles unit.
344 fcfc0c2d Bernardo Dal Seno
unitSpindle :: Int
345 fcfc0c2d Bernardo Dal Seno
unitSpindle = 1
346 fcfc0c2d Bernardo Dal Seno
347 525bfb36 Iustin Pop
-- | Reason for an operation's falure.
348 f2280553 Iustin Pop
data FailMode = FailMem  -- ^ Failed due to not enough RAM
349 f2280553 Iustin Pop
              | FailDisk -- ^ Failed due to not enough disk
350 f2280553 Iustin Pop
              | FailCPU  -- ^ Failed due to not enough CPU capacity
351 f2280553 Iustin Pop
              | FailN1   -- ^ Failed due to not passing N1 checks
352 5f0b9579 Iustin Pop
              | FailTags -- ^ Failed due to tag exclusion
353 6ef49eef Bernardo Dal Seno
              | FailDiskCount -- ^ Failed due to wrong number of disks
354 6ef49eef Bernardo Dal Seno
              | FailSpindles -- ^ Failed due to wrong/missing spindles
355 6ef49eef Bernardo Dal Seno
              | FailInternal -- ^ Internal error
356 139c0683 Iustin Pop
                deriving (Eq, Enum, Bounded, Show)
357 f2280553 Iustin Pop
358 525bfb36 Iustin Pop
-- | List with failure statistics.
359 478df686 Iustin Pop
type FailStats = [(FailMode, Int)]
360 478df686 Iustin Pop
361 525bfb36 Iustin Pop
-- | Either-like data-type customized for our failure modes.
362 a30b473c Iustin Pop
--
363 a30b473c Iustin Pop
-- The failure values for this monad track the specific allocation
364 a30b473c Iustin Pop
-- failures, so this is not a general error-monad (compare with the
365 a30b473c Iustin Pop
-- 'Result' data type). One downside is that this type cannot encode a
366 a8038349 Iustin Pop
-- generic failure mode, hence our way to build a FailMode from string
367 a8038349 Iustin Pop
-- will instead raise an exception.
368 a8038349 Iustin Pop
type OpResult = GenericResult FailMode
369 f2280553 Iustin Pop
370 a87a017b Petr Pudlak
-- | 'Error' instance for 'FailMode' designed to catch unintended
371 a8038349 Iustin Pop
-- use as a general monad.
372 a87a017b Petr Pudlak
instance Error FailMode where
373 a87a017b Petr Pudlak
  strMsg v = error $ "Programming error: OpResult used as generic monad" ++ v
374 f2280553 Iustin Pop
375 a30b473c Iustin Pop
-- | Conversion from 'OpResult' to 'Result'.
376 a30b473c Iustin Pop
opToResult :: OpResult a -> Result a
377 a8038349 Iustin Pop
opToResult (Bad f) = Bad $ show f
378 a8038349 Iustin Pop
opToResult (Ok v) = Ok v
379 a30b473c Iustin Pop
380 9188aeef Iustin Pop
-- | A generic class for items that have updateable names and indices.
381 497e30a1 Iustin Pop
class Element a where
382 ebf38064 Iustin Pop
  -- | Returns the name of the element
383 ebf38064 Iustin Pop
  nameOf  :: a -> String
384 ebf38064 Iustin Pop
  -- | Returns all the known names of the element
385 ebf38064 Iustin Pop
  allNames :: a -> [String]
386 ebf38064 Iustin Pop
  -- | Returns the index of the element
387 ebf38064 Iustin Pop
  idxOf   :: a -> Int
388 ebf38064 Iustin Pop
  -- | Updates the alias of the element
389 ebf38064 Iustin Pop
  setAlias :: a -> String -> a
390 ebf38064 Iustin Pop
  -- | Compute the alias by stripping a given suffix (domain) from
391 ebf38064 Iustin Pop
  -- the name
392 ebf38064 Iustin Pop
  computeAlias :: String -> a -> a
393 ebf38064 Iustin Pop
  computeAlias dom e = setAlias e alias
394 ebf38064 Iustin Pop
    where alias = take (length name - length dom) name
395 ebf38064 Iustin Pop
          name = nameOf e
396 ebf38064 Iustin Pop
  -- | Updates the index of the element
397 ebf38064 Iustin Pop
  setIdx  :: a -> Int -> a
398 1fe412bb Iustin Pop
399 3e77a36c Dato Simó
-- | The repair modes for the auto-repair tool.
400 8397ffde Jose A. Lopes
$(THH.declareLADT ''String "AutoRepairType"
401 8397ffde Jose A. Lopes
  -- Order is important here: from least destructive to most.
402 8397ffde Jose A. Lopes
  [ ("ArFixStorage", "fix-storage")
403 8397ffde Jose A. Lopes
  , ("ArMigrate",    "migrate")
404 8397ffde Jose A. Lopes
  , ("ArFailover",   "failover")
405 8397ffde Jose A. Lopes
  , ("ArReinstall",  "reinstall")
406 8397ffde Jose A. Lopes
  ])
407 3e77a36c Dato Simó
408 3e77a36c Dato Simó
-- | The possible auto-repair results.
409 8397ffde Jose A. Lopes
$(THH.declareLADT ''String "AutoRepairResult"
410 8397ffde Jose A. Lopes
  -- Order is important here: higher results take precedence when an object
411 8397ffde Jose A. Lopes
  -- has several result annotations attached.
412 8397ffde Jose A. Lopes
  [ ("ArEnoperm", "enoperm")
413 8397ffde Jose A. Lopes
  , ("ArSuccess", "success")
414 8397ffde Jose A. Lopes
  , ("ArFailure", "failure")
415 8397ffde Jose A. Lopes
  ])
416 7ec2f76b Dato Simó
417 7ec2f76b Dato Simó
-- | The possible auto-repair policy for a given instance.
418 7ec2f76b Dato Simó
data AutoRepairPolicy
419 7ec2f76b Dato Simó
  = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
420 7ec2f76b Dato Simó
  | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
421 7ec2f76b Dato Simó
  | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
422 7ec2f76b Dato Simó
  deriving (Eq, Show)
423 7ec2f76b Dato Simó
424 7ec2f76b Dato Simó
-- | The suspend timeout for 'ArSuspended'.
425 7ec2f76b Dato Simó
data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
426 7ec2f76b Dato Simó
                           | Until ClockTime -- ^ Suspended up to a certain time
427 7ec2f76b Dato Simó
                           deriving (Eq, Show)
428 7ec2f76b Dato Simó
429 7ec2f76b Dato Simó
-- | The possible auto-repair states for any given instance.
430 7ec2f76b Dato Simó
data AutoRepairStatus
431 de9d75c8 Dato Simó
  = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
432 7ec2f76b Dato Simó
  | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
433 7ec2f76b Dato Simó
  | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
434 7ec2f76b Dato Simó
  | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
435 de9d75c8 Dato Simó
  deriving (Eq, Show)
436 7ec2f76b Dato Simó
437 7ec2f76b Dato Simó
-- | The data accompanying a repair operation (future, pending, or failed).
438 7ec2f76b Dato Simó
data AutoRepairData = AutoRepairData { arType :: AutoRepairType
439 7ec2f76b Dato Simó
                                     , arUuid :: String
440 7ec2f76b Dato Simó
                                     , arTime :: ClockTime
441 7ec2f76b Dato Simó
                                     , arJobs :: [JobId]
442 7ec2f76b Dato Simó
                                     , arResult :: Maybe AutoRepairResult
443 de9d75c8 Dato Simó
                                     , arTag :: String
444 7ec2f76b Dato Simó
                                     }
445 de9d75c8 Dato Simó
                    deriving (Eq, Show)