Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Instance.hs @ a46f34d7

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