Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Instance.hs @ 7c3a6391

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