Statistics
| Branch: | Tag: | Revision:

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

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