Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Instance.hs @ 4fe04580

History | View | Annotate | Download (11.3 kB)

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