Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ 8bcdde0c

History | View | Annotate | Download (17.2 kB)

1 e4f08c46 Iustin Pop
{-| Module describing a node.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
    All updates are functional (copy-based) and return a new node with
4 e4f08c46 Iustin Pop
    updated value.
5 e4f08c46 Iustin Pop
-}
6 e4f08c46 Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 669d7e3d Iustin Pop
module Ganeti.HTools.Node
29 aa8d2e71 Iustin Pop
    ( Node(..)
30 262a08a2 Iustin Pop
    , List
31 e4f08c46 Iustin Pop
    -- * Constructor
32 e4f08c46 Iustin Pop
    , create
33 e4f08c46 Iustin Pop
    -- ** Finalization after data loading
34 e4f08c46 Iustin Pop
    , buildPeers
35 e4f08c46 Iustin Pop
    , setIdx
36 497e30a1 Iustin Pop
    , setName
37 8bcdde0c Iustin Pop
    , setAlias
38 c2c1ef0c Iustin Pop
    , setOffline
39 8c5b0a0d Iustin Pop
    , setXmem
40 53f00b20 Iustin Pop
    , setFmem
41 9188aeef Iustin Pop
    , setPri
42 9188aeef Iustin Pop
    , setSec
43 844eff86 Iustin Pop
    , setMdsk
44 844eff86 Iustin Pop
    , setMcpu
45 1e3dccc8 Iustin Pop
    -- * Tag maps
46 1e3dccc8 Iustin Pop
    , addTags
47 1e3dccc8 Iustin Pop
    , delTags
48 1e3dccc8 Iustin Pop
    , rejectAddTags
49 e4f08c46 Iustin Pop
    -- * Instance (re)location
50 e4f08c46 Iustin Pop
    , removePri
51 e4f08c46 Iustin Pop
    , removeSec
52 e4f08c46 Iustin Pop
    , addPri
53 e4f08c46 Iustin Pop
    , addSec
54 fe3d6f02 Iustin Pop
    -- * Stats
55 fe3d6f02 Iustin Pop
    , availDisk
56 1e3dccc8 Iustin Pop
    , availMem
57 1e3dccc8 Iustin Pop
    , availCpu
58 1e4b5230 Iustin Pop
    , conflictingPrimaries
59 e4f08c46 Iustin Pop
    -- * Formatting
60 76354e11 Iustin Pop
    , defaultFields
61 76354e11 Iustin Pop
    , showHeader
62 76354e11 Iustin Pop
    , showField
63 e4f08c46 Iustin Pop
    , list
64 040afc35 Iustin Pop
    -- * Misc stuff
65 040afc35 Iustin Pop
    , AssocList
66 1fe81531 Iustin Pop
    , AllocElement
67 040afc35 Iustin Pop
    , noSecondary
68 e4f08c46 Iustin Pop
    ) where
