Merge branch 'stable-2.9' into stable-2.10
[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, 2013 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   , Disk(..)
32   , AssocList
33   , List
34   , create
35   , isRunning
36   , isOffline
37   , notOffline
38   , instanceDown
39   , usesSecMem
40   , applyIfOnline
41   , setIdx
42   , setName
43   , setAlias
44   , setPri
45   , setSec
46   , setBoth
47   , setMovable
48   , specOf
49   , getTotalSpindles
50   , instBelowISpec
51   , instAboveISpec
52   , instMatchesPolicy
53   , shrinkByType
54   , localStorageTemplates
55   , hasSecondary
56   , requiredNodes
57   , allNodes
58   , usesLocalStorage
59   , mirrorType
60   ) where
61
62 import Control.Monad (liftM2)
63
64 import Ganeti.BasicTypes
65 import qualified Ganeti.HTools.Types as T
66 import qualified Ganeti.HTools.Container as Container
67 import Ganeti.HTools.Nic (Nic)
68
69 import Ganeti.Utils
70
71 -- * Type declarations
72 data Disk = Disk
73   { dskSize     :: Int       -- ^ Size in bytes
74   , dskSpindles :: Maybe Int -- ^ Number of spindles
75   } deriving (Show, Eq)
76
77 -- | The instance type.
78 data Instance = Instance
79   { name         :: String    -- ^ The instance name
80   , alias        :: String    -- ^ The shortened name
81   , mem          :: Int       -- ^ Memory of the instance
82   , dsk          :: Int       -- ^ Total disk usage of the instance
83   , disks        :: [Disk]    -- ^ Sizes of the individual disks
84   , vcpus        :: Int       -- ^ Number of VCPUs
85   , runSt        :: T.InstanceStatus -- ^ Original run status
86   , pNode        :: T.Ndx     -- ^ Original primary node
87   , sNode        :: T.Ndx     -- ^ Original secondary node
88   , idx          :: T.Idx     -- ^ Internal index
89   , util         :: T.DynUtil -- ^ Dynamic resource usage
90   , movable      :: Bool      -- ^ Can and should the instance be moved?
91   , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
92   , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
93   , spindleUse   :: Int       -- ^ The numbers of used spindles
94   , allTags      :: [String]  -- ^ List of all instance tags
95   , exclTags     :: [String]  -- ^ List of instance exclusion tags
96   , arPolicy     :: T.AutoRepairPolicy -- ^ Instance's auto-repair policy
97   , nics         :: [Nic]     -- ^ NICs of the instance
98   } deriving (Show, Eq)
99
100 instance T.Element Instance where
101   nameOf   = name
102   idxOf    = idx
103   setAlias = setAlias
104   setIdx   = setIdx
105   allNames n = [name n, alias n]
106
107 -- | Check if instance is running.
108 isRunning :: Instance -> Bool
109 isRunning (Instance {runSt = T.Running}) = True
110 isRunning (Instance {runSt = T.ErrorUp}) = True
111 isRunning _                              = False
112
113 -- | Check if instance is offline.
114 isOffline :: Instance -> Bool
115 isOffline (Instance {runSt = T.StatusOffline}) = True
116 isOffline _                                    = False
117
118
119 -- | Helper to check if the instance is not offline.
120 notOffline :: Instance -> Bool
121 notOffline = not . isOffline
122
123 -- | Check if instance is down.
124 instanceDown :: Instance -> Bool
125 instanceDown inst | isRunning inst = False
126 instanceDown inst | isOffline inst = False
127 instanceDown _                     = True
128
129 -- | Apply the function if the instance is online. Otherwise use
130 -- the initial value
131 applyIfOnline :: Instance -> (a -> a) -> a -> a
132 applyIfOnline = applyIf . notOffline
133
134 -- | Helper for determining whether an instance's memory needs to be
135 -- taken into account for secondary memory reservation.
136 usesSecMem :: Instance -> Bool
137 usesSecMem inst = notOffline inst && autoBalance inst
138
139 -- | Constant holding the local storage templates.
140 --
141 -- /Note:/ Currently Ganeti only exports node total/free disk space
142 -- for LVM-based storage; file-based storage is ignored in this model,
143 -- so even though file-based storage uses in reality disk space on the
144 -- node, in our model it won't affect it and we can't compute whether
145 -- there is enough disk space for a file-based instance. Therefore we
146 -- will treat this template as \'foreign\' storage.
147 localStorageTemplates :: [T.DiskTemplate]
148 localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
149
150 -- | Constant holding the movable disk templates.
151 --
152 -- This only determines the initial 'movable' state of the
153 -- instance. Further the movable state can be restricted more due to
154 -- user choices, etc.
155 movableDiskTemplates :: [T.DiskTemplate]
156 movableDiskTemplates =
157   [ T.DTDrbd8
158   , T.DTBlock
159   , T.DTSharedFile
160   , T.DTRbd
161   , T.DTExt
162   ]
163
164 -- | A simple name for the int, instance association list.
165 type AssocList = [(T.Idx, Instance)]
166
167 -- | A simple name for an instance map.
168 type List = Container.Container Instance
169
170 -- * Initialization
171
172 -- | Create an instance.
173 --
174 -- Some parameters are not initialized by function, and must be set
175 -- later (via 'setIdx' for example).
176 create :: String -> Int -> Int -> [Disk] -> Int -> T.InstanceStatus
177        -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Int
178        -> [Nic] -> Instance
179 create name_init mem_init dsk_init disks_init vcpus_init run_init tags_init
180        auto_balance_init pn sn dt su nics_init =
181   Instance { name = name_init
182            , alias = name_init
183            , mem = mem_init
184            , dsk = dsk_init
185            , disks = disks_init
186            , vcpus = vcpus_init
187            , runSt = run_init
188            , pNode = pn
189            , sNode = sn
190            , idx = -1
191            , util = T.baseUtil
192            , movable = supportsMoves dt
193            , autoBalance = auto_balance_init
194            , diskTemplate = dt
195            , spindleUse = su
196            , allTags = tags_init
197            , exclTags = []
198            , arPolicy = T.ArNotEnabled
199            , nics = nics_init
200            }
201
202 -- | Changes the index.
203 --
204 -- This is used only during the building of the data structures.
205 setIdx :: Instance -- ^ The original instance
206        -> T.Idx    -- ^ New index
207        -> Instance -- ^ The modified instance
208 setIdx t i = t { idx = i }
209
210 -- | Changes the name.
211 --
212 -- This is used only during the building of the data structures.
213 setName :: Instance -- ^ The original instance
214         -> String   -- ^ New name
215         -> Instance -- ^ The modified instance
216 setName t s = t { name = s, alias = s }
217
218 -- | Changes the alias.
219 --
220 -- This is used only during the building of the data structures.
221 setAlias :: Instance -- ^ The original instance
222          -> String   -- ^ New alias
223          -> Instance -- ^ The modified instance
224 setAlias t s = t { alias = s }
225
226 -- * Update functions
227
228 -- | Changes the primary node of the instance.
229 setPri :: Instance  -- ^ the original instance
230         -> T.Ndx    -- ^ the new primary node
231         -> Instance -- ^ the modified instance
232 setPri t p = t { pNode = p }
233
234 -- | Changes the secondary node of the instance.
235 setSec :: Instance  -- ^ the original instance
236         -> T.Ndx    -- ^ the new secondary node
237         -> Instance -- ^ the modified instance
238 setSec t s = t { sNode = s }
239
240 -- | Changes both nodes of the instance.
241 setBoth :: Instance  -- ^ the original instance
242          -> T.Ndx    -- ^ new primary node index
243          -> T.Ndx    -- ^ new secondary node index
244          -> Instance -- ^ the modified instance
245 setBoth t p s = t { pNode = p, sNode = s }
246
247 -- | Sets the movable flag on an instance.
248 setMovable :: Instance -- ^ The original instance
249            -> Bool     -- ^ New movable flag
250            -> Instance -- ^ The modified instance
251 setMovable t m = t { movable = m }
252
253 -- | Try to shrink the instance based on the reason why we can't
254 -- allocate it.
255 shrinkByType :: Instance -> T.FailMode -> Result Instance
256 shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
257                               in if v < T.unitMem
258                                  then Bad "out of memory"
259                                  else Ok inst { mem = v }
260 shrinkByType inst T.FailDisk =
261   let newdisks = [d {dskSize = dskSize d - T.unitDsk}| d <- disks inst]
262       v = dsk inst - (length . disks $ inst) * T.unitDsk
263   in if any (< T.unitDsk) $ map dskSize newdisks
264      then Bad "out of disk"
265      else Ok inst { dsk = v, disks = newdisks }
266 shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
267                               in if v < T.unitCpu
268                                  then Bad "out of vcpus"
269                                  else Ok inst { vcpus = v }
270 shrinkByType inst T.FailSpindles =
271   case disks inst of
272     [Disk ds sp] -> case sp of
273                       Nothing -> Bad "No spindles, shouldn't have happened"
274                       Just sp' -> let v = sp' - T.unitSpindle
275                                   in if v < T.unitSpindle
276                                      then Bad "out of spindles"
277                                      else Ok inst { disks = [Disk ds (Just v)] }
278     d -> Bad $ "Expected one disk, but found " ++ show d
279 shrinkByType _ f = Bad $ "Unhandled failure mode " ++ show f
280
281 -- | Get the number of disk spindles
282 getTotalSpindles :: Instance -> Maybe Int
283 getTotalSpindles inst =
284   foldr (liftM2 (+) . dskSpindles ) (Just 0) (disks inst)
285
286 -- | Return the spec of an instance.
287 specOf :: Instance -> T.RSpec
288 specOf Instance { mem = m, dsk = d, vcpus = c, disks = dl } =
289   let sp = case dl of
290              [Disk _ (Just sp')] -> sp'
291              _ -> 0
292   in T.RSpec { T.rspecCpu = c, T.rspecMem = m,
293                T.rspecDsk = d, T.rspecSpn = sp }
294
295 -- | Checks if an instance is smaller/bigger than a given spec. Returns
296 -- OpGood for a correct spec, otherwise Bad one of the possible
297 -- failure modes.
298 instCompareISpec :: Ordering -> Instance-> T.ISpec -> Bool -> T.OpResult ()
299 instCompareISpec which inst ispec exclstor
300   | which == mem inst `compare` T.iSpecMemorySize ispec = Bad T.FailMem
301   | which `elem` map ((`compare` T.iSpecDiskSize ispec) . dskSize)
302     (disks inst) = Bad T.FailDisk
303   | which == vcpus inst `compare` T.iSpecCpuCount ispec = Bad T.FailCPU
304   | exclstor &&
305     case getTotalSpindles inst of
306       Nothing -> True
307       Just sp_sum -> which == sp_sum `compare` T.iSpecSpindleUse ispec
308     = Bad T.FailSpindles
309   | not exclstor && which == spindleUse inst `compare` T.iSpecSpindleUse ispec
310     = Bad T.FailSpindles
311   | diskTemplate inst /= T.DTDiskless &&
312     which == length (disks inst) `compare` T.iSpecDiskCount ispec
313     = Bad T.FailDiskCount
314   | otherwise = Ok ()
315
316 -- | Checks if an instance is smaller than a given spec.
317 instBelowISpec :: Instance -> T.ISpec -> Bool -> T.OpResult ()
318 instBelowISpec = instCompareISpec GT
319
320 -- | Checks if an instance is bigger than a given spec.
321 instAboveISpec :: Instance -> T.ISpec -> Bool -> T.OpResult ()
322 instAboveISpec = instCompareISpec LT
323
324 -- | Checks if an instance matches a min/max specs pair
325 instMatchesMinMaxSpecs :: Instance -> T.MinMaxISpecs -> Bool -> T.OpResult ()
326 instMatchesMinMaxSpecs inst minmax exclstor = do
327   instAboveISpec inst (T.minMaxISpecsMinSpec minmax) exclstor
328   instBelowISpec inst (T.minMaxISpecsMaxSpec minmax) exclstor
329
330 -- | Checks if an instance matches any specs of a policy
331 instMatchesSpecs :: Instance -> [T.MinMaxISpecs] -> Bool -> T.OpResult ()
332  -- Return Ok for no constraints, though this should never happen
333 instMatchesSpecs _ [] _ = Ok ()
334 instMatchesSpecs inst minmaxes exclstor =
335   -- The initial "Bad" should be always replaced by a real result
336   foldr eithermatch (Bad T.FailInternal) minmaxes
337   where eithermatch mm (Bad _) = instMatchesMinMaxSpecs inst mm exclstor
338         eithermatch _ y@(Ok ()) = y
339
340 -- | Checks if an instance matches a policy.
341 instMatchesPolicy :: Instance -> T.IPolicy -> Bool -> T.OpResult ()
342 instMatchesPolicy inst ipol exclstor = do
343   instMatchesSpecs inst (T.iPolicyMinMaxISpecs ipol) exclstor
344   if diskTemplate inst `elem` T.iPolicyDiskTemplates ipol
345     then Ok ()
346     else Bad T.FailDisk
347
348 -- | Checks whether the instance uses a secondary node.
349 --
350 -- /Note:/ This should be reconciled with @'sNode' ==
351 -- 'Node.noSecondary'@.
352 hasSecondary :: Instance -> Bool
353 hasSecondary = (== T.DTDrbd8) . diskTemplate
354
355 -- | Computed the number of nodes for a given disk template.
356 requiredNodes :: T.DiskTemplate -> Int
357 requiredNodes T.DTDrbd8 = 2
358 requiredNodes _         = 1
359
360 -- | Computes all nodes of an instance.
361 allNodes :: Instance -> [T.Ndx]
362 allNodes inst = case diskTemplate inst of
363                   T.DTDrbd8 -> [pNode inst, sNode inst]
364                   _ -> [pNode inst]
365
366 -- | Checks whether a given disk template uses local storage.
367 usesLocalStorage :: Instance -> Bool
368 usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
369
370 -- | Checks whether a given disk template supported moves.
371 supportsMoves :: T.DiskTemplate -> Bool
372 supportsMoves = (`elem` movableDiskTemplates)
373
374 -- | A simple wrapper over 'T.templateMirrorType'.
375 mirrorType :: Instance -> T.MirrorType
376 mirrorType = T.templateMirrorType . diskTemplate