Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Instance.hs @ 55bd1414

History | View | Annotate | Download (10.2 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 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
  , instanceRunning
35
  , instanceOffline
36
  , instanceNotOffline
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
  ) where
58

    
59
import qualified Ganeti.HTools.Types as T
60
import qualified Ganeti.HTools.Container as Container
61

    
62
import Ganeti.HTools.Utils
63

    
64
-- * Type declarations
65

    
66
-- | The instance type.
67
data Instance = Instance
68
  { name         :: String    -- ^ The instance name
69
  , alias        :: String    -- ^ The shortened name
70
  , mem          :: Int       -- ^ Memory of the instance
71
  , dsk          :: Int       -- ^ Disk size of instance
72
  , vcpus        :: Int       -- ^ Number of VCPUs
73
  , runSt        :: T.InstanceStatus -- ^ Original run status
74
  , pNode        :: T.Ndx     -- ^ Original primary node
75
  , sNode        :: T.Ndx     -- ^ Original secondary node
76
  , idx          :: T.Idx     -- ^ Internal index
77
  , util         :: T.DynUtil -- ^ Dynamic resource usage
78
  , movable      :: Bool      -- ^ Can and should the instance be moved?
79
  , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
80
  , tags         :: [String]  -- ^ List of instance tags
81
  , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
82
  } deriving (Show, Read)
83

    
84
instance T.Element Instance where
85
  nameOf   = name
86
  idxOf    = idx
87
  setAlias = setAlias
88
  setIdx   = setIdx
89
  allNames n = [name n, alias n]
90

    
91
-- | Check if instance is running.
92
instanceRunning :: Instance -> Bool
93
instanceRunning (Instance {runSt = T.Running}) = True
94
instanceRunning (Instance {runSt = T.ErrorUp}) = True
95
instanceRunning _                              = False
96

    
97
-- | Check if instance is offline.
98
instanceOffline :: Instance -> Bool
99
instanceOffline (Instance {runSt = T.AdminOffline}) = True
100
instanceOffline _                                   = False
101

    
102

    
103
-- | Helper to check if the instance is not offline.
104
instanceNotOffline :: Instance -> Bool
105
instanceNotOffline = not . instanceOffline
106

    
107
-- | Check if instance is down.
108
instanceDown :: Instance -> Bool
109
instanceDown inst | instanceRunning inst = False
110
instanceDown inst | instanceOffline inst = False
111
instanceDown _                           = True
112

    
113
-- | Apply the function if the instance is online. Otherwise use
114
-- the initial value
115
applyIfOnline :: Instance -> (a -> a) -> a -> a
116
applyIfOnline = applyIf . instanceNotOffline
117

    
118
-- | Helper for determining whether an instance's memory needs to be
119
-- taken into account for secondary memory reservation.
120
usesSecMem :: Instance -> Bool
121
usesSecMem inst = instanceNotOffline inst && autoBalance inst
122

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

    
134
-- | Constant holding the movable disk templates.
135
--
136
-- This only determines the initial 'movable' state of the
137
-- instance. Further the movable state can be restricted more due to
138
-- user choices, etc.
139
movableDiskTemplates :: [T.DiskTemplate]
140
movableDiskTemplates = [ T.DTDrbd8, T.DTBlock, T.DTSharedFile ]
141

    
142
-- | A simple name for the int, instance association list.
143
type AssocList = [(T.Idx, Instance)]
144

    
145
-- | A simple name for an instance map.
146
type List = Container.Container Instance
147

    
148
-- * Initialization
149

    
150
-- | Create an instance.
151
--
152
-- Some parameters are not initialized by function, and must be set
153
-- later (via 'setIdx' for example).
154
create :: String -> Int -> Int -> Int -> T.InstanceStatus
155
       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Instance
156
create name_init mem_init dsk_init vcpus_init run_init tags_init
157
       auto_balance_init pn sn dt =
158
  Instance { name = name_init
159
           , alias = name_init
160
           , mem = mem_init
161
           , dsk = dsk_init
162
           , vcpus = vcpus_init
163
           , runSt = run_init
164
           , pNode = pn
165
           , sNode = sn
166
           , idx = -1
167
           , util = T.baseUtil
168
           , tags = tags_init
169
           , movable = supportsMoves dt
170
           , autoBalance = auto_balance_init
171
           , diskTemplate = dt
172
           }
173

    
174
-- | Changes the index.
175
--
176
-- This is used only during the building of the data structures.
177
setIdx :: Instance -- ^ The original instance
178
       -> T.Idx    -- ^ New index
179
       -> Instance -- ^ The modified instance
180
setIdx t i = t { idx = i }
181

    
182
-- | Changes the name.
183
--
184
-- This is used only during the building of the data structures.
185
setName :: Instance -- ^ The original instance
186
        -> String   -- ^ New name
187
        -> Instance -- ^ The modified instance