69 e4f08c46 Iustin Pop
70 e4f08c46 Iustin Pop
import Data.List
71 5f0b9579 Iustin Pop
import qualified Data.Map as Map
72 1e4b5230 Iustin Pop
import qualified Data.Foldable as Foldable
73 e4f08c46 Iustin Pop
import Text.Printf (printf)
74 e4f08c46 Iustin Pop
75 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
76 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
77 12e6776a Iustin Pop
import qualified Ganeti.HTools.PeerMap as P
78 e4f08c46 Iustin Pop
79 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
80 262a08a2 Iustin Pop
81 9188aeef Iustin Pop
-- * Type declarations
82 9188aeef Iustin Pop
83 5f0b9579 Iustin Pop
-- | The tag map type
84 5f0b9579 Iustin Pop
type TagMap = Map.Map String Int
85 5f0b9579 Iustin Pop
86 9188aeef Iustin Pop
-- | The node type.
87 12e6776a Iustin Pop
data Node = Node
88 12e6776a Iustin Pop
    { name     :: String    -- ^ The node name
89 8bcdde0c Iustin Pop
    , alias    :: String    -- ^ The shortened name (for display purposes)
90 12e6776a Iustin Pop
    , tMem     :: Double    -- ^ Total memory (MiB)
91 12e6776a Iustin Pop
    , nMem     :: Int       -- ^ Node memory (MiB)
92 12e6776a Iustin Pop
    , fMem     :: Int       -- ^ Free memory (MiB)
93 12e6776a Iustin Pop
    , xMem     :: Int       -- ^ Unaccounted memory (MiB)
94 12e6776a Iustin Pop
    , tDsk     :: Double    -- ^ Total disk space (MiB)
95 12e6776a Iustin Pop
    , fDsk     :: Int       -- ^ Free disk space (MiB)
96 12e6776a Iustin Pop
    , tCpu     :: Double    -- ^ Total CPU count
97 12e6776a Iustin Pop
    , uCpu     :: Int       -- ^ Used VCPU count
98 12e6776a Iustin Pop
    , pList    :: [T.Idx]   -- ^ List of primary instance indices
99 12e6776a Iustin Pop
    , sList    :: [T.Idx]   -- ^ List of secondary instance indices
100 12e6776a Iustin Pop
    , idx      :: T.Ndx     -- ^ Internal index for book-keeping
101 12e6776a Iustin Pop
    , peers    :: P.PeerMap -- ^ Pnode to instance mapping
102 12e6776a Iustin Pop
    , failN1   :: Bool      -- ^ Whether the node has failed n1
103 12e6776a Iustin Pop
    , rMem     :: Int       -- ^ Maximum memory needed for failover by
104 12e6776a Iustin Pop
                            -- primaries of this node
105 12e6776a Iustin Pop
    , pMem     :: Double    -- ^ Percent of free memory
106 12e6776a Iustin Pop
    , pDsk     :: Double    -- ^ Percent of free disk
107 12e6776a Iustin Pop
    , pRem     :: Double    -- ^ Percent of reserved memory
108 12e6776a Iustin Pop
    , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
109 12e6776a Iustin Pop
    , mDsk     :: Double    -- ^ Minimum free disk ratio
110 12e6776a Iustin Pop
    , mCpu     :: Double    -- ^ Max ratio of virt-to-phys CPUs
111 12e6776a Iustin Pop
    , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
112 12e6776a Iustin Pop
                            -- threshold
113 12e6776a Iustin Pop
    , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
114 12e6776a Iustin Pop
                            -- threshold
115 12e6776a Iustin Pop
    , offline  :: Bool      -- ^ Whether the node should not be used
116 12e6776a Iustin Pop
                            -- for allocations and skipped from score
117 12e6776a Iustin Pop
                            -- computations
118 12e6776a Iustin Pop
    , utilPool :: T.DynUtil -- ^ Total utilisation capacity
119 12e6776a Iustin Pop
    , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
120 5f0b9579 Iustin Pop
    , pTags    :: TagMap    -- ^ Map of primary instance tags and their count
121 12e6776a Iustin Pop
    } deriving (Show)
122 e4f08c46 Iustin Pop
123 262a08a2 Iustin Pop
instance T.Element Node where
124 262a08a2 Iustin Pop
    nameOf = name
125 262a08a2 Iustin Pop
    idxOf = idx
126 262a08a2 Iustin Pop
    setName = setName
127 262a08a2 Iustin Pop
    setIdx = setIdx
128 262a08a2 Iustin Pop
129 9188aeef Iustin Pop
-- | A simple name for the int, node association list.
130 608efcce Iustin Pop
type AssocList = [(T.Ndx, Node)]
131 040afc35 Iustin Pop
132 9188aeef Iustin Pop
-- | A simple name for a node map.
133 262a08a2 Iustin Pop
type List = Container.Container Node
134 262a08a2 Iustin Pop
135 1fe81531 Iustin Pop
-- | A simple name for an allocation element (here just for logistic
136 1fe81531 Iustin Pop
-- reasons)
137 1fe81531 Iustin Pop
type AllocElement = (List, Instance.Instance, [Node])
138 1fe81531 Iustin Pop
139 9188aeef Iustin Pop
-- | Constant node index for a non-moveable instance.
140 608efcce Iustin Pop
noSecondary :: T.Ndx
141 040afc35 Iustin Pop
noSecondary = -1
142 040afc35 Iustin Pop
143 5f0b9579 Iustin Pop
-- * Helper functions
144 5f0b9579 Iustin Pop
145 5f0b9579 Iustin Pop
-- | Add a tag to a tagmap
146 5f0b9579 Iustin Pop
addTag :: TagMap -> String -> TagMap
147 5f0b9579 Iustin Pop
addTag t s = Map.insertWith (+) s 1 t
148 5f0b9579 Iustin Pop
149 5f0b9579 Iustin Pop
-- | Add multiple tags
150 5f0b9579 Iustin Pop
addTags :: TagMap -> [String] -> TagMap
151 5f0b9579 Iustin Pop
addTags = foldl' addTag
152 5f0b9579 Iustin Pop
153 5f0b9579 Iustin Pop
-- | Adjust or delete a tag from a tagmap
154 5f0b9579 Iustin Pop
delTag :: TagMap -> String -> TagMap
155 5f0b9579 Iustin Pop
delTag t s = Map.update (\v -> if v > 1
156 5f0b9579 Iustin Pop
                               then Just (v-1)
157 5f0b9579 Iustin Pop
                               else Nothing)
