Statistics
| Branch: | Tag: | Revision:

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

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