Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Instance.hs @ d6c76bd5

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