Instance.hs: add an 'arPolicy' field for auto-repair policy
[ganeti-local] / src / Ganeti / HTools / Instance.hs
1 {-| Module describing an instance.
2
3 The instance data type holds very few fields, the algorithm
4 intelligence is in the "Node" and "Cluster" modules.
5
6 -}
7
8 {-
9
10 Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11
12 This program is free software; you can redistribute it and/or modify
13 it under the terms of the GNU General Public License as published by
14 the Free Software Foundation; either version 2 of the License, or
15 (at your option) any later version.
16
17 This program is distributed in the hope that it will be useful, but
18 WITHOUT ANY WARRANTY; without even the implied warranty of
19 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 General Public License for more details.
21
22 You should have received a copy of the GNU General Public License
23 along with this program; if not, write to the Free Software
24 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 02110-1301, USA.
26
27 -}
28
29 module Ganeti.HTools.Instance
30   ( Instance(..)
31   , AssocList
32   , List
33   , create
34   , isRunning
35   , isOffline
36   , notOffline
37   , instanceDown
38   , usesSecMem
39   , applyIfOnline
40   , setIdx
41   , setName
42   , setAlias
43   , setPri
44   , setSec
45   , setBoth
46   , setMovable
47   , specOf
48   , instBelowISpec
49   , instAboveISpec
50   , instMatchesPolicy
51   , shrinkByType
52   , localStorageTemplates
53   , hasSecondary
54   , requiredNodes
55   , allNodes
56   , usesLocalStorage
57   , mirrorType
58   ) where
59
60 import Ganeti.BasicTypes
61 import qualified Ganeti.HTools.Types as T
62 import qualified Ganeti.HTools.Container as Container
63
64 import Ganeti.Utils
65
66 -- * Type declarations
67
68 -- | The instance type.
69 data Instance = Instance
70   { name         :: String    -- ^ The instance name
71   , alias        :: String    -- ^ The shortened name
72   , mem          :: Int       -- ^ Memory of the instance
73   , dsk          :: Int       -- ^ Disk size of instance
74   , vcpus        :: Int       -- ^ Number of VCPUs
75   , runSt        :: T.InstanceStatus -- ^ Original run status
76   , pNode        :: T.Ndx     -- ^ Original primary node
77   , sNode        :: T.Ndx     -- ^ Original secondary node
78   , idx          :: T.Idx     -- ^ Internal index
79   , util         :: T.DynUtil -- ^ Dynamic resource usage
80   , movable      :: Bool      -- ^ Can and should the instance be moved?
81   , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
82   , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
83   , spindleUse   :: Int       -- ^ The numbers of used spindles
84   , allTags      :: [String]  -- ^ List of all instance tags
85   , exclTags     :: [String]  -- ^ List of instance exclusion tags
86   , arPolicy     :: T.AutoRepairPolicy -- ^ Instance's auto-repair policy
87   } deriving (Show, Eq)
88
89 instance T.Element Instance where
90   nameOf   = name
91   idxOf    = idx
92   setAlias = setAlias
93   setIdx   = setIdx
94   allNames n = [name n, alias n]
95
96 -- | Check if instance is running.
97 isRunning :: Instance -> Bool
98 isRunning (Instance {runSt = T.Running}) = True
99 isRunning (Instance {runSt = T.ErrorUp}) = True
100 isRunning _                              = False
101
102 -- | Check if instance is offline.
103 isOffline :: Instance -> Bool
104 isOffline (Instance {runSt = T.StatusOffline}) = True
105 isOffline _                                    = False
106
107
108 -- | Helper to check if the instance is not offline.
109 notOffline :: Instance -> Bool
110 notOffline = not . isOffline
111
112 -- | Check if instance is down.
113 instanceDown :: Instance -> Bool
114 instanceDown inst | isRunning inst = False
115 instanceDown inst | isOffline inst = False
116 instanceDown _                     = True
117
118 -- | Apply the function if the instance is online. Otherwise use
119 -- the initial value
120 applyIfOnline :: Instance -> (a -> a) -> a -> a
121 applyIfOnline = applyIf . notOffline
122
123 -- | Helper for determining whether an instance's memory needs to be
124 -- taken into account for secondary memory reservation.
125 usesSecMem :: Instance -> Bool
126 usesSecMem inst = notOffline inst && autoBalance inst
127
128 -- | Constant holding the local storage templates.
129 --
130 -- /Note:/ Currently Ganeti only exports node total/free disk space
131 -- for LVM-based storage; file-based storage is ignored in this model,
132 -- so even though file-based storage uses in reality disk space on the
133 -- node, in our model it won't affect it and we can't compute whether
134 -- there is enough disk space for a file-based instance. Therefore we
135 -- will treat this template as \'foreign\' storage.
136 localStorageTemplates :: [T.DiskTemplate]
137 localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
138
139 -- | Constant holding the movable disk templates.
140 --
141 -- This only determines the initial 'movable' state of the
142 -- instance. Further the movable state can be restricted more due to
143 -- user choices, etc.
144 movableDiskTemplates :: [T.DiskTemplate]
145 movableDiskTemplates =
146   [ T.DTDrbd8
147   , T.DTBlock
148   , T.DTSharedFile
149   , T.DTRbd
150   , T.DTExt
151   ]
152
153 -- | A simple name for the int, instance association list.
154 type AssocList = [(T.Idx, Instance)]
155
156 -- | A simple name for an instance map.
157 type List = Container.Container Instance
158
159 -- * Initialization
160
161 -- | Create an instance.
162 --
163 -- Some parameters are not initialized by function, and must be set
164 -- later (via 'setIdx' for example).
165 create :: String -> Int -> Int -> Int -> T.InstanceStatus
166        -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Int
167        -> Instance
168 create name_init mem_init dsk_init vcpus_init run_init tags_init
169        auto_balance_init pn sn dt su =
170   Instance { name = name_init
171            , alias = name_init
172            , mem = mem_init
173            , dsk = dsk_init
174            , vcpus = vcpus_init
175            , runSt = run_init
176            , pNode = pn
177            , sNode = sn
178            , idx = -1
179            , util = T.baseUtil
180            , movable = supportsMoves dt
181            , autoBalance = auto_balance_init
182            , diskTemplate = dt
183            , spindleUse = su
184            , allTags = tags_init
185            , exclTags = []
186            , arPolicy = T.ArNotEnabled
187            }
188
189 -- | Changes the index.
190 --
191 -- This is used only during the building of the data structures.
192 setIdx :: Instance -- ^ The original instance
193        -> T.Idx    -- ^ New index
194        -> Instance -- ^ The modified instance
195 setIdx t i = t { idx = i }
196
197 -- | Changes the name.
198 --
199 -- This is used only during the building of the data structures.
200 setName :: Instance -- ^ The original instance
201         -> String   -- ^ New name
202         -> Instance -- ^ The modified instance
203 setName t s = t { name = s, alias = s }
204
205 -- | Changes the alias.
206 --
207 -- This is used only during the building of the data structures.
208 setAlias :: Instance -- ^ The original instance
209          -> String   -- ^ New alias
210          -> Instance -- ^ The modified instance
211 setAlias t s = t { alias = s }
212
213 -- * Update functions
214
215 -- | Changes the primary node of the instance.
216 setPri :: Instance  -- ^ the original instance
217         -> T.Ndx    -- ^ the new primary node
218         -> Instance -- ^ the modified instance
219 setPri t p = t { pNode = p }
220
221 -- | Changes the secondary node of the instance.
222 setSec :: Instance  -- ^ the original instance
223         -> T.Ndx    -- ^ the new secondary node
224         -> Instance -- ^ the modified instance
225 setSec t s = t { sNode = s }
226
227 -- | Changes both nodes of the instance.
228 setBoth :: Instance  -- ^ the original instance
229          -> T.Ndx    -- ^ new primary node index
230          -> T.Ndx    -- ^ new secondary node index
231          -> Instance -- ^ the modified instance
232 setBoth t p s = t { pNode = p, sNode = s }
233
234 -- | Sets the movable flag on an instance.
235 setMovable :: Instance -- ^ The original instance
236            -> Bool     -- ^ New movable flag
237            -> Instance -- ^ The modified instance
238 setMovable t m = t { movable = m }
239
240 -- | Try to shrink the instance based on the reason why we can't
241 -- allocate it.
242 shrinkByType :: Instance -> T.FailMode -> Result Instance
243 shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
244                               in if v < T.unitMem
245                                  then Bad "out of memory"
246                                  else Ok inst { mem = v }
247 shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
248                                in if v < T.unitDsk
249                                   then Bad "out of disk"
250                                   else Ok inst { dsk = v }
251 shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
252                               in if v < T.unitCpu
253                                  then Bad "out of vcpus"
254                                  else Ok inst { vcpus = v }
255 shrinkByType _ f = Bad $ "Unhandled failure mode " ++ show f
256
257 -- | Return the spec of an instance.
258 specOf :: Instance -> T.RSpec
259 specOf Instance { mem = m, dsk = d, vcpus = c } =
260   T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
261
262 -- | Checks if an instance is smaller than a given spec. Returns
263 -- OpGood for a correct spec, otherwise Bad one of the possible
264 -- failure modes.
265 instBelowISpec :: Instance -> T.ISpec -> T.OpResult ()
266 instBelowISpec inst ispec
267   | mem inst > T.iSpecMemorySize ispec = Bad T.FailMem
268   | dsk inst > T.iSpecDiskSize ispec   = Bad T.FailDisk
269   | vcpus inst > T.iSpecCpuCount ispec = Bad T.FailCPU
270   | otherwise = Ok ()
271
272 -- | Checks if an instance is bigger than a given spec.
273 instAboveISpec :: Instance -> T.ISpec -> T.OpResult ()
274 instAboveISpec inst ispec
275   | mem inst < T.iSpecMemorySize ispec = Bad T.FailMem
276   | dsk inst < T.iSpecDiskSize ispec   = Bad T.FailDisk
277   | vcpus inst < T.iSpecCpuCount ispec = Bad T.FailCPU
278   | otherwise = Ok ()
279
280 -- | Checks if an instance matches a policy.
281 instMatchesPolicy :: Instance -> T.IPolicy -> T.OpResult ()
282 instMatchesPolicy inst ipol = do
283   instAboveISpec inst (T.iPolicyMinSpec ipol)
284   instBelowISpec inst (T.iPolicyMaxSpec ipol)
285   if diskTemplate inst `elem` T.iPolicyDiskTemplates ipol
286     then Ok ()
287     else Bad T.FailDisk
288
289 -- | Checks whether the instance uses a secondary node.
290 --
291 -- /Note:/ This should be reconciled with @'sNode' ==
292 -- 'Node.noSecondary'@.
293 hasSecondary :: Instance -> Bool
294 hasSecondary = (== T.DTDrbd8) . diskTemplate
295
296 -- | Computed the number of nodes for a given disk template.
297 requiredNodes :: T.DiskTemplate -> Int
298 requiredNodes T.DTDrbd8 = 2
299 requiredNodes _         = 1
300
301 -- | Computes all nodes of an instance.
302 allNodes :: Instance -> [T.Ndx]
303 allNodes inst = case diskTemplate inst of
304                   T.DTDrbd8 -> [pNode inst, sNode inst]
305                   _ -> [pNode inst]
306
307 -- | Checks whether a given disk template uses local storage.
308 usesLocalStorage :: Instance -> Bool
309 usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
310
311 -- | Checks whether a given disk template supported moves.
312 supportsMoves :: T.DiskTemplate -> Bool
313 supportsMoves = (`elem` movableDiskTemplates)
314
315 -- | A simple wrapper over 'T.templateMirrorType'.
316 mirrorType :: Instance -> T.MirrorType
317 mirrorType = T.templateMirrorType . diskTemplate