Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Types.hs @ ffc18bb2

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