Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Instance.hs @ 8353b5e1

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