158 5f0b9579 Iustin Pop
             s t
159 5f0b9579 Iustin Pop
160 5f0b9579 Iustin Pop
-- | Remove multiple tags
161 5f0b9579 Iustin Pop
delTags :: TagMap -> [String] -> TagMap
162 5f0b9579 Iustin Pop
delTags = foldl' delTag
163 5f0b9579 Iustin Pop
164 5f0b9579 Iustin Pop
-- | Check if we can add a list of tags to a tagmap
165 5f0b9579 Iustin Pop
rejectAddTags :: TagMap -> [String] -> Bool
166 5182e970 Iustin Pop
rejectAddTags t = any (`Map.member` t)
167 5f0b9579 Iustin Pop
168 1e4b5230 Iustin Pop
-- | Check how many primary instances have conflicting tags. The
169 1e4b5230 Iustin Pop
-- algorithm to compute this is to sum the count of all tags, then
170 1e4b5230 Iustin Pop
-- subtract the size of the tag map (since each tag has at least one,
171 1e4b5230 Iustin Pop
-- non-conflicting instance); this is equivalent to summing the
172 1e4b5230 Iustin Pop
-- values in the tag map minus one.
173 1e4b5230 Iustin Pop
conflictingPrimaries :: Node -> Int
174 1e4b5230 Iustin Pop
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
175 1e4b5230 Iustin Pop
176 9188aeef Iustin Pop
-- * Initialization functions
177 e4f08c46 Iustin Pop
178 9188aeef Iustin Pop
-- | Create a new node.
179 9188aeef Iustin Pop
--
180 9188aeef Iustin Pop
-- The index and the peers maps are empty, and will be need to be
181 9188aeef Iustin Pop
-- update later via the 'setIdx' and 'buildPeers' functions.
182 1a82215d Iustin Pop
create :: String -> Double -> Int -> Int -> Double
183 1a82215d Iustin Pop
       -> Int -> Double -> Bool -> Node
184 2727257a Iustin Pop
create name_init mem_t_init mem_n_init mem_f_init
185 1a82215d Iustin Pop
       dsk_t_init dsk_f_init cpu_t_init offline_init =
186 8bcdde0c Iustin Pop
    Node { name = name_init
187 8bcdde0c Iustin Pop
         , alias = name_init
188 2180829f Iustin Pop
         , tMem = mem_t_init
189 2180829f Iustin Pop
         , nMem = mem_n_init
190 2180829f Iustin Pop
         , fMem = mem_f_init
191 2180829f Iustin Pop
         , tDsk = dsk_t_init
192 2180829f Iustin Pop
         , fDsk = dsk_f_init
193 2180829f Iustin Pop
         , tCpu = cpu_t_init
194 2180829f Iustin Pop
         , uCpu = 0
195 2180829f Iustin Pop
         , pList = []
196 2180829f Iustin Pop
         , sList = []
197 2180829f Iustin Pop
         , failN1 = True
198 2180829f Iustin Pop
         , idx = -1
199 12e6776a Iustin Pop
         , peers = P.empty
200 2180829f Iustin Pop
         , rMem = 0
201 2180829f Iustin Pop
         , pMem = fromIntegral mem_f_init / mem_t_init
202 2180829f Iustin Pop
         , pDsk = fromIntegral dsk_f_init / dsk_t_init
203 2180829f Iustin Pop
         , pRem = 0
204 2180829f Iustin Pop
         , pCpu = 0
205 2180829f Iustin Pop
         , offline = offline_init
206 2180829f Iustin Pop
         , xMem = 0
207 f4c0b8c5 Iustin Pop
         , mDsk = T.defReservedDiskRatio
208 f4c0b8c5 Iustin Pop
         , mCpu = T.defVcpuRatio
209 f4c0b8c5 Iustin Pop
         , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
210 f4c0b8c5 Iustin Pop
         , hiCpu = mCpuTohiCpu T.defVcpuRatio cpu_t_init
211 ee9724b9 Iustin Pop
         , utilPool = T.baseUtil
212 2180829f Iustin Pop
         , utilLoad = T.zeroUtil
213 5f0b9579 Iustin Pop
         , pTags = Map.empty
214 2180829f Iustin Pop
         }
