Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 34ad1d7c

History | View | Annotate | Download (15.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 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 ebf38064 Iustin Pop
  , EvacMode(..)
73 a07343b2 Iustin Pop
  , ISpec(..)
74 da5f09ef Bernardo Dal Seno
  , MinMaxISpecs(..)
75 a07343b2 Iustin Pop
  , IPolicy(..)
76 d02f941e Iustin Pop
  , defIPolicy
77 304f9292 Iustin Pop
  , rspecFromISpec
78 3e77a36c Dato Simó
  , AutoRepairType(..)
79 3e77a36c Dato Simó
  , autoRepairTypeToRaw
80 3e77a36c Dato Simó
  , autoRepairTypeFromRaw
81 3e77a36c Dato Simó
  , AutoRepairResult(..)
82 3e77a36c Dato Simó
  , autoRepairResultToRaw
83 3e77a36c Dato Simó
  , autoRepairResultFromRaw
84 7ec2f76b Dato Simó
  , AutoRepairPolicy(..)
85 7ec2f76b Dato Simó
  , AutoRepairSuspendTime(..)
86 7ec2f76b Dato Simó
  , AutoRepairData(..)
87 7ec2f76b Dato Simó
  , AutoRepairStatus(..)
88 ebf38064 Iustin Pop
  ) where
89 e4c5beaf Iustin Pop
90 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
91 7ec2f76b Dato Simó
import System.Time (ClockTime)
92 2d0ca2c5 Iustin Pop
93 2e5eb96a Iustin Pop
import qualified Ganeti.Constants as C
94 e9aaa3c6 Iustin Pop
import qualified Ganeti.THH as THH
95 0c37d1e4 Iustin Pop
import Ganeti.BasicTypes
96 5e9deac0 Iustin Pop
import Ganeti.Types
97 2e5eb96a Iustin Pop
98 9188aeef Iustin Pop
-- | The instance index type.
99 608efcce Iustin Pop
type Idx = Int
100 608efcce Iustin Pop
101 9188aeef Iustin Pop
-- | The node index type.
102 608efcce Iustin Pop
type Ndx = Int
103 608efcce Iustin Pop
104 0dc1bf87 Iustin Pop
-- | The group index type.
105 0dc1bf87 Iustin Pop
type Gdx = Int
106 0dc1bf87 Iustin Pop
107 9188aeef Iustin Pop
-- | The type used to hold name-to-idx mappings.
108 2d0ca2c5 Iustin Pop
type NameAssoc = M.Map String Int
109 e4c5beaf Iustin Pop
110 92e32d76 Iustin Pop
-- | A separate name for the cluster score type.
111 92e32d76 Iustin Pop
type Score = Double
112 92e32d76 Iustin Pop
113 2180829f Iustin Pop
-- | A separate name for a weight metric.
114 2180829f Iustin Pop
type Weight = Double
115 2180829f Iustin Pop
116 0dc1bf87 Iustin Pop
-- | The Group UUID type.
117 c4d98278 Iustin Pop
type GroupID = String
118 c4d98278 Iustin Pop
119 f3f76ccc Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
120 f3f76ccc Iustin Pop
defaultGroupID :: GroupID
121 f3f76ccc Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
122 f3f76ccc Iustin Pop
123 b906d7c1 Iustin Pop
-- | Mirroring type.
124 b906d7c1 Iustin Pop
data MirrorType = MirrorNone     -- ^ No mirroring/movability
125 b906d7c1 Iustin Pop
                | MirrorInternal -- ^ DRBD-type mirroring
126 b906d7c1 Iustin Pop
                | MirrorExternal -- ^ Shared-storage type mirroring
127 139c0683 Iustin Pop
                  deriving (Eq, Show)
