Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Instance.hs @ 7959cbb9

History | View | Annotate | Download (10.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 aa5b2f07 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  ) where
58 e4f08c46 Iustin Pop
59 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
60 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
61 262a08a2 Iustin Pop
62 61bbbed7 Agata Murawska
import Ganeti.HTools.Utils
63 61bbbed7 Agata Murawska
64 9188aeef Iustin Pop
-- * Type declarations
65 9188aeef Iustin Pop
66 525bfb36 Iustin Pop
-- | The instance type.
67 c352b0a9 Iustin Pop
data Instance = Instance
68 ebf38064 Iustin Pop
  { name         :: String    -- ^ The instance name
69 ebf38064 Iustin Pop
  , alias        :: String    -- ^ The shortened name
70 ebf38064 Iustin Pop
  , mem          :: Int       -- ^ Memory of the instance
71 ebf38064 Iustin Pop
  , dsk          :: Int       -- ^ Disk size of instance
72 ebf38064 Iustin Pop
  , vcpus        :: Int       -- ^ Number of VCPUs
73 ebf38064 Iustin Pop
  , runSt        :: T.InstanceStatus -- ^ Original run status
74 ebf38064 Iustin Pop
  , pNode        :: T.Ndx     -- ^ Original primary node
75 ebf38064 Iustin Pop
  , sNode        :: T.Ndx     -- ^ Original secondary node
76 ebf38064 Iustin Pop
  , idx          :: T.Idx     -- ^ Internal index
77 ebf38064 Iustin Pop
  , util         :: T.DynUtil -- ^ Dynamic resource usage
78 ebf38064 Iustin Pop
  , movable      :: Bool      -- ^ Can and should the instance be moved?
79 ebf38064 Iustin Pop
  , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
80 ebf38064 Iustin Pop
  , tags         :: [String]  -- ^ List of instance tags
81 ebf38064 Iustin Pop
  , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
82 dce9bbb3 Iustin Pop
  } deriving (Show, Read, Eq)
83 e4f08c46 Iustin Pop
84 262a08a2 Iustin Pop
instance T.Element Instance where
85 ebf38064 Iustin Pop
  nameOf   = name
86 ebf38064 Iustin Pop
  idxOf    = idx
87 ebf38064 Iustin Pop
  setAlias = setAlias
88 ebf38064 Iustin Pop
  setIdx   = setIdx
89 ebf38064 Iustin Pop
  allNames n = [name n, alias n]
90 262a08a2 Iustin Pop
91 8a8ed513 Agata Murawska
-- | Check if instance is running.
92 7959cbb9 Iustin Pop
isRunning :: Instance -> Bool
93 7959cbb9 Iustin Pop
isRunning (Instance {runSt = T.Running}) = True
94 7959cbb9 Iustin Pop
isRunning (Instance {runSt = T.ErrorUp}) = True
95 7959cbb9 Iustin Pop
isRunning _                              = False
96 a46f34d7 Iustin Pop
97 61bbbed7 Agata Murawska
-- | Check if instance is offline.
98 7959cbb9 Iustin Pop
isOffline :: Instance -> Bool
99 7959cbb9 Iustin Pop
isOffline (Instance {runSt = T.AdminOffline}) = True
100 7959cbb9 Iustin Pop
isOffline _                                   = False
101 61bbbed7 Agata Murawska
102 9cd6c325 Iustin Pop
103 9cd6c325 Iustin Pop
-- | Helper to check if the instance is not offline.
104 7959cbb9 Iustin Pop
notOffline :: Instance -> Bool
105 7959cbb9 Iustin Pop
notOffline = not . isOffline
106 9cd6c325 Iustin Pop
107 61bbbed7 Agata Murawska
-- | Check if instance is down.
108 61bbbed7 Agata Murawska
instanceDown :: Instance -> Bool
109 7959cbb9 Iustin Pop
instanceDown inst | isRunning inst = False
110 7959cbb9 Iustin Pop
instanceDown inst | isOffline inst = False
111 7959cbb9 Iustin Pop
instanceDown _                     = True
112 61bbbed7 Agata Murawska
113 61bbbed7 Agata Murawska
-- | Apply the function if the instance is online. Otherwise use
114 61bbbed7 Agata Murawska
-- the initial value
115 61bbbed7 Agata Murawska
applyIfOnline :: Instance -> (a -> a) -> a -> a
116 7959cbb9 Iustin Pop
applyIfOnline = applyIf . notOffline
117 61bbbed7 Agata Murawska
118 55bd1414 Iustin Pop
-- | Helper for determining whether an instance's memory needs to be
119 55bd1414 Iustin Pop
-- taken into account for secondary memory reservation.
120 55bd1414 Iustin Pop
usesSecMem :: Instance -> Bool
121 7959cbb9 Iustin Pop
usesSecMem inst = notOffline inst && autoBalance inst
122 55bd1414 Iustin Pop
123 8353b5e1 Iustin Pop
-- | Constant holding the local storage templates.
124 8353b5e1 Iustin Pop
--
125 8353b5e1 Iustin Pop
-- /Note:/ Currently Ganeti only exports node total/free disk space
126 8353b5e1 Iustin Pop
-- for LVM-based storage; file-based storage is ignored in this model,
127 8353b5e1 Iustin Pop
-- so even though file-based storage uses in reality disk space on the
128 8353b5e1 Iustin Pop
-- node, in our model it won't affect it and we can't compute whether
129 8353b5e1 Iustin Pop
-- there is enough disk space for a file-based instance. Therefore we
130 8353b5e1 Iustin Pop
-- will treat this template as \'foreign\' storage.
131 8353b5e1 Iustin Pop
localStorageTemplates :: [T.DiskTemplate]
132 8353b5e1 Iustin Pop
localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
133 8353b5e1 Iustin Pop
134 8353b5e1 Iustin Pop
-- | Constant holding the movable disk templates.
135 8353b5e1 Iustin Pop
--
136 8353b5e1 Iustin Pop
-- This only determines the initial 'movable' state of the
137 8353b5e1 Iustin Pop
-- instance. Further the movable state can be restricted more due to
138 8353b5e1 Iustin Pop
-- user choices, etc.
139 8353b5e1 Iustin Pop
movableDiskTemplates :: [T.DiskTemplate]
140 8353b5e1 Iustin Pop
movableDiskTemplates = [ T.DTDrbd8, T.DTBlock, T.DTSharedFile ]
141 8353b5e1 Iustin Pop
142 9188aeef Iustin Pop
-- | A simple name for the int, instance association list.
143 608efcce Iustin Pop
type AssocList = [(T.Idx, Instance)]
144 040afc35 Iustin Pop
145 9188aeef Iustin Pop
-- | A simple name for an instance map.
146 262a08a2 Iustin Pop
type List = Container.Container Instance
147 262a08a2 Iustin Pop
148 9188aeef Iustin Pop
-- * Initialization
149 9188aeef Iustin Pop
150 9188aeef Iustin Pop
-- | Create an instance.
151 9188aeef Iustin Pop
--
152 9188aeef Iustin Pop
-- Some parameters are not initialized by function, and must be set
153 9188aeef Iustin Pop
-- later (via 'setIdx' for example).
154 7dd14211 Agata Murawska
create :: String -> Int -> Int -> Int -> T.InstanceStatus
155 d25643d1 Iustin Pop
       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Instance
156 c352b0a9 Iustin Pop
create name_init mem_init dsk_init vcpus_init run_init tags_init
157 d25643d1 Iustin Pop
       auto_balance_init pn sn dt =
158 ebf38064 Iustin Pop
  Instance { name = name_init
159 ebf38064 Iustin Pop
           , alias = name_init
160 ebf38064 Iustin Pop
           , mem = mem_init
161 ebf38064 Iustin Pop
           , dsk = dsk_init
162 ebf38064 Iustin Pop
           , vcpus = vcpus_init
163 ebf38064 Iustin Pop
           , runSt = run_init
164 ebf38064 Iustin Pop
           , pNode = pn
165 ebf38064 Iustin Pop
           , sNode = sn
166 ebf38064 Iustin Pop
           , idx = -1
167 ebf38064 Iustin Pop
           , util = T.baseUtil
168 ebf38064 Iustin Pop
           , tags = tags_init
169 ebf38064 Iustin Pop
           , movable = supportsMoves dt
170 ebf38064 Iustin Pop
           , autoBalance = auto_balance_init
171 ebf38064 Iustin Pop
           , diskTemplate = dt
172 ebf38064 Iustin Pop
           }
173 e4f08c46 Iustin Pop
174 9188aeef Iustin Pop
-- | Changes the index.
175 9188aeef Iustin Pop
--
176 9188aeef Iustin Pop
-- This is used only during the building of the data structures.
177 903a7d46 Iustin Pop
setIdx :: Instance -- ^ The original instance
178 903a7d46 Iustin Pop
       -> T.Idx    -- ^ New index
179 903a7d46 Iustin Pop
       -> Instance -- ^ The modified instance
180 9188aeef Iustin Pop
setIdx t i = t { idx = i }
181 9188aeef Iustin Pop
182 9188aeef Iustin Pop
-- | Changes the name.
183 9188aeef Iustin Pop
--
184 9188aeef Iustin Pop
-- This is used only during the building of the data structures.
185 9188aeef Iustin Pop
setName :: Instance -- ^ The original instance
186 9188aeef Iustin Pop
        -> String   -- ^ New name
187 903a7d46 Iustin Pop
        -> Instance -- ^ The modified instance
188 8bcdde0c Iustin Pop
setName t s = t { name = s, alias = s }
189 8bcdde0c Iustin Pop
190 8bcdde0c Iustin Pop
-- | Changes the alias.
191 8bcdde0c Iustin Pop
--
192 8bcdde0c Iustin Pop
-- This is used only during the building of the data structures.
193 8bcdde0c Iustin Pop
setAlias :: Instance -- ^ The original instance
194 8bcdde0c Iustin Pop
         -> String   -- ^ New alias
195 8bcdde0c Iustin Pop
         -> Instance -- ^ The modified instance
196 8bcdde0c Iustin Pop
setAlias t s = t { alias = s }
197 9188aeef Iustin Pop
198 9188aeef Iustin Pop
-- * Update functions
199 9188aeef Iustin Pop
200 e4f08c46 Iustin Pop
-- | Changes the primary node of the instance.
201 fd934a28 Iustin Pop
setPri :: Instance  -- ^ the original instance
202 608efcce Iustin Pop
        -> T.Ndx    -- ^ the new primary node
203 e4f08c46 Iustin Pop
        -> Instance -- ^ the modified instance
204 2060348b Iustin Pop
setPri t p = t { pNode = p }
205 e4f08c46 Iustin Pop
206 e4f08c46 Iustin Pop
-- | Changes the secondary node of the instance.
207 fd934a28 Iustin Pop
setSec :: Instance  -- ^ the original instance
208 608efcce Iustin Pop
        -> T.Ndx    -- ^ the new secondary node
209 e4f08c46 Iustin Pop
        -> Instance -- ^ the modified instance
210 2060348b Iustin Pop
setSec t s = t { sNode = s }
211 e4f08c46 Iustin Pop
212 e4f08c46 Iustin Pop
-- | Changes both nodes of the instance.
213 fd934a28 Iustin Pop
setBoth :: Instance  -- ^ the original instance
214 608efcce Iustin Pop
         -> T.Ndx    -- ^ new primary node index
215 608efcce Iustin Pop
         -> T.Ndx    -- ^ new secondary node index
216 e4f08c46 Iustin Pop
         -> Instance -- ^ the modified instance
217 2060348b Iustin Pop
setBoth t p s = t { pNode = p, sNode = s }
218 c8db97e5 Iustin Pop
219 179c0828 Iustin Pop
-- | Sets the movable flag on an instance.
220 a182df55 Iustin Pop
setMovable :: Instance -- ^ The original instance
221 a182df55 Iustin Pop
           -> Bool     -- ^ New movable flag
222 a182df55 Iustin Pop
           -> Instance -- ^ The modified instance
223 a182df55 Iustin Pop
setMovable t m = t { movable = m }
224 a182df55 Iustin Pop
225 c8db97e5 Iustin Pop
-- | Try to shrink the instance based on the reason why we can't
226 c8db97e5 Iustin Pop
-- allocate it.
227 c8db97e5 Iustin Pop
shrinkByType :: Instance -> T.FailMode -> T.Result Instance
228 1e3dccc8 Iustin Pop
shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
229 1e3dccc8 Iustin Pop
                              in if v < T.unitMem
230 c8db97e5 Iustin Pop
                                 then T.Bad "out of memory"
231 c8db97e5 Iustin Pop
                                 else T.Ok inst { mem = v }
232 1e3dccc8 Iustin Pop
shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
233 1e3dccc8 Iustin Pop
                               in if v < T.unitDsk
234 c8db97e5 Iustin Pop
                                  then T.Bad "out of disk"
235 c8db97e5 Iustin Pop
                                  else T.Ok inst { dsk = v }
236 1e3dccc8 Iustin Pop
shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
237 1e3dccc8 Iustin Pop
                              in if v < T.unitCpu
238 c8db97e5 Iustin Pop
                                 then T.Bad "out of vcpus"
239 c8db97e5 Iustin Pop
                                 else T.Ok inst { vcpus = v }
240 c8db97e5 Iustin Pop
shrinkByType _ f = T.Bad $ "Unhandled failure mode " ++ show f
241 83ad1f3c Iustin Pop
242 83ad1f3c Iustin Pop
-- | Return the spec of an instance.
243 83ad1f3c Iustin Pop
specOf :: Instance -> T.RSpec
244 83ad1f3c Iustin Pop
specOf Instance { mem = m, dsk = d, vcpus = c } =
245 ebf38064 Iustin Pop
  T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
246 a10a476a Iustin Pop
247 aa5b2f07 Iustin Pop
-- | Checks if an instance is smaller than a given spec. Returns
248 aa5b2f07 Iustin Pop
-- OpGood for a correct spec, otherwise OpFail one of the possible
249 aa5b2f07 Iustin Pop
-- failure modes.
250 aa5b2f07 Iustin Pop
instBelowISpec :: Instance -> T.ISpec -> T.OpResult ()
251 aa5b2f07 Iustin Pop
instBelowISpec inst ispec
252 aa5b2f07 Iustin Pop
  | mem inst > T.iSpecMemorySize ispec = T.OpFail T.FailMem
253 aa5b2f07 Iustin Pop
  | dsk inst > T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
254 aa5b2f07 Iustin Pop
  | vcpus inst > T.iSpecCpuCount ispec = T.OpFail T.FailCPU
255 aa5b2f07 Iustin Pop
  | otherwise = T.OpGood ()
256 aa5b2f07 Iustin Pop
257 aa5b2f07 Iustin Pop
-- | Checks if an instance is bigger than a given spec.
258 aa5b2f07 Iustin Pop
instAboveISpec :: Instance -> T.ISpec -> T.OpResult ()
259 aa5b2f07 Iustin Pop
instAboveISpec inst ispec
260 aa5b2f07 Iustin Pop
  | mem inst < T.iSpecMemorySize ispec = T.OpFail T.FailMem
261 aa5b2f07 Iustin Pop
  | dsk inst < T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
262 aa5b2f07 Iustin Pop
  | vcpus inst < T.iSpecCpuCount ispec = T.OpFail T.FailCPU
263 aa5b2f07 Iustin Pop
  | otherwise = T.OpGood ()
264 aa5b2f07 Iustin Pop
265 aa5b2f07 Iustin Pop
-- | Checks if an instance matches a policy.
266 aa5b2f07 Iustin Pop
instMatchesPolicy :: Instance -> T.IPolicy -> T.OpResult ()
267 aa5b2f07 Iustin Pop
instMatchesPolicy inst ipol = do
268 aa5b2f07 Iustin Pop
  instAboveISpec inst (T.iPolicyMinSpec ipol)
269 aa5b2f07 Iustin Pop
  instBelowISpec inst (T.iPolicyMaxSpec ipol)
270 aa5b2f07 Iustin Pop
  if (diskTemplate inst `elem` T.iPolicyDiskTemplates ipol)
271 aa5b2f07 Iustin Pop
    then T.OpGood ()
272 aa5b2f07 Iustin Pop
    else T.OpFail T.FailDisk
273 aa5b2f07 Iustin Pop
274 8353b5e1 Iustin Pop
-- | Checks whether the instance uses a secondary node.
275 8353b5e1 Iustin Pop
--
276 8353b5e1 Iustin Pop
-- /Note:/ This should be reconciled with @'sNode' ==
277 8353b5e1 Iustin Pop
-- 'Node.noSecondary'@.
278 8353b5e1 Iustin Pop
hasSecondary :: Instance -> Bool
279 8353b5e1 Iustin Pop
hasSecondary = (== T.DTDrbd8) . diskTemplate
280 8353b5e1 Iustin Pop
281 179c0828 Iustin Pop
-- | Computed the number of nodes for a given disk template.
282 a10a476a Iustin Pop
requiredNodes :: T.DiskTemplate -> Int
283 a10a476a Iustin Pop
requiredNodes T.DTDrbd8 = 2
284 a10a476a Iustin Pop
requiredNodes _         = 1
285 d254d6ce Iustin Pop
286 d254d6ce Iustin Pop
-- | Computes all nodes of an instance.
287 d254d6ce Iustin Pop
allNodes :: Instance -> [T.Ndx]
288 d254d6ce Iustin Pop
allNodes inst = case diskTemplate inst of
289 d254d6ce Iustin Pop
                  T.DTDrbd8 -> [pNode inst, sNode inst]
290 d254d6ce Iustin Pop
                  _ -> [pNode inst]
291 8353b5e1 Iustin Pop
292 8353b5e1 Iustin Pop
-- | Checks whether a given disk template uses local storage.
293 8353b5e1 Iustin Pop
usesLocalStorage :: Instance -> Bool
294 8353b5e1 Iustin Pop
usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
295 8353b5e1 Iustin Pop
296 8353b5e1 Iustin Pop
-- | Checks whether a given disk template supported moves.
297 8353b5e1 Iustin Pop
supportsMoves :: T.DiskTemplate -> Bool
298 8353b5e1 Iustin Pop
supportsMoves = (`elem` movableDiskTemplates)