215 e4f08c46 Iustin Pop
216 3ed46bb7 Iustin Pop
-- | Conversion formula from mDsk\/tDsk to loDsk
217 f4c0b8c5 Iustin Pop
mDskToloDsk :: Double -> Double -> Int
218 f4c0b8c5 Iustin Pop
mDskToloDsk mval tdsk = floor (mval * tdsk)
219 f4c0b8c5 Iustin Pop
220 3ed46bb7 Iustin Pop
-- | Conversion formula from mCpu\/tCpu to hiCpu
221 f4c0b8c5 Iustin Pop
mCpuTohiCpu :: Double -> Double -> Int
222 f4c0b8c5 Iustin Pop
mCpuTohiCpu mval tcpu = floor (mval * tcpu)
223 f4c0b8c5 Iustin Pop
224 e4f08c46 Iustin Pop
-- | Changes the index.
225 9188aeef Iustin Pop
--
226 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
227 608efcce Iustin Pop
setIdx :: Node -> T.Ndx -> Node
228 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
229 e4f08c46 Iustin Pop
230 9188aeef Iustin Pop
-- | Changes the name.
231 9188aeef Iustin Pop
--
232 497e30a1 Iustin Pop
-- This is used only during the building of the data structures.
233 9188aeef Iustin Pop
setName :: Node -> String -> Node
234 8bcdde0c Iustin Pop
setName t s = t { name = s, alias = s }
235 8bcdde0c Iustin Pop
236 8bcdde0c Iustin Pop
-- | Changes the alias.
237 8bcdde0c Iustin Pop
--
238 8bcdde0c Iustin Pop
-- This is used only during the building of the data structures.
239 8bcdde0c Iustin Pop
setAlias :: Node -> String -> Node
240 8bcdde0c Iustin Pop
setAlias t s = t { alias = s }
241 497e30a1 Iustin Pop
242 9188aeef Iustin Pop
-- | Sets the offline attribute.
243 c2c1ef0c Iustin Pop
setOffline :: Node -> Bool -> Node
244 c2c1ef0c Iustin Pop
setOffline t val = t { offline = val }
245 c2c1ef0c Iustin Pop
246 9188aeef Iustin Pop
-- | Sets the unnaccounted memory.
247 8c5b0a0d Iustin Pop
setXmem :: Node -> Int -> Node
248 2060348b Iustin Pop
setXmem t val = t { xMem = val }
249 8c5b0a0d Iustin Pop
250 844eff86 Iustin Pop
-- | Sets the max disk usage ratio
251 844eff86 Iustin Pop
setMdsk :: Node -> Double -> Node
252 f4c0b8c5 Iustin Pop
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
253 844eff86 Iustin Pop
254 844eff86 Iustin Pop
-- | Sets the max cpu usage ratio
255 844eff86 Iustin Pop
setMcpu :: Node -> Double -> Node
256 f4c0b8c5 Iustin Pop
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
257 844eff86 Iustin Pop
258 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
259 12e6776a Iustin Pop
computeMaxRes :: P.PeerMap -> P.Elem
260 12e6776a Iustin Pop
computeMaxRes = P.maxElem
261 e4f08c46 Iustin Pop
262 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
263 9cf4267a Iustin Pop
buildPeers :: Node -> Instance.List -> Node
264 9cf4267a Iustin Pop
buildPeers t il =
265 e4f08c46 Iustin Pop
    let mdata = map
266 e4f08c46 Iustin Pop
                (\i_idx -> let inst = Container.find i_idx il
267 2060348b Iustin Pop
                           in (Instance.pNode inst, Instance.mem inst))
268 2060348b Iustin Pop
                (sList t)
269 12e6776a Iustin Pop
        pmap = P.accumArray (+) mdata
270 e4f08c46 Iustin Pop
        new_rmem = computeMaxRes pmap