128 b906d7c1 Iustin Pop
129 b906d7c1 Iustin Pop
-- | Correspondence between disk template and mirror type.
130 b906d7c1 Iustin Pop
templateMirrorType :: DiskTemplate -> MirrorType
131 b906d7c1 Iustin Pop
templateMirrorType DTDiskless   = MirrorExternal
132 b906d7c1 Iustin Pop
templateMirrorType DTFile       = MirrorNone
133 b906d7c1 Iustin Pop
templateMirrorType DTSharedFile = MirrorExternal
134 b906d7c1 Iustin Pop
templateMirrorType DTPlain      = MirrorNone
135 b906d7c1 Iustin Pop
templateMirrorType DTBlock      = MirrorExternal
136 b906d7c1 Iustin Pop
templateMirrorType DTDrbd8      = MirrorInternal
137 b906d7c1 Iustin Pop
templateMirrorType DTRbd        = MirrorExternal
138 277a2ec9 Constantinos Venetsanopoulos
templateMirrorType DTExt        = MirrorExternal
139 b906d7c1 Iustin Pop
140 1f9066c0 Iustin Pop
-- | The resource spec type.
141 1f9066c0 Iustin Pop
data RSpec = RSpec
142 ebf38064 Iustin Pop
  { rspecCpu  :: Int  -- ^ Requested VCPUs
143 ebf38064 Iustin Pop
  , rspecMem  :: Int  -- ^ Requested memory
144 ebf38064 Iustin Pop
  , rspecDsk  :: Int  -- ^ Requested disk
145 914c6df4 Bernardo Dal Seno
  , rspecSpn  :: Int  -- ^ Requested spindles
146 139c0683 Iustin Pop
  } deriving (Show, Eq)
147 1f9066c0 Iustin Pop
148 76a20994 Iustin Pop
-- | Allocation stats type. This is used instead of 'RSpec' (which was
149 76a20994 Iustin Pop
-- used at first), because we need to track more stats. The actual
150 76a20994 Iustin Pop
-- data can refer either to allocated, or available, etc. values
151 76a20994 Iustin Pop
-- depending on the context. See also
152 76a20994 Iustin Pop
-- 'Cluster.computeAllocationDelta'.
153 76a20994 Iustin Pop
data AllocInfo = AllocInfo
154 76a20994 Iustin Pop
  { allocInfoVCpus :: Int    -- ^ VCPUs
155 76a20994 Iustin Pop
  , allocInfoNCpus :: Double -- ^ Normalised CPUs
156 76a20994 Iustin Pop
  , allocInfoMem   :: Int    -- ^ Memory
157 76a20994 Iustin Pop
  , allocInfoDisk  :: Int    -- ^ Disk
158 0cc3d742 Bernardo Dal Seno
  , allocInfoSpn   :: Int    -- ^ Spindles
159 139c0683 Iustin Pop
  } deriving (Show, Eq)
160 a07343b2 Iustin Pop
161 80d7d8a1 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
162 80d7d8a1 Iustin Pop
type AllocStats = (AllocInfo, AllocInfo, AllocInfo)
163 80d7d8a1 Iustin Pop
164 c8b199db Thomas Thrainer
-- | The network UUID type.
165 c8b199db Thomas Thrainer
type NetworkID = String
166 c8b199db Thomas Thrainer
167 a07343b2 Iustin Pop
-- | Instance specification type.
168 a07343b2 Iustin Pop
$(THH.buildObject "ISpec" "iSpec"
169 9cda4d6a Iustin Pop
  [ THH.renameField "MemorySize" $ THH.simpleField C.ispecMemSize    [t| Int |]
170 9cda4d6a Iustin Pop
  , THH.renameField "CpuCount"   $ THH.simpleField C.ispecCpuCount   [t| Int |]
171 9cda4d6a Iustin Pop
  , THH.renameField "DiskSize"   $ THH.simpleField C.ispecDiskSize   [t| Int |]
172 9cda4d6a Iustin Pop
  , THH.renameField "DiskCount"  $ THH.simpleField C.ispecDiskCount  [t| Int |]
173 9cda4d6a Iustin Pop
  , THH.renameField "NicCount"   $ THH.simpleField C.ispecNicCount   [t| Int |]
174 9cda4d6a Iustin Pop
  , THH.renameField "SpindleUse" $ THH.simpleField C.ispecSpindleUse [t| Int |]
175 a07343b2 Iustin Pop
  ])
176 a07343b2 Iustin Pop
177 d02f941e Iustin Pop
-- | The default minimum ispec.
178 d02f941e Iustin Pop
defMinISpec :: ISpec
179 41044e04 Bernardo Dal Seno
defMinISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMinMemorySize
180 41044e04 Bernardo Dal Seno
                    , iSpecCpuCount   = C.ispecsMinmaxDefaultsMinCpuCount
181 41044e04 Bernardo Dal Seno
                    , iSpecDiskSize   = C.ispecsMinmaxDefaultsMinDiskSize
