Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Instance.hs @ 7c14b50a

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