Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Instance.hs @ ebf38064

History | View | Annotate | Download (8.7 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 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
  , instanceDown
37
  , applyIfOnline
38
  , setIdx
39
  , setName
40
  , setAlias
41
  , setPri
42
  , setSec
43
  , setBoth
44
  , setMovable
45
  , specOf
46
  , shrinkByType
47
  , localStorageTemplates
48
  , hasSecondary
49
  , requiredNodes
50
  , allNodes
51
  , usesLocalStorage
52
  ) where
53

    
54
import qualified Ganeti.HTools.Types as T
55
import qualified Ganeti.HTools.Container as Container
56
import qualified Ganeti.Constants as C
57

    
58
import Ganeti.HTools.Utils
59

    
60
-- * Type declarations
61

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

    
80
instance T.Element Instance where
81
  nameOf   = name
82
  idxOf    = idx
83
  setAlias = setAlias
84
  setIdx   = setIdx
85
  allNames n = [name n, alias n]
86

    
87
-- | Check if instance is running.
88
instanceRunning :: Instance -> Bool
89
instanceRunning (Instance {runSt = T.Running}) = True
90
instanceRunning (Instance {runSt = T.ErrorUp}) = True
91
instanceRunning _                              = False
92

    
93
-- | Check if instance is offline.
94
instanceOffline :: Instance -> Bool
95
instanceOffline (Instance {runSt = T.AdminOffline}) = True
96
instanceOffline _                                   = False
97

    
98
-- | Check if instance is down.
99
instanceDown :: Instance -> Bool
100
instanceDown inst | instanceRunning inst = False
101
instanceDown inst | instanceOffline inst = False
102
instanceDown _                           = True
103

    
104
-- | Apply the function if the instance is online. Otherwise use
105
-- the initial value
106
applyIfOnline :: Instance -> (a -> a) -> a -> a
107
applyIfOnline = applyIf . not . instanceOffline
108

    
109
-- | Constant holding the local storage templates.
110
--
111
-- /Note:/ Currently Ganeti only exports node total/free disk space
112
-- for LVM-based storage; file-based storage is ignored in this model,
113
-- so even though file-based storage uses in reality disk space on the
114
-- node, in our model it won't affect it and we can't compute whether
115
-- there is enough disk space for a file-based instance. Therefore we
116
-- will treat this template as \'foreign\' storage.
117
localStorageTemplates :: [T.DiskTemplate]
118
localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
119

    
120
-- | Constant holding the movable disk templates.
121
--
122
-- This only determines the initial 'movable' state of the
123
-- instance. Further the movable state can be restricted more due to
124
-- user choices, etc.
125
movableDiskTemplates :: [T.DiskTemplate]
126
movableDiskTemplates = [ T.DTDrbd8, T.DTBlock, T.DTSharedFile ]
127

    
128
-- | A simple name for the int, instance association list.
129
type AssocList = [(T.Idx, Instance)]
130

    
131
-- | A simple name for an instance map.
132
type List = Container.Container Instance
133

    
134
-- * Initialization
135

    
136
-- | Create an instance.
137
--
138
-- Some parameters are not initialized by function, and must be set
139
-- later (via 'setIdx' for example).
140
create :: String -> Int -> Int -> Int -> T.InstanceStatus
141
       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Instance
142
create name_init mem_init dsk_init vcpus_init run_init tags_init
143
       auto_balance_init pn sn dt =
144
  Instance { name = name_init
145
           , alias = name_init
146
           , mem = mem_init
147
           , dsk = dsk_init
148
           , vcpus = vcpus_init
149
           , runSt = run_init
150
           , pNode = pn
151
           , sNode = sn
152
           , idx = -1
153
           , util = T.baseUtil
154
           , tags = tags_init
155
           , movable = supportsMoves dt
156
           , autoBalance = auto_balance_init
157
           , diskTemplate = dt
158
           }
159

    
160
-- | Changes the index.
161
--
162
-- This is used only during the building of the data structures.
163
setIdx :: Instance -- ^ The original instance
164
       -> T.Idx    -- ^ New index
165
       -> Instance -- ^ The modified instance
166
setIdx t i = t { idx = i }
167

    
168
-- | Changes the name.
169
--
170
-- This is used only during the building of the data structures.
171
setName :: Instance -- ^ The original instance
172
        -> String   -- ^ New name
173
        -> Instance -- ^ The modified instance
174
setName t s = t { name = s, alias = s }
175

    
176
-- | Changes the alias.
177
--
178
-- This is used only during the building of the data structures.
179
setAlias :: Instance -- ^ The original instance
180
         -> String   -- ^ New alias
181
         -> Instance -- ^ The modified instance
182
setAlias t s = t { alias = s }
183

    
184
-- * Update functions
185

    
186
-- | Changes the primary node of the instance.
187
setPri :: Instance  -- ^ the original instance
188
        -> T.Ndx    -- ^ the new primary node
189
        -> Instance -- ^ the modified instance
190
setPri t p = t { pNode = p }
191

    
192
-- | Changes the secondary node of the instance.
193
setSec :: Instance  -- ^ the original instance
194
        -> T.Ndx    -- ^ the new secondary node
195
        -> Instance -- ^ the modified instance
196
setSec t s = t { sNode = s }
197

    
198
-- | Changes both nodes of the instance.
199
setBoth :: Instance  -- ^ the original instance
200
         -> T.Ndx    -- ^ new primary node index
201
         -> T.Ndx    -- ^ new secondary node index
202
         -> Instance -- ^ the modified instance
203
setBoth t p s = t { pNode = p, sNode = s }
204

    
205
-- | Sets the movable flag on an instance.
206
setMovable :: Instance -- ^ The original instance
207
           -> Bool     -- ^ New movable flag
208
           -> Instance -- ^ The modified instance
209
setMovable t m = t { movable = m }
210

    
211
-- | Try to shrink the instance based on the reason why we can't
212
-- allocate it.
213
shrinkByType :: Instance -> T.FailMode -> T.Result Instance
214
shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
215
                              in if v < T.unitMem
216
                                 then T.Bad "out of memory"
217
                                 else T.Ok inst { mem = v }
218
shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
219
                               in if v < T.unitDsk
220
                                  then T.Bad "out of disk"
221
                                  else T.Ok inst { dsk = v }
222
shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
223
                              in if v < T.unitCpu
224
                                 then T.Bad "out of vcpus"
225
                                 else T.Ok inst { vcpus = v }
226
shrinkByType _ f = T.Bad $ "Unhandled failure mode " ++ show f
227

    
228
-- | Return the spec of an instance.
229
specOf :: Instance -> T.RSpec
230
specOf Instance { mem = m, dsk = d, vcpus = c } =
231
  T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
232

    
233
-- | Checks whether the instance uses a secondary node.
234
--
235
-- /Note:/ This should be reconciled with @'sNode' ==
236
-- 'Node.noSecondary'@.
237
hasSecondary :: Instance -> Bool
238
hasSecondary = (== T.DTDrbd8) . diskTemplate
239

    
240
-- | Computed the number of nodes for a given disk template.
241
requiredNodes :: T.DiskTemplate -> Int
242
requiredNodes T.DTDrbd8 = 2
243
requiredNodes _         = 1
244

    
245
-- | Computes all nodes of an instance.
246
allNodes :: Instance -> [T.Ndx]
247
allNodes inst = case diskTemplate inst of
248
                  T.DTDrbd8 -> [pNode inst, sNode inst]
249
                  _ -> [pNode inst]
250

    
251
-- | Checks whether a given disk template uses local storage.
252
usesLocalStorage :: Instance -> Bool
253
usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
254

    
255
-- | Checks whether a given disk template supported moves.
256
supportsMoves :: T.DiskTemplate -> Bool
257
supportsMoves = (`elem` movableDiskTemplates)