182 41044e04 Bernardo Dal Seno
                    , iSpecDiskCount  = C.ispecsMinmaxDefaultsMinDiskCount
183 41044e04 Bernardo Dal Seno
                    , iSpecNicCount   = C.ispecsMinmaxDefaultsMinNicCount
184 41044e04 Bernardo Dal Seno
                    , iSpecSpindleUse = C.ispecsMinmaxDefaultsMinSpindleUse
185 d02f941e Iustin Pop
                    }
186 d02f941e Iustin Pop
187 d02f941e Iustin Pop
-- | The default standard ispec.
188 d02f941e Iustin Pop
defStdISpec :: ISpec
189 d02f941e Iustin Pop
defStdISpec = ISpec { iSpecMemorySize = C.ipolicyDefaultsStdMemorySize
190 d02f941e Iustin Pop
                    , iSpecCpuCount   = C.ipolicyDefaultsStdCpuCount
191 d02f941e Iustin Pop
                    , iSpecDiskSize   = C.ipolicyDefaultsStdDiskSize
192 d02f941e Iustin Pop
                    , iSpecDiskCount  = C.ipolicyDefaultsStdDiskCount
193 d02f941e Iustin Pop
                    , iSpecNicCount   = C.ipolicyDefaultsStdNicCount
194 d953a965 René Nussbaumer
                    , iSpecSpindleUse = C.ipolicyDefaultsStdSpindleUse
195 d02f941e Iustin Pop
                    }
196 d02f941e Iustin Pop
197 d02f941e Iustin Pop
-- | The default max ispec.
198 d02f941e Iustin Pop
defMaxISpec :: ISpec
199 41044e04 Bernardo Dal Seno
defMaxISpec = ISpec { iSpecMemorySize = C.ispecsMinmaxDefaultsMaxMemorySize
200 41044e04 Bernardo Dal Seno
                    , iSpecCpuCount   = C.ispecsMinmaxDefaultsMaxCpuCount
201 41044e04 Bernardo Dal Seno
                    , iSpecDiskSize   = C.ispecsMinmaxDefaultsMaxDiskSize
202 41044e04 Bernardo Dal Seno
                    , iSpecDiskCount  = C.ispecsMinmaxDefaultsMaxDiskCount
203 41044e04 Bernardo Dal Seno
                    , iSpecNicCount   = C.ispecsMinmaxDefaultsMaxNicCount
204 41044e04 Bernardo Dal Seno
                    , iSpecSpindleUse = C.ispecsMinmaxDefaultsMaxSpindleUse
205 d02f941e Iustin Pop
                    }
206 d02f941e Iustin Pop
207 da5f09ef Bernardo Dal Seno
-- | Minimum and maximum instance specs type.
208 da5f09ef Bernardo Dal Seno
$(THH.buildObject "MinMaxISpecs" "minMaxISpecs"
209 da5f09ef Bernardo Dal Seno
  [ THH.renameField "MinSpec" $ THH.simpleField "min" [t| ISpec |]
210 da5f09ef Bernardo Dal Seno
  , THH.renameField "MaxSpec" $ THH.simpleField "max" [t| ISpec |]
211 da5f09ef Bernardo Dal Seno
  ])
212 da5f09ef Bernardo Dal Seno
213 da5f09ef Bernardo Dal Seno
-- | Defult minimum and maximum instance specs.
214 41044e04 Bernardo Dal Seno
defMinMaxISpecs :: [MinMaxISpecs]
215 41044e04 Bernardo Dal Seno
defMinMaxISpecs = [MinMaxISpecs { minMaxISpecsMinSpec = defMinISpec
216 41044e04 Bernardo Dal Seno
                                , minMaxISpecsMaxSpec = defMaxISpec
217 41044e04 Bernardo Dal Seno
                                }]
218 da5f09ef Bernardo Dal Seno
219 a07343b2 Iustin Pop
-- | Instance policy type.
220 a07343b2 Iustin Pop
$(THH.buildObject "IPolicy" "iPolicy"
221 da5f09ef Bernardo Dal Seno
  [ THH.renameField "MinMaxISpecs" $
222 41044e04 Bernardo Dal Seno
      THH.simpleField C.ispecsMinmax [t| [MinMaxISpecs] |]
223 da5f09ef Bernardo Dal Seno
  , THH.renameField "StdSpec" $ THH.simpleField C.ispecsStd [t| ISpec |]
224 fc42a408 Iustin Pop
  , THH.renameField "DiskTemplates" $
225 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyDts [t| [DiskTemplate] |]
226 e8fa4ff6 Iustin Pop
  , THH.renameField "VcpuRatio" $
227 cd79cd83 Iustin Pop
      THH.simpleField C.ipolicyVcpuRatio [t| Double |]
228 c22d4dd4 Iustin Pop
  , THH.renameField "SpindleRatio" $
229 c22d4dd4 Iustin Pop
      THH.simpleField C.ipolicySpindleRatio [t| Double |]
230 a07343b2 Iustin Pop
  ])
231 a07343b2 Iustin Pop
232 304f9292 Iustin Pop
-- | Converts an ISpec type to a RSpec one.
233 304f9292 Iustin Pop
rspecFromISpec :: ISpec -> RSpec
234 304f9292 Iustin Pop
rspecFromISpec ispec = RSpec { rspecCpu = iSpecCpuCount ispec
235 304f9292 Iustin Pop
                             , rspecMem = iSpecMemorySize ispec
236 304f9292 Iustin Pop
                             , rspecDsk = iSpecDiskSize ispec
237 914c6df4 Bernardo Dal Seno
                             , rspecSpn = iSpecSpindleUse ispec
238 304f9292 Iustin Pop
                             }
239 304f9292 Iustin Pop
240 d02f941e Iustin Pop
-- | The default instance policy.
241 d02f941e Iustin Pop
defIPolicy :: IPolicy
242 da5f09ef Bernardo Dal Seno
defIPolicy = IPolicy { iPolicyMinMaxISpecs = defMinMaxISpecs
243 da5f09ef Bernardo Dal Seno
                     , iPolicyStdSpec = defStdISpec
244 fc42a408 Iustin Pop
                     -- hardcoding here since Constants.hs exports the
245 fc42a408 Iustin Pop
                     -- string values, not the actual type; and in
246 fc42a408 Iustin Pop
                     -- htools, we are mostly looking at DRBD
247 810d051f Iustin Pop
                     , iPolicyDiskTemplates = [minBound..maxBound]
248 e8fa4ff6 Iustin Pop
                     , iPolicyVcpuRatio = C.ipolicyDefaultsVcpuRatio
249 c22d4dd4 Iustin Pop
                     , iPolicySpindleRatio = C.ipolicyDefaultsSpindleRatio
250 d02f941e Iustin Pop
                     }
251 d02f941e Iustin Pop
252 2180829f Iustin Pop
-- | The dynamic resource specs of a machine (i.e. load or load
253 2180829f Iustin Pop
-- capacity, as opposed to size).
254 2180829f Iustin Pop
data DynUtil = DynUtil
255 ebf38064 Iustin Pop
  { cpuWeight :: Weight -- ^ Standardised CPU usage
256 ebf38064 Iustin Pop
  , memWeight :: Weight -- ^ Standardised memory load
257 ebf38064 Iustin Pop
  , dskWeight :: Weight -- ^ Standardised disk I\/O usage
258 ebf38064 Iustin Pop
  , netWeight :: Weight -- ^ Standardised network usage
259 139c0683 Iustin Pop
  } deriving (Show, Eq)
260 2180829f Iustin Pop
261 525bfb36 Iustin Pop
-- | Initial empty utilisation.
262 2180829f Iustin Pop
zeroUtil :: DynUtil
263 2180829f Iustin Pop
zeroUtil = DynUtil { cpuWeight = 0, memWeight = 0
264 2180829f Iustin Pop
                   , dskWeight = 0, netWeight = 0 }
265 2180829f Iustin Pop
266 525bfb36 Iustin Pop
-- | Base utilisation (used when no actual utilisation data is
267 525bfb36 Iustin Pop
-- supplied).
268 ee9724b9 Iustin Pop
baseUtil :: DynUtil
269 ee9724b9 Iustin Pop
baseUtil = DynUtil { cpuWeight = 1, memWeight = 1
270 ee9724b9 Iustin Pop
                   , dskWeight = 1, netWeight = 1 }
271 ee9724b9 Iustin Pop
272 525bfb36 Iustin Pop
-- | Sum two utilisation records.
273 2180829f Iustin Pop
addUtil :: DynUtil -> DynUtil -> DynUtil
274 2180829f Iustin Pop
addUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
275 ebf38064 Iustin Pop
  DynUtil (a1+b1) (a2+b2) (a3+b3) (a4+b4)
276 2180829f Iustin Pop
277 525bfb36 Iustin Pop
-- | Substracts one utilisation record from another.
278 2180829f Iustin Pop
subUtil :: DynUtil -> DynUtil -> DynUtil
279 2180829f Iustin Pop
subUtil (DynUtil a1 a2 a3 a4) (DynUtil b1 b2 b3 b4) =
280 ebf38064 Iustin Pop
  DynUtil (a1-b1) (a2-b2) (a3-b3) (a4-b4)
281 2180829f Iustin Pop
282 66dac8e0 Iustin Pop
-- | The description of an instance placement. It contains the
283 66dac8e0 Iustin Pop
-- instance index, the new primary and secondary node, the move being
284 66dac8e0 Iustin Pop
-- performed and the score of the cluster after the move.
285 66dac8e0 Iustin Pop
type Placement = (Idx, Ndx, Ndx, IMove, Score)
286 92e32d76 Iustin Pop
287 525bfb36 Iustin Pop
-- | An instance move definition.
288 92e32d76 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
289 0c8cef35 Iustin Pop
           | FailoverToAny Ndx       -- ^ Failover to a random node
290 0c8cef35 Iustin Pop
                                     -- (fa:np), for shared storage
291 92e32d76 Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
292 92e32d76 Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
293 92e32d76 Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
294 92e32d76 Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
295 139c0683 Iustin Pop
             deriving (Show)
296 92e32d76 Iustin Pop
297 0e8ae201 Iustin Pop
-- | Formatted solution output for one move (involved nodes and
298 525bfb36 Iustin Pop
-- commands.
299 924f9c16 Iustin Pop
type MoveJob = ([Ndx], Idx, IMove, [String])
300 0e8ae201 Iustin Pop
301 525bfb36 Iustin Pop
-- | Unknown field in table output.
302 82ea2874 Iustin Pop
unknownField :: String
303 82ea2874 Iustin Pop
unknownField = "<unknown field>"
304 82ea2874 Iustin Pop
305 525bfb36 Iustin Pop
-- | A list of command elements.
306 0e8ae201 Iustin Pop
type JobSet = [MoveJob]
307 0e8ae201 Iustin Pop
308 f4c0b8c5 Iustin Pop
-- | Default max disk usage ratio.
309 f4c0b8c5 Iustin Pop
defReservedDiskRatio :: Double
310 f4c0b8c5 Iustin Pop
defReservedDiskRatio = 0
311 f4c0b8c5 Iustin Pop
312 1e3dccc8 Iustin Pop
-- | Base memory unit.
313 1e3dccc8 Iustin Pop
unitMem :: Int
314 1e3dccc8 Iustin Pop
unitMem = 64
315 1e3dccc8 Iustin Pop
316 1e3dccc8 Iustin Pop
-- | Base disk unit.
317 1e3dccc8 Iustin Pop
unitDsk :: Int
318 1e3dccc8 Iustin Pop
unitDsk = 256
319 1e3dccc8 Iustin Pop
320 1e3dccc8 Iustin Pop
-- | Base vcpus unit.
321 1e3dccc8 Iustin Pop
unitCpu :: Int
322 1e3dccc8 Iustin Pop
unitCpu = 1
323 1e3dccc8 Iustin Pop
324 fcfc0c2d Bernardo Dal Seno
-- | Base spindles unit.
325 fcfc0c2d Bernardo Dal Seno
unitSpindle :: Int
326 fcfc0c2d Bernardo Dal Seno
unitSpindle = 1
327 fcfc0c2d Bernardo Dal Seno
328 525bfb36 Iustin Pop
-- | Reason for an operation's falure.
329 f2280553 Iustin Pop
data FailMode = FailMem  -- ^ Failed due to not enough RAM
330 f2280553 Iustin Pop
              | FailDisk -- ^ Failed due to not enough disk
331 f2280553 Iustin Pop
              | FailCPU  -- ^ Failed due to not enough CPU capacity
332 f2280553 Iustin Pop
              | FailN1   -- ^ Failed due to not passing N1 checks
333 5f0b9579 Iustin Pop
              | FailTags -- ^ Failed due to tag exclusion
334 6ef49eef Bernardo Dal Seno
              | FailDiskCount -- ^ Failed due to wrong number of disks
335 6ef49eef Bernardo Dal Seno
              | FailSpindles -- ^ Failed due to wrong/missing spindles
336 6ef49eef Bernardo Dal Seno
              | FailInternal -- ^ Internal error
337 139c0683 Iustin Pop
                deriving (Eq, Enum, Bounded, Show)
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)
388 3e77a36c Dato Simó
389 3e77a36c Dato Simó
-- | The repair modes for the auto-repair tool.
390 3e77a36c Dato Simó
$(THH.declareSADT "AutoRepairType"
391 3e77a36c Dato Simó
       -- Order is important here: from least destructive to most.
392 3e77a36c Dato Simó
       [ ("ArFixStorage", 'C.autoRepairFixStorage)
393 3e77a36c Dato Simó
       , ("ArMigrate",    'C.autoRepairMigrate)
394 3e77a36c Dato Simó
       , ("ArFailover",   'C.autoRepairFailover)
395 3e77a36c Dato Simó
       , ("ArReinstall",  'C.autoRepairReinstall)
396 3e77a36c Dato Simó
       ])
397 3e77a36c Dato Simó
398 3e77a36c Dato Simó
-- | The possible auto-repair results.
399 3e77a36c Dato Simó
$(THH.declareSADT "AutoRepairResult"
400 de9d75c8 Dato Simó
       -- Order is important here: higher results take precedence when an object
401 de9d75c8 Dato Simó
       -- has several result annotations attached.
402 de9d75c8 Dato Simó
       [ ("ArEnoperm", 'C.autoRepairEnoperm)
403 de9d75c8 Dato Simó
       , ("ArSuccess", 'C.autoRepairSuccess)
404 3e77a36c Dato Simó
       , ("ArFailure", 'C.autoRepairFailure)
405 3e77a36c Dato Simó
       ])
406 7ec2f76b Dato Simó
407 7ec2f76b Dato Simó
-- | The possible auto-repair policy for a given instance.
408 7ec2f76b Dato Simó
data AutoRepairPolicy
409 7ec2f76b Dato Simó
  = ArEnabled AutoRepairType          -- ^ Auto-repair explicitly enabled
410 7ec2f76b Dato Simó
  | ArSuspended AutoRepairSuspendTime -- ^ Suspended temporarily, or forever
411 7ec2f76b Dato Simó
  | ArNotEnabled                      -- ^ Auto-repair not explicitly enabled
412 7ec2f76b Dato Simó
  deriving (Eq, Show)
413 7ec2f76b Dato Simó
414 7ec2f76b Dato Simó
-- | The suspend timeout for 'ArSuspended'.
415 7ec2f76b Dato Simó
data AutoRepairSuspendTime = Forever         -- ^ Permanently suspended
416 7ec2f76b Dato Simó
                           | Until ClockTime -- ^ Suspended up to a certain time
417 7ec2f76b Dato Simó
                           deriving (Eq, Show)
418 7ec2f76b Dato Simó
419 7ec2f76b Dato Simó
-- | The possible auto-repair states for any given instance.
420 7ec2f76b Dato Simó
data AutoRepairStatus
421 de9d75c8 Dato Simó
  = ArHealthy (Maybe AutoRepairData) -- ^ No problems detected with the instance
422 7ec2f76b Dato Simó
  | ArNeedsRepair AutoRepairData   -- ^ Instance has problems, no action taken
423 7ec2f76b Dato Simó
  | ArPendingRepair AutoRepairData -- ^ Repair jobs ongoing for the instance
424 7ec2f76b Dato Simó
  | ArFailedRepair AutoRepairData  -- ^ Some repair jobs for the instance failed
425 de9d75c8 Dato Simó
  deriving (Eq, Show)
426 7ec2f76b Dato Simó
427 7ec2f76b Dato Simó
-- | The data accompanying a repair operation (future, pending, or failed).
428 7ec2f76b Dato Simó
data AutoRepairData = AutoRepairData { arType :: AutoRepairType
429 7ec2f76b Dato Simó
                                     , arUuid :: String
430 7ec2f76b Dato Simó
                                     , arTime :: ClockTime
431 7ec2f76b Dato Simó
                                     , arJobs :: [JobId]
432 7ec2f76b Dato Simó
                                     , arResult :: Maybe AutoRepairResult
433 de9d75c8 Dato Simó
                                     , arTag :: String
434 7ec2f76b Dato Simó
                                     }
435 de9d75c8 Dato Simó
                    deriving (Eq, Show)