271 2060348b Iustin Pop
        new_failN1 = fMem t <= new_rmem
272 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
273 2060348b Iustin Pop
    in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
274 e4f08c46 Iustin Pop
275 a488a217 Iustin Pop
-- | Assigns an instance to a node as primary and update the used VCPU
276 5f0b9579 Iustin Pop
-- count, utilisation data and tags map.
277 a488a217 Iustin Pop
setPri :: Node -> Instance.Instance -> Node
278 aa8d2e71 Iustin Pop
setPri t inst = t { pList = Instance.idx inst:pList t
279 a488a217 Iustin Pop
                  , uCpu = new_count
280 aa8d2e71 Iustin Pop
                  , pCpu = fromIntegral new_count / tCpu t
281 aa8d2e71 Iustin Pop
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
282 5f0b9579 Iustin Pop
                  , pTags = addTags (pTags t) (Instance.tags inst)
283 aa8d2e71 Iustin Pop
                  }
284 a488a217 Iustin Pop
    where new_count = uCpu t + Instance.vcpus inst
285 9188aeef Iustin Pop
286 9188aeef Iustin Pop
-- | Assigns an instance to a node as secondary without other updates.
287 a488a217 Iustin Pop
setSec :: Node -> Instance.Instance -> Node
288 aa8d2e71 Iustin Pop
setSec t inst = t { sList = Instance.idx inst:sList t
289 aa8d2e71 Iustin Pop
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
290 aa8d2e71 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
291 aa8d2e71 Iustin Pop
                  }
292 aa8d2e71 Iustin Pop
    where old_load = utilLoad t
293 1a82215d Iustin Pop
294 9188aeef Iustin Pop
-- * Update functions
295 9188aeef Iustin Pop
296 9188aeef Iustin Pop
-- | Sets the free memory.
297 9188aeef Iustin Pop
setFmem :: Node -> Int -> Node
298 9188aeef Iustin Pop
setFmem t new_mem =
299 2060348b Iustin Pop
    let new_n1 = new_mem <= rMem t
300 2060348b Iustin Pop
        new_mp = fromIntegral new_mem / tMem t
301 bbd8efd2 Iustin Pop
    in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
302 9188aeef Iustin Pop
303 e4f08c46 Iustin Pop
-- | Removes a primary instance.
304 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
305 e4f08c46 Iustin Pop
removePri t inst =
306 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
307 2060348b Iustin Pop
        new_plist = delete iname (pList t)
308 2060348b Iustin Pop
        new_mem = fMem t + Instance.mem inst
309 2060348b Iustin Pop
        new_dsk = fDsk t + Instance.dsk inst
310 2060348b Iustin Pop
        new_mp = fromIntegral new_mem / tMem t
311 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
312 2060348b Iustin Pop
        new_failn1 = new_mem <= rMem t
313 2060348b Iustin Pop
        new_ucpu = uCpu t - Instance.vcpus inst
314 2060348b Iustin Pop
        new_rcpu = fromIntegral new_ucpu / tCpu t
315 aa8d2e71 Iustin Pop
        new_load = utilLoad t `T.subUtil` Instance.util inst
316 bbd8efd2 Iustin Pop
    in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
317 bbd8efd2 Iustin Pop
         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
318 5f0b9579 Iustin Pop
         , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
319 5f0b9579 Iustin Pop
         , pTags = delTags (pTags t) (Instance.tags inst) }
320 e4f08c46 Iustin Pop
321 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
322 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
323 e4f08c46 Iustin Pop
removeSec t inst =
324 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
325 2060348b Iustin Pop
        pnode = Instance.pNode inst
326 2060348b Iustin Pop
        new_slist = delete iname (sList t)
327 2060348b Iustin Pop
        new_dsk = fDsk t + Instance.dsk inst
328 e4f08c46 Iustin Pop
        old_peers = peers t
329 12e6776a Iustin Pop
        old_peem = P.find pnode old_peers
330 9f6dcdea Iustin Pop
        new_peem =  old_peem - Instance.mem inst
331 12e6776a Iustin Pop
        new_peers = P.add pnode new_peem old_peers
332 2060348b Iustin Pop
        old_rmem = rMem t
333 bbd8efd2 Iustin Pop
        new_rmem = if old_peem < old_rmem
334 bbd8efd2 Iustin Pop
                   then old_rmem
335 bbd8efd2 Iustin Pop
                   else computeMaxRes new_peers
336 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
337 2060348b Iustin Pop
        new_failn1 = fMem t <= new_rmem
338 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
339 aa8d2e71 Iustin Pop
        old_load = utilLoad t
340 aa8d2e71 Iustin Pop
        new_load = old_load { T.dskWeight = T.dskWeight old_load -
341 aa8d2e71 Iustin Pop
                                            T.dskWeight (Instance.util inst) }
342 bbd8efd2 Iustin Pop
    in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
343 bbd8efd2 Iustin Pop
         , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
344 bbd8efd2 Iustin Pop
         , pRem = new_prem, utilLoad = new_load }
345 e4f08c46 Iustin Pop
346 e4f08c46 Iustin Pop
-- | Adds a primary instance.
347 f2280553 Iustin Pop
addPri :: Node -> Instance.Instance -> T.OpResult Node
348 e4f08c46 Iustin Pop
addPri t inst =
349 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
350 2060348b Iustin Pop
        new_mem = fMem t - Instance.mem inst
351 2060348b Iustin Pop
        new_dsk = fDsk t - Instance.dsk inst
352 2060348b Iustin Pop
        new_failn1 = new_mem <= rMem t
353 2060348b Iustin Pop
        new_ucpu = uCpu t + Instance.vcpus inst
354 2060348b Iustin Pop
        new_pcpu = fromIntegral new_ucpu / tCpu t
355 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
356 2060348b Iustin Pop
        l_cpu = mCpu t
357 aa8d2e71 Iustin Pop
        new_load = utilLoad t `T.addUtil` Instance.util inst
358 5f0b9579 Iustin Pop
        inst_tags = Instance.tags inst
359 5f0b9579 Iustin Pop
        old_tags = pTags t
360 a4a6e623 Iustin Pop
    in case () of
361 a4a6e623 Iustin Pop
         _ | new_mem <= 0 -> T.OpFail T.FailMem
362 a4a6e623 Iustin Pop
           | new_dsk <= 0 || mDsk t > new_dp -> T.OpFail T.FailDisk
363 a4a6e623 Iustin Pop
           | new_failn1 && not (failN1 t) -> T.OpFail T.FailMem
364 a4a6e623 Iustin Pop
           | l_cpu >= 0 && l_cpu < new_pcpu -> T.OpFail T.FailCPU
365 a4a6e623 Iustin Pop
           | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
366 a4a6e623 Iustin Pop
           | otherwise ->
367 a4a6e623 Iustin Pop
               let new_plist = iname:pList t
368 a4a6e623 Iustin Pop
                   new_mp = fromIntegral new_mem / tMem t
369 a4a6e623 Iustin Pop
                   r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
370 a4a6e623 Iustin Pop
                         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
371 a4a6e623 Iustin Pop
                         , uCpu = new_ucpu, pCpu = new_pcpu
372 a4a6e623 Iustin Pop
                         , utilLoad = new_load
373 a4a6e623 Iustin Pop
                         , pTags = addTags old_tags inst_tags }
374 a4a6e623 Iustin Pop
               in T.OpGood r
375 e4f08c46 Iustin Pop
376 e4f08c46 Iustin Pop
-- | Adds a secondary instance.
377 f2280553 Iustin Pop
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
378 e4f08c46 Iustin Pop
addSec t inst pdx =
379 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
380 e4f08c46 Iustin Pop
        old_peers = peers t
381 2060348b Iustin Pop
        old_mem = fMem t
382 2060348b Iustin Pop
        new_dsk = fDsk t - Instance.dsk inst
383 12e6776a Iustin Pop
        new_peem = P.find pdx old_peers + Instance.mem inst
384 12e6776a Iustin Pop
        new_peers = P.add pdx new_peem old_peers
385 2060348b Iustin Pop
        new_rmem = max (rMem t) new_peem
386 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
387 c43c3354 Iustin Pop
        new_failn1 = old_mem <= new_rmem
388 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
389 aa8d2e71 Iustin Pop
        old_load = utilLoad t
390 aa8d2e71 Iustin Pop
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
391 aa8d2e71 Iustin Pop
                                            T.dskWeight (Instance.util inst) }
392 a4a6e623 Iustin Pop
    in case () of
393 a4a6e623 Iustin Pop
         _ | new_dsk <= 0 || mDsk t > new_dp -> T.OpFail T.FailDisk
394 146b37eb Iustin Pop
           | Instance.mem inst >= old_mem -> T.OpFail T.FailMem
395 a4a6e623 Iustin Pop
           | new_failn1 && not (failN1 t) -> T.OpFail T.FailMem
396 a4a6e623 Iustin Pop
           | otherwise ->
397 a4a6e623 Iustin Pop
               let new_slist = iname:sList t
398 a4a6e623 Iustin Pop
                   r = t { sList = new_slist, fDsk = new_dsk
399 a4a6e623 Iustin Pop
                         , peers = new_peers, failN1 = new_failn1
400 a4a6e623 Iustin Pop
                         , rMem = new_rmem, pDsk = new_dp
401 a4a6e623 Iustin Pop
                         , pRem = new_prem, utilLoad = new_load }
402 a4a6e623 Iustin Pop
               in T.OpGood r
403 e4f08c46 Iustin Pop
404 fe3d6f02 Iustin Pop
-- * Stats functions
405 fe3d6f02 Iustin Pop
406 fe3d6f02 Iustin Pop
-- | Computes the amount of available disk on a given node
407 fe3d6f02 Iustin Pop
availDisk :: Node -> Int
408 fe3d6f02 Iustin Pop
availDisk t =
409 2060348b Iustin Pop
    let _f = fDsk t
410 2060348b Iustin Pop
        _l = loDsk t
411 f4c0b8c5 Iustin Pop
    in if _f < _l
412 f4c0b8c5 Iustin Pop
       then 0
413 f4c0b8c5 Iustin Pop
       else _f - _l
414 fe3d6f02 Iustin Pop
415 1e3dccc8 Iustin Pop
-- | Computes the amount of available memory on a given node
416 1e3dccc8 Iustin Pop
availMem :: Node -> Int
417 1e3dccc8 Iustin Pop
availMem t =
418 1e3dccc8 Iustin Pop
    let _f = fMem t
419 1e3dccc8 Iustin Pop
        _l = rMem t
420 1e3dccc8 Iustin Pop
    in if _f < _l
421 1e3dccc8 Iustin Pop
       then 0
422 1e3dccc8 Iustin Pop
       else _f - _l
423 1e3dccc8 Iustin Pop
424 1e3dccc8 Iustin Pop
-- | Computes the amount of available memory on a given node
425 1e3dccc8 Iustin Pop
availCpu :: Node -> Int
426 1e3dccc8 Iustin Pop
availCpu t =
427 1e3dccc8 Iustin Pop
    let _u = uCpu t
428 1e3dccc8 Iustin Pop
        _l = hiCpu t
429 1e3dccc8 Iustin Pop
    in if _l >= _u
430 1e3dccc8 Iustin Pop
       then _l - _u
431 1e3dccc8 Iustin Pop
       else 0
432 1e3dccc8 Iustin Pop
433 9188aeef Iustin Pop
-- * Display functions
434 01f6a5d2 Iustin Pop
435 c5f7412e Iustin Pop
showField :: Node -> String -> String
436 c5f7412e Iustin Pop
showField t field =
437 c5f7412e Iustin Pop
    case field of
438 c5f7412e Iustin Pop
      "name" -> name t
439 c5f7412e Iustin Pop
      "status" -> if offline t then "-"
440 c5f7412e Iustin Pop
                  else if failN1 t then "*" else " "
441 c5f7412e Iustin Pop
      "tmem" -> printf "%5.0f" $ tMem t
442 c5f7412e Iustin Pop
      "nmem" -> printf "%5d" $ nMem t
443 c5f7412e Iustin Pop
      "xmem" -> printf "%5d" $ xMem t
444 c5f7412e Iustin Pop
      "fmem" -> printf "%5d" $ fMem t
445 c5f7412e Iustin Pop
      "imem" -> printf "%5d" imem
446 c5f7412e Iustin Pop
      "rmem" -> printf "%5d" $ rMem t
447 76354e11 Iustin Pop
      "amem" -> printf "%5d" $ fMem t - rMem t
448 c5f7412e Iustin Pop
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
449 c5f7412e Iustin Pop
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
450 c5f7412e Iustin Pop
      "tcpu" -> printf "%4.0f" $ tCpu t
451 c5f7412e Iustin Pop
      "ucpu" -> printf "%4d" $ uCpu t
452 c5f7412e Iustin Pop
      "plist" -> printf "%3d" $ length (pList t)
453 c5f7412e Iustin Pop
      "slist" -> printf "%3d" $ length (sList t)
454 c5f7412e Iustin Pop
      "pfmem" -> printf "%6.4f" $ pMem t
455 c5f7412e Iustin Pop
      "pfdsk" -> printf "%6.4f" $ pDsk t
456 c5f7412e Iustin Pop
      "rcpu"  -> printf "%5.2f" $ pCpu t
457 c5f7412e Iustin Pop
      "cload" -> printf "%5.3f" uC
458 c5f7412e Iustin Pop
      "mload" -> printf "%5.3f" uM
459 c5f7412e Iustin Pop
      "dload" -> printf "%5.3f" uD
460 c5f7412e Iustin Pop
      "nload" -> printf "%5.3f" uN
461 b2999982 Iustin Pop
      "ptags" -> intercalate "," . map (\(k, v) -> printf "%s=%d" k v) .
462 b2999982 Iustin Pop
                 Map.toList $ pTags t
463 c5f7412e Iustin Pop
      _ -> printf "<unknown field>"
464 c5f7412e Iustin Pop
    where
465 c5f7412e Iustin Pop
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
466 c5f7412e Iustin Pop
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
467 c5f7412e Iustin Pop
      imem = truncate (tMem t) - nMem t - xMem t - fMem t
468 c5f7412e Iustin Pop
469 76354e11 Iustin Pop
-- | Returns the header and numeric propery of a field
470 76354e11 Iustin Pop
showHeader :: String -> (String, Bool)
471 76354e11 Iustin Pop
showHeader field =
472 76354e11 Iustin Pop
    case field of
473 76354e11 Iustin Pop
      "name" -> ("Name", False)
474 76354e11 Iustin Pop
      "status" -> ("F", False)
475 76354e11 Iustin Pop
      "tmem" -> ("t_mem", True)
476 76354e11 Iustin Pop
      "nmem" -> ("n_mem", True)
477 76354e11 Iustin Pop
      "xmem" -> ("x_mem", True)
478 76354e11 Iustin Pop
      "fmem" -> ("f_mem", True)
479 76354e11 Iustin Pop
      "imem" -> ("i_mem", True)
480 76354e11 Iustin Pop
      "rmem" -> ("r_mem", True)
481 76354e11 Iustin Pop
      "amem" -> ("a_mem", True)
482 76354e11 Iustin Pop
      "tdsk" -> ("t_dsk", True)
483 76354e11 Iustin Pop
      "fdsk" -> ("f_dsk", True)
484 76354e11 Iustin Pop
      "tcpu" -> ("pcpu", True)
485 76354e11 Iustin Pop
      "ucpu" -> ("vcpu", True)
486 76354e11 Iustin Pop
      "plist" -> ("pri", True)
487 76354e11 Iustin Pop
      "slist" -> ("sec", True)
488 76354e11 Iustin Pop
      "pfmem" -> ("p_fmem", True)
489 76354e11 Iustin Pop
      "pfdsk" -> ("p_fdsk", True)
490 76354e11 Iustin Pop
      "rcpu"  -> ("r_cpu", True)
491 76354e11 Iustin Pop
      "cload" -> ("lCpu", True)
492 76354e11 Iustin Pop
      "mload" -> ("lMem", True)
493 76354e11 Iustin Pop
      "dload" -> ("lDsk", True)
494 76354e11 Iustin Pop
      "nload" -> ("lNet", True)
495 b2999982 Iustin Pop
      "ptags" -> ("PrimaryTags", False)
496 76354e11 Iustin Pop
      _ -> ("<unknown field>", False)
497 c5f7412e Iustin Pop
498 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
499 76354e11 Iustin Pop
list :: [String] -> Node -> [String]
500 76354e11 Iustin Pop
list fields t = map (showField t) fields
501 76354e11 Iustin Pop
502 76354e11 Iustin Pop
503 76354e11 Iustin Pop
defaultFields :: [String]
504 76354e11 Iustin Pop
defaultFields =
505 76354e11 Iustin Pop
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
506 76354e11 Iustin Pop
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
507 76354e11 Iustin Pop
    , "pfmem", "pfdsk", "rcpu"
508 76354e11 Iustin Pop
    , "cload", "mload", "dload", "nload" ]