Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ 67ec18c0

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