Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.6 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 a10a476a Iustin Pop
    , requiredNodes
45 d254d6ce Iustin Pop
    , allNodes
46 181d4e04 Iustin Pop
    ) where
47 e4f08c46 Iustin Pop
48 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
49 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
50 e82271f8 Iustin Pop
import qualified Ganeti.Constants as C
51 262a08a2 Iustin Pop
52 9188aeef Iustin Pop
-- * Type declarations
53 9188aeef Iustin Pop
54 525bfb36 Iustin Pop
-- | The instance type.
55 c352b0a9 Iustin Pop
data Instance = Instance
56 c352b0a9 Iustin Pop
    { name         :: String    -- ^ The instance name
57 c352b0a9 Iustin Pop
    , alias        :: String    -- ^ The shortened name
58 c352b0a9 Iustin Pop
    , mem          :: Int       -- ^ Memory of the instance
59 c352b0a9 Iustin Pop
    , dsk          :: Int       -- ^ Disk size of instance
60 c352b0a9 Iustin Pop
    , vcpus        :: Int       -- ^ Number of VCPUs
61 c352b0a9 Iustin Pop
    , running      :: Bool      -- ^ Is the instance running?
62 c352b0a9 Iustin Pop
    , runSt        :: String    -- ^ Original (text) run status
63 c352b0a9 Iustin Pop
    , pNode        :: T.Ndx     -- ^ Original primary node
64 c352b0a9 Iustin Pop
    , sNode        :: T.Ndx     -- ^ Original secondary node
65 c352b0a9 Iustin Pop
    , idx          :: T.Idx     -- ^ Internal index
66 c352b0a9 Iustin Pop
    , util         :: T.DynUtil -- ^ Dynamic resource usage
67 c352b0a9 Iustin Pop
    , movable      :: Bool      -- ^ Can the instance be moved?
68 0e09422b Iustin Pop
    , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
69 c352b0a9 Iustin Pop
    , tags         :: [String]  -- ^ List of instance tags
70 d25643d1 Iustin Pop
    , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
71 c352b0a9 Iustin Pop
    } deriving (Show, Read)
72 e4f08c46 Iustin Pop
73 262a08a2 Iustin Pop
instance T.Element Instance where
74 3e4480e0 Iustin Pop
    nameOf   = name
75 3e4480e0 Iustin Pop
    idxOf    = idx
76 3e4480e0 Iustin Pop
    setAlias = setAlias
77 3e4480e0 Iustin Pop
    setIdx   = setIdx
78 c854092b Iustin Pop
    allNames n = [name n, alias n]
79 262a08a2 Iustin Pop
80 525bfb36 Iustin Pop
-- | Constant holding the running instance states.
81 a46f34d7 Iustin Pop
runningStates :: [String]
82 e82271f8 Iustin Pop
runningStates = [C.inststRunning, C.inststErrorup]
83 a46f34d7 Iustin Pop
84 9188aeef Iustin Pop
-- | A simple name for the int, instance association list.
85 608efcce Iustin Pop
type AssocList = [(T.Idx, Instance)]
86 040afc35 Iustin Pop
87 9188aeef Iustin Pop
-- | A simple name for an instance map.
88 262a08a2 Iustin Pop
type List = Container.Container Instance
89 262a08a2 Iustin Pop
90 9188aeef Iustin Pop
-- * Initialization
91 9188aeef Iustin Pop
92 9188aeef Iustin Pop
-- | Create an instance.
93 9188aeef Iustin Pop
--
94 9188aeef Iustin Pop
-- Some parameters are not initialized by function, and must be set
95 9188aeef Iustin Pop
-- later (via 'setIdx' for example).
96 17e7af2b Iustin Pop
create :: String -> Int -> Int -> Int -> String
97 d25643d1 Iustin Pop
       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Instance
98 c352b0a9 Iustin Pop
create name_init mem_init dsk_init vcpus_init run_init tags_init
99 d25643d1 Iustin Pop
       auto_balance_init pn sn dt =
100 2180829f Iustin Pop
    Instance { name = name_init
101 8bcdde0c Iustin Pop
             , alias = name_init
102 2180829f Iustin Pop
             , mem = mem_init
103 2180829f Iustin Pop
             , dsk = dsk_init
104 2180829f Iustin Pop
             , vcpus = vcpus_init
105 a46f34d7 Iustin Pop
             , running = run_init `elem` runningStates
106 2180829f Iustin Pop
             , runSt = run_init
107 2180829f Iustin Pop
             , pNode = pn
108 2180829f Iustin Pop
             , sNode = sn
109 2180829f Iustin Pop
             , idx = -1
110 a7a8f280 Iustin Pop
             , util = T.baseUtil
111 17e7af2b Iustin Pop
             , tags = tags_init
112 a182df55 Iustin Pop
             , movable = True
113 0e09422b Iustin Pop
             , autoBalance = auto_balance_init
114 d25643d1 Iustin Pop
             , diskTemplate = dt
115 2180829f Iustin Pop
             }
116 e4f08c46 Iustin Pop
117 9188aeef Iustin Pop
-- | Changes the index.
118 9188aeef Iustin Pop
--
119 9188aeef Iustin Pop
-- This is used only during the building of the data structures.
120 903a7d46 Iustin Pop
setIdx :: Instance -- ^ The original instance
121 903a7d46 Iustin Pop
       -> T.Idx    -- ^ New index
122 903a7d46 Iustin Pop
       -> Instance -- ^ The modified instance
123 9188aeef Iustin Pop
setIdx t i = t { idx = i }
124 9188aeef Iustin Pop
125 9188aeef Iustin Pop
-- | Changes the name.
126 9188aeef Iustin Pop
--
127 9188aeef Iustin Pop
-- This is used only during the building of the data structures.
128 9188aeef Iustin Pop
setName :: Instance -- ^ The original instance
129 9188aeef Iustin Pop
        -> String   -- ^ New name
130 903a7d46 Iustin Pop
        -> Instance -- ^ The modified instance
131 8bcdde0c Iustin Pop
setName t s = t { name = s, alias = s }
132 8bcdde0c Iustin Pop
133 8bcdde0c Iustin Pop
-- | Changes the alias.
134 8bcdde0c Iustin Pop
--
135 8bcdde0c Iustin Pop
-- This is used only during the building of the data structures.
136 8bcdde0c Iustin Pop
setAlias :: Instance -- ^ The original instance
137 8bcdde0c Iustin Pop
         -> String   -- ^ New alias
138 8bcdde0c Iustin Pop
         -> Instance -- ^ The modified instance
139 8bcdde0c Iustin Pop
setAlias t s = t { alias = s }
140 9188aeef Iustin Pop
141 9188aeef Iustin Pop
-- * Update functions
142 9188aeef Iustin Pop
143 e4f08c46 Iustin Pop
-- | Changes the primary node of the instance.
144 fd934a28 Iustin Pop
setPri :: Instance  -- ^ the original instance
145 608efcce Iustin Pop
        -> T.Ndx    -- ^ the new primary node
146 e4f08c46 Iustin Pop
        -> Instance -- ^ the modified instance
147 2060348b Iustin Pop
setPri t p = t { pNode = p }
148 e4f08c46 Iustin Pop
149 e4f08c46 Iustin Pop
-- | Changes the secondary node of the instance.
150 fd934a28 Iustin Pop
setSec :: Instance  -- ^ the original instance
151 608efcce Iustin Pop
        -> T.Ndx    -- ^ the new secondary node
152 e4f08c46 Iustin Pop
        -> Instance -- ^ the modified instance
153 2060348b Iustin Pop
setSec t s = t { sNode = s }
154 e4f08c46 Iustin Pop
155 e4f08c46 Iustin Pop
-- | Changes both nodes of the instance.
156 fd934a28 Iustin Pop
setBoth :: Instance  -- ^ the original instance
157 608efcce Iustin Pop
         -> T.Ndx    -- ^ new primary node index
158 608efcce Iustin Pop
         -> T.Ndx    -- ^ new secondary node index
159 e4f08c46 Iustin Pop
         -> Instance -- ^ the modified instance
160 2060348b Iustin Pop
setBoth t p s = t { pNode = p, sNode = s }
161 c8db97e5 Iustin Pop
162 a182df55 Iustin Pop
setMovable :: Instance -- ^ The original instance
163 a182df55 Iustin Pop
           -> Bool     -- ^ New movable flag
164 a182df55 Iustin Pop
           -> Instance -- ^ The modified instance
165 a182df55 Iustin Pop
setMovable t m = t { movable = m }
166 a182df55 Iustin Pop
167 c8db97e5 Iustin Pop
-- | Try to shrink the instance based on the reason why we can't
168 c8db97e5 Iustin Pop
-- allocate it.
169 c8db97e5 Iustin Pop
shrinkByType :: Instance -> T.FailMode -> T.Result Instance
170 1e3dccc8 Iustin Pop
shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
171 1e3dccc8 Iustin Pop
                              in if v < T.unitMem
172 c8db97e5 Iustin Pop
                                 then T.Bad "out of memory"
173 c8db97e5 Iustin Pop
                                 else T.Ok inst { mem = v }
174 1e3dccc8 Iustin Pop
shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
175 1e3dccc8 Iustin Pop
                               in if v < T.unitDsk
176 c8db97e5 Iustin Pop
                                  then T.Bad "out of disk"
177 c8db97e5 Iustin Pop
                                  else T.Ok inst { dsk = v }
178 1e3dccc8 Iustin Pop
shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
179 1e3dccc8 Iustin Pop
                              in if v < T.unitCpu
180 c8db97e5 Iustin Pop
                                 then T.Bad "out of vcpus"
181 c8db97e5 Iustin Pop
                                 else T.Ok inst { vcpus = v }
182 c8db97e5 Iustin Pop
shrinkByType _ f = T.Bad $ "Unhandled failure mode " ++ show f
183 83ad1f3c Iustin Pop
184 83ad1f3c Iustin Pop
-- | Return the spec of an instance.
185 83ad1f3c Iustin Pop
specOf :: Instance -> T.RSpec
186 83ad1f3c Iustin Pop
specOf Instance { mem = m, dsk = d, vcpus = c } =
187 83ad1f3c Iustin Pop
    T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
188 a10a476a Iustin Pop
189 a10a476a Iustin Pop
-- | Computed the number of nodes for a given disk template
190 a10a476a Iustin Pop
requiredNodes :: T.DiskTemplate -> Int
191 a10a476a Iustin Pop
requiredNodes T.DTDrbd8 = 2
192 a10a476a Iustin Pop
requiredNodes _         = 1
193 d254d6ce Iustin Pop
194 d254d6ce Iustin Pop
-- | Computes all nodes of an instance.
195 d254d6ce Iustin Pop
allNodes :: Instance -> [T.Ndx]
196 d254d6ce Iustin Pop
allNodes inst = case diskTemplate inst of
197 d254d6ce Iustin Pop
                  T.DTDrbd8 -> [pNode inst, sNode inst]
198 d254d6ce Iustin Pop
                  _ -> [pNode inst]