Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Instance.hs @ 908c2f67

History | View | Annotate | Download (11.5 kB)

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
  , 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
import Ganeti.HTools.Nic (Nic)
64

    
65
import Ganeti.Utils
66

    
67
-- * Type declarations
68

    
69
-- | The instance type.
70
data Instance = Instance
71
  { name         :: String    -- ^ The instance name
72
  , alias        :: String    -- ^ The shortened name
73
  , mem          :: Int       -- ^ Memory of the instance
74
  , dsk          :: Int       -- ^ Total disk usage of the instance
75
  , disks        :: [Int]     -- ^ Sizes of the individual disks
76
  , vcpus        :: Int       -- ^ Number of VCPUs
77
  , runSt        :: T.InstanceStatus -- ^ Original run status
78
  , pNode        :: T.Ndx     -- ^ Original primary node
79
  , sNode        :: T.Ndx     -- ^ Original secondary node
80
  , idx          :: T.Idx     -- ^ Internal index
81
  , util         :: T.DynUtil -- ^ Dynamic resource usage
82
  , movable      :: Bool      -- ^ Can and should the instance be moved?
83
  , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
84
  , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
85
  , spindleUse   :: Int       -- ^ The numbers of used spindles
86
  , allTags      :: [String]  -- ^ List of all instance tags
87
  , exclTags     :: [String]  -- ^ List of instance exclusion tags
88
  , arPolicy     :: T.AutoRepairPolicy -- ^ Instance's auto-repair policy
89
  , nics         :: [Nic]     -- ^ NICs of the instance
90
  } deriving (Show, Eq)
91

    
92
instance T.Element Instance where
93
  nameOf   = name
94
  idxOf    = idx
95
  setAlias = setAlias
96
  setIdx   = setIdx
97
  allNames n = [name n, alias n]
98

    
99
-- | Check if instance is running.
100
isRunning :: Instance -> Bool
101
isRunning (Instance {runSt = T.Running}) = True
102
isRunning (Instance {runSt = T.ErrorUp}) = True
103
isRunning _                              = False
104

    
105
-- | Check if instance is offline.
106
isOffline :: Instance -> Bool
107
isOffline (Instance {runSt = T.StatusOffline}) = True
108
isOffline _                                    = False
109

    
110

    
111
-- | Helper to check if the instance is not offline.
112
notOffline :: Instance -> Bool
113
notOffline = not . isOffline
114

    
115
-- | Check if instance is down.
116
instanceDown :: Instance -> Bool
117
instanceDown inst | isRunning inst = False
118
instanceDown inst | isOffline inst = False
119
instanceDown _                     = True
120

    
121
-- | Apply the function if the instance is online. Otherwise use
122
-- the initial value
123
applyIfOnline :: Instance -> (a -> a) -> a -> a
124
applyIfOnline = applyIf . notOffline
125

    
126
-- | Helper for determining whether an instance's memory needs to be
127
-- taken into account for secondary memory reservation.
128
usesSecMem :: Instance -> Bool
129
usesSecMem inst = notOffline inst && autoBalance inst
130

    
131
-- | Constant holding the local storage templates.
132
--
133
-- /Note:/ Currently Ganeti only exports node total/free disk space
134
-- for LVM-based storage; file-based storage is ignored in this model,
135
-- so even though file-based storage uses in reality disk space on the
136
-- node, in our model it won't affect it and we can't compute whether
137
-- there is enough disk space for a file-based instance. Therefore we
138
-- will treat this template as \'foreign\' storage.
139
localStorageTemplates :: [T.DiskTemplate]
140
localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
141

    
142
-- | Constant holding the movable disk templates.
143
--
144
-- This only determines the initial 'movable' state of the
145
-- instance. Further the movable state can be restricted more due to
146
-- user choices, etc.
147
movableDiskTemplates :: [T.DiskTemplate]
148
movableDiskTemplates =
149
  [ T.DTDrbd8
150
  , T.DTBlock
151
  , T.DTSharedFile
152
  , T.DTRbd
153
  , T.DTExt
154
  ]
155

    
156
-- | A simple name for the int, instance association list.
157
type AssocList = [(T.Idx, Instance)]
158

    
159
-- | A simple name for an instance map.
160
type List = Container.Container Instance
161

    
162
-- * Initialization
163

    
164
-- | Create an instance.
165
--
166
-- Some parameters are not initialized by function, and must be set
167
-- later (via 'setIdx' for example).
168
create :: String -> Int -> Int -> [Int] -> Int -> T.InstanceStatus
169
       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Int
170
       -> [Nic] -> Instance
171
create name_init mem_init dsk_init disks_init vcpus_init run_init tags_init
172
       auto_balance_init pn sn dt su nics_init =
173
  Instance { name = name_init
174
           , alias = name_init
175
           , mem = mem_init
176
           , dsk = dsk_init
177
           , disks = disks_init
178
           , vcpus = vcpus_init
179
           , runSt = run_init
180
           , pNode = pn
181
           , sNode = sn
182
           , idx = -1
183
           , util = T.baseUtil
184
           , movable = supportsMoves dt
185
           , autoBalance = auto_balance_init
186
           , diskTemplate = dt
187
           , spindleUse = su
188
           , allTags = tags_init
189
           , exclTags = []
190
           , arPolicy = T.ArNotEnabled
191
           , nics = nics_init
192
           }
193

    
194
-- | Changes the index.
195
--
196
-- This is used only during the building of the data structures.
197
setIdx :: Instance -- ^ The original instance
198
       -> T.Idx    -- ^ New index
199
       -> Instance -- ^ The modified instance
200
setIdx t i = t { idx = i }
201

    
202
-- | Changes the name.
203
--
204
-- This is used only during the building of the data structures.
205
setName :: Instance -- ^ The original instance
206
        -> String   -- ^ New name
207
        -> Instance -- ^ The modified instance
208
setName t s = t { name = s, alias = s }
209

    
210
-- | Changes the alias.
211
--
212
-- This is used only during the building of the data structures.
213
setAlias :: Instance -- ^ The original instance
214
         -> String   -- ^ New alias
215
         -> Instance -- ^ The modified instance
216
setAlias t s = t { alias = s }
217

    
218
-- * Update functions
219

    
220
-- | Changes the primary node of the instance.
221
setPri :: Instance  -- ^ the original instance
222
        -> T.Ndx    -- ^ the new primary node
223
        -> Instance -- ^ the modified instance
224
setPri t p = t { pNode = p }
225

    
226
-- | Changes the secondary node of the instance.
227
setSec :: Instance  -- ^ the original instance
228
        -> T.Ndx    -- ^ the new secondary node
229
        -> Instance -- ^ the modified instance
230
setSec t s = t { sNode = s }
231

    
232
-- | Changes both nodes of the instance.
233
setBoth :: Instance  -- ^ the original instance
234
         -> T.Ndx    -- ^ new primary node index
235
         -> T.Ndx    -- ^ new secondary node index
236
         -> Instance -- ^ the modified instance
237
setBoth t p s = t { pNode = p, sNode = s }
238

    
239
-- | Sets the movable flag on an instance.
240
setMovable :: Instance -- ^ The original instance
241
           -> Bool     -- ^ New movable flag
242
           -> Instance -- ^ The modified instance
243
setMovable t m = t { movable = m }
244

    
245
-- | Try to shrink the instance based on the reason why we can't
246
-- allocate it.
247
shrinkByType :: Instance -> T.FailMode -> Result Instance
248
shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
249
                              in if v < T.unitMem
250
                                 then Bad "out of memory"
251
                                 else Ok inst { mem = v }
252
shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
253
                               in if v < T.unitDsk
254
                                  then Bad "out of disk"
255
                                  else Ok inst { dsk = v }
256
shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
257
                              in if v < T.unitCpu
258
                                 then Bad "out of vcpus"
259
                                 else Ok inst { vcpus = v }
260
shrinkByType _ f = Bad $ "Unhandled failure mode " ++ show f
261

    
262
-- | Return the spec of an instance.
263
specOf :: Instance -> T.RSpec
264
specOf Instance { mem = m, dsk = d, vcpus = c } =
265
  T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
266

    
267
-- | Checks if an instance is smaller than a given spec. Returns
268
-- OpGood for a correct spec, otherwise Bad one of the possible
269
-- failure modes.
270
instBelowISpec :: Instance -> T.ISpec -> T.OpResult ()
271
instBelowISpec inst ispec
272
  | mem inst > T.iSpecMemorySize ispec = Bad T.FailMem
273
  | any (> T.iSpecDiskSize ispec) (disks inst) = Bad T.FailDisk
274
  | vcpus inst > T.iSpecCpuCount ispec = Bad T.FailCPU
275
  | otherwise = Ok ()
276

    
277
-- | Checks if an instance is bigger than a given spec.
278
instAboveISpec :: Instance -> T.ISpec -> T.OpResult ()
279
instAboveISpec inst ispec
280
  | mem inst < T.iSpecMemorySize ispec = Bad T.FailMem
281
  | any (< T.iSpecDiskSize ispec) (disks inst) = Bad T.FailDisk
282
  | vcpus inst < T.iSpecCpuCount ispec = Bad T.FailCPU
283
  | otherwise = Ok ()
284

    
285
-- | Checks if an instance matches a min/max specs pair
286
instMatchesMinMaxSpecs :: Instance -> T.MinMaxISpecs -> T.OpResult ()
287
instMatchesMinMaxSpecs inst minmax = do
288
  instAboveISpec inst (T.minMaxISpecsMinSpec minmax)
289
  instBelowISpec inst (T.minMaxISpecsMaxSpec minmax)
290

    
291
-- | Checks if an instance matches any specs of a policy
292
instMatchesSpecs :: Instance -> [T.MinMaxISpecs] -> T.OpResult ()
293
 -- Return Ok for no constraints, though this should never happen
294
instMatchesSpecs _ [] = Ok ()
295
instMatchesSpecs inst (minmax:minmaxes) =
296
  foldr eithermatch (instMatchesMinMaxSpecs inst minmax) minmaxes
297
  where eithermatch mm (Bad _) = instMatchesMinMaxSpecs inst mm
298
        eithermatch _ y@(Ok ()) = y
299
--  # See 04f231771
300

    
301
-- | Checks if an instance matches a policy.
302
instMatchesPolicy :: Instance -> T.IPolicy -> T.OpResult ()
303
instMatchesPolicy inst ipol = do
304
  instMatchesSpecs inst $ T.iPolicyMinMaxISpecs ipol
305
  if diskTemplate inst `elem` T.iPolicyDiskTemplates ipol
306
    then Ok ()
307
    else Bad T.FailDisk
308

    
309
-- | Checks whether the instance uses a secondary node.
310
--
311
-- /Note:/ This should be reconciled with @'sNode' ==
312
-- 'Node.noSecondary'@.
313
hasSecondary :: Instance -> Bool
314
hasSecondary = (== T.DTDrbd8) . diskTemplate
315

    
316
-- | Computed the number of nodes for a given disk template.
317
requiredNodes :: T.DiskTemplate -> Int
318
requiredNodes T.DTDrbd8 = 2
319
requiredNodes _         = 1
320

    
321
-- | Computes all nodes of an instance.
322
allNodes :: Instance -> [T.Ndx]
323
allNodes inst = case diskTemplate inst of
324
                  T.DTDrbd8 -> [pNode inst, sNode inst]
325
                  _ -> [pNode inst]
326

    
327
-- | Checks whether a given disk template uses local storage.
328
usesLocalStorage :: Instance -> Bool
329
usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
330

    
331
-- | Checks whether a given disk template supported moves.
332
supportsMoves :: T.DiskTemplate -> Bool
333
supportsMoves = (`elem` movableDiskTemplates)
334

    
335
-- | A simple wrapper over 'T.templateMirrorType'.
336
mirrorType :: Instance -> T.MirrorType
337
mirrorType = T.templateMirrorType . diskTemplate