Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ f4c0b8c5

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