188
setName t s = t { name = s, alias = s }
189

    
190
-- | Changes the alias.
191
--
192
-- This is used only during the building of the data structures.
193
setAlias :: Instance -- ^ The original instance
194
         -> String   -- ^ New alias
195
         -> Instance -- ^ The modified instance
196
setAlias t s = t { alias = s }
197

    
198
-- * Update functions
199

    
200
-- | Changes the primary node of the instance.
201
setPri :: Instance  -- ^ the original instance
202
        -> T.Ndx    -- ^ the new primary node
203
        -> Instance -- ^ the modified instance
204
setPri t p = t { pNode = p }
205

    
206
-- | Changes the secondary node of the instance.
207
setSec :: Instance  -- ^ the original instance
208
        -> T.Ndx    -- ^ the new secondary node
209
        -> Instance -- ^ the modified instance
210
setSec t s = t { sNode = s }
211

    
212
-- | Changes both nodes of the instance.
213
setBoth :: Instance  -- ^ the original instance
214
         -> T.Ndx    -- ^ new primary node index
215
         -> T.Ndx    -- ^ new secondary node index
216
         -> Instance -- ^ the modified instance
217
setBoth t p s = t { pNode = p, sNode = s }
218

    
219
-- | Sets the movable flag on an instance.
220
setMovable :: Instance -- ^ The original instance
221
           -> Bool     -- ^ New movable flag
222
           -> Instance -- ^ The modified instance
223
setMovable t m = t { movable = m }
224

    
225
-- | Try to shrink the instance based on the reason why we can't
226
-- allocate it.
227
shrinkByType :: Instance -> T.FailMode -> T.Result Instance
228
shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
229
                              in if v < T.unitMem
230
                                 then T.Bad "out of memory"
231
                                 else T.Ok inst { mem = v }
232
shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
233
                               in if v < T.unitDsk
234
                                  then T.Bad "out of disk"
235
                                  else T.Ok inst { dsk = v }
236
shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
237
                              in if v < T.unitCpu
238
                                 then T.Bad "out of vcpus"
239
                                 else T.Ok inst { vcpus = v }
240
shrinkByType _ f = T.Bad $ "Unhandled failure mode " ++ show f
241

    
242
-- | Return the spec of an instance.
243
specOf :: Instance -> T.RSpec
244
specOf Instance { mem = m, dsk = d, vcpus = c } =
245
  T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
246

    
247
-- | Checks if an instance is smaller than a given spec. Returns
248
-- OpGood for a correct spec, otherwise OpFail one of the possible
249
-- failure modes.
250
instBelowISpec :: Instance -> T.ISpec -> T.OpResult ()
251
instBelowISpec inst ispec
252
  | mem inst > T.iSpecMemorySize ispec = T.OpFail T.FailMem
253
  | dsk inst > T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
254
  | vcpus inst > T.iSpecCpuCount ispec = T.OpFail T.FailCPU
255
  | otherwise = T.OpGood ()
256

    
257
-- | Checks if an instance is bigger than a given spec.
258
instAboveISpec :: Instance -> T.ISpec -> T.OpResult ()
259
instAboveISpec inst ispec
260
  | mem inst < T.iSpecMemorySize ispec = T.OpFail T.FailMem
261
  | dsk inst < T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
262
  | vcpus inst < T.iSpecCpuCount ispec = T.OpFail T.FailCPU
263
  | otherwise = T.OpGood ()
264

    
265
-- | Checks if an instance matches a policy.
266
instMatchesPolicy :: Instance -> T.IPolicy -> T.OpResult ()
267
instMatchesPolicy inst ipol = do
268
  instAboveISpec inst (T.iPolicyMinSpec ipol)
269
  instBelowISpec inst (T.iPolicyMaxSpec ipol)
270
  if (diskTemplate inst `elem` T.iPolicyDiskTemplates ipol)
271
    then T.OpGood ()
272
    else T.OpFail T.FailDisk
273

    
274
-- | Checks whether the instance uses a secondary node.
275
--
276
-- /Note:/ This should be reconciled with @'sNode' ==
277
-- 'Node.noSecondary'@.
278
hasSecondary :: Instance -> Bool
279
hasSecondary = (== T.DTDrbd8) . diskTemplate
280

    
281
-- | Computed the number of nodes for a given disk template.
282
requiredNodes :: T.DiskTemplate -> Int
283
requiredNodes T.DTDrbd8 = 2
284
requiredNodes _         = 1
285

    
286
-- | Computes all nodes of an instance.
287
allNodes :: Instance -> [T.Ndx]
288
allNodes inst = case diskTemplate inst of
289
                  T.DTDrbd8 -> [pNode inst, sNode inst]
290
                  _ -> [pNode inst]
291

    
292
-- | Checks whether a given disk template uses local storage.
293
usesLocalStorage :: Instance -> Bool
294
usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
295

    
296
-- | Checks whether a given disk template supported moves.
297
supportsMoves :: T.DiskTemplate -> Bool
298
supportsMoves = (`elem` movableDiskTemplates)