Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ bbd8efd2

History | View | Annotate | Download (13.5 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 e4f08c46 Iustin Pop
    -- * Formatting
52 e4f08c46 Iustin Pop
    , list
53 040afc35 Iustin Pop
    -- * Misc stuff
54 040afc35 Iustin Pop
    , AssocList
55 040afc35 Iustin Pop
    , noSecondary
56 e4f08c46 Iustin Pop
    ) where
57 e4f08c46 Iustin Pop
58 e4f08c46 Iustin Pop
import Data.List
59 e4f08c46 Iustin Pop
import Text.Printf (printf)
60 e4f08c46 Iustin Pop
61 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
62 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
63 669d7e3d Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
64 e4f08c46 Iustin Pop
65 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
66 262a08a2 Iustin Pop
67 9188aeef Iustin Pop
-- * Type declarations
68 9188aeef Iustin Pop
69 9188aeef Iustin Pop
-- | The node type.
70 bbd8efd2 Iustin Pop
data Node = Node { name :: String  -- ^ The node name
71 2060348b Iustin Pop
                 , tMem :: Double  -- ^ Total memory (MiB)
72 2060348b Iustin Pop
                 , nMem :: Int     -- ^ Node memory (MiB)
73 2060348b Iustin Pop
                 , fMem :: Int     -- ^ Free memory (MiB)
74 2060348b Iustin Pop
                 , xMem :: Int     -- ^ Unaccounted memory (MiB)
75 2060348b Iustin Pop
                 , tDsk :: Double  -- ^ Total disk space (MiB)
76 2060348b Iustin Pop
                 , fDsk :: Int     -- ^ Free disk space (MiB)
77 2060348b Iustin Pop
                 , tCpu :: Double  -- ^ Total CPU count
78 2060348b Iustin Pop
                 , uCpu :: Int     -- ^ Used VCPU count
79 2060348b Iustin Pop
                 , pList :: [T.Idx]-- ^ List of primary instance indices
80 2060348b Iustin Pop
                 , sList :: [T.Idx]-- ^ List of secondary instance indices
81 9188aeef Iustin Pop
                 , idx :: T.Ndx    -- ^ Internal index for book-keeping
82 9188aeef Iustin Pop
                 , peers :: PeerMap.PeerMap -- ^ Pnode to instance mapping
83 bbd8efd2 Iustin Pop
                 , failN1 :: Bool  -- ^ Whether the node has failed n1
84 2060348b Iustin Pop
                 , rMem :: Int     -- ^ Maximum memory needed for
85 80d0d2f1 Iustin Pop
                                   -- failover by primaries of this node
86 2060348b Iustin Pop
                 , pMem :: Double  -- ^ Percent of free memory
87 2060348b Iustin Pop
                 , pDsk :: Double  -- ^ Percent of free disk
88 2060348b Iustin Pop
                 , pRem :: Double  -- ^ Percent of reserved memory
89 2060348b Iustin Pop
                 , pCpu :: Double  -- ^ Ratio of virtual to physical CPUs
90 2060348b Iustin Pop
                 , mDsk :: Double  -- ^ Minimum free disk ratio
91 2060348b Iustin Pop
                 , mCpu :: Double  -- ^ Max ratio of virt-to-phys CPUs
92 2060348b Iustin Pop
                 , loDsk :: Int    -- ^ Autocomputed from mDsk low disk
93 836533fa Iustin Pop
                                   -- threshold
94 2060348b Iustin Pop
                 , hiCpu :: Int    -- ^ Autocomputed from mCpu high cpu
95 836533fa Iustin Pop
                                   -- threshold
96 9188aeef Iustin Pop
                 , offline :: Bool -- ^ Whether the node should not be used
97 c2c1ef0c Iustin Pop
                                   -- for allocations and skipped from
98 c2c1ef0c Iustin Pop
                                   -- score computations
99 2180829f Iustin Pop
                 , utilPool :: T.DynUtil -- ^ Total utilisation capacity
100 2180829f Iustin Pop
                 , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
101 2180829f Iustin Pop
                 } deriving (Show)
102 e4f08c46 Iustin Pop
103 262a08a2 Iustin Pop
instance T.Element Node where
104 262a08a2 Iustin Pop
    nameOf = name
105 262a08a2 Iustin Pop
    idxOf = idx
106 262a08a2 Iustin Pop
    setName = setName
107 262a08a2 Iustin Pop
    setIdx = setIdx
108 262a08a2 Iustin Pop
109 9188aeef Iustin Pop
-- | A simple name for the int, node association list.
110 608efcce Iustin Pop
type AssocList = [(T.Ndx, Node)]
111 040afc35 Iustin Pop
112 9188aeef Iustin Pop
-- | A simple name for a node map.
113 262a08a2 Iustin Pop
type List = Container.Container Node
114 262a08a2 Iustin Pop
115 9188aeef Iustin Pop
-- | Constant node index for a non-moveable instance.
116 608efcce Iustin Pop
noSecondary :: T.Ndx
117 040afc35 Iustin Pop
noSecondary = -1
118 040afc35 Iustin Pop
119 18b6444b Iustin Pop
-- | No limit value
120 18b6444b Iustin Pop
noLimit :: Double
121 18b6444b Iustin Pop
noLimit = -1
122 18b6444b Iustin Pop
123 836533fa Iustin Pop
-- | No limit int value
124 836533fa Iustin Pop
noLimitInt :: Int
125 836533fa Iustin Pop
noLimitInt = -1
126 836533fa Iustin Pop
127 9188aeef Iustin Pop
-- * Initialization functions
128 e4f08c46 Iustin Pop
129 9188aeef Iustin Pop
-- | Create a new node.
130 9188aeef Iustin Pop
--
131 9188aeef Iustin Pop
-- The index and the peers maps are empty, and will be need to be
132 9188aeef Iustin Pop
-- update later via the 'setIdx' and 'buildPeers' functions.
133 1a82215d Iustin Pop
create :: String -> Double -> Int -> Int -> Double
134 1a82215d Iustin Pop
       -> Int -> Double -> Bool -> Node
135 2727257a Iustin Pop
create name_init mem_t_init mem_n_init mem_f_init
136 1a82215d Iustin Pop
       dsk_t_init dsk_f_init cpu_t_init offline_init =
137 2180829f Iustin Pop
    Node { name  = name_init
138 2180829f Iustin Pop
         , tMem = mem_t_init
139 2180829f Iustin Pop
         , nMem = mem_n_init
140 2180829f Iustin Pop
         , fMem = mem_f_init
141 2180829f Iustin Pop
         , tDsk = dsk_t_init
142 2180829f Iustin Pop
         , fDsk = dsk_f_init
143 2180829f Iustin Pop
         , tCpu = cpu_t_init
144 2180829f Iustin Pop
         , uCpu = 0
145 2180829f Iustin Pop
         , pList = []
146 2180829f Iustin Pop
         , sList = []
147 2180829f Iustin Pop
         , failN1 = True
148 2180829f Iustin Pop
         , idx = -1
149 2180829f Iustin Pop
         , peers = PeerMap.empty
150 2180829f Iustin Pop
         , rMem = 0
151 2180829f Iustin Pop
         , pMem = fromIntegral mem_f_init / mem_t_init
152 2180829f Iustin Pop
         , pDsk = fromIntegral dsk_f_init / dsk_t_init
153 2180829f Iustin Pop
         , pRem = 0
154 2180829f Iustin Pop
         , pCpu = 0
155 2180829f Iustin Pop
         , offline = offline_init
156 2180829f Iustin Pop
         , xMem = 0
157 2180829f Iustin Pop
         , mDsk = noLimit
158 2180829f Iustin Pop
         , mCpu = noLimit
159 2180829f Iustin Pop
         , loDsk = noLimitInt
160 2180829f Iustin Pop
         , hiCpu = noLimitInt
161 ee9724b9 Iustin Pop
         , utilPool = T.baseUtil
162 2180829f Iustin Pop
         , utilLoad = T.zeroUtil
163 2180829f Iustin Pop
         }
164 e4f08c46 Iustin Pop
165 e4f08c46 Iustin Pop
-- | Changes the index.
166 9188aeef Iustin Pop
--
167 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
168 608efcce Iustin Pop
setIdx :: Node -> T.Ndx -> Node
169 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
170 e4f08c46 Iustin Pop
171 9188aeef Iustin Pop
-- | Changes the name.
172 9188aeef Iustin Pop
--
173 497e30a1 Iustin Pop
-- This is used only during the building of the data structures.
174 9188aeef Iustin Pop
setName :: Node -> String -> Node
175 497e30a1 Iustin Pop
setName t s = t {name = s}
176 497e30a1 Iustin Pop
177 9188aeef Iustin Pop
-- | Sets the offline attribute.
178 c2c1ef0c Iustin Pop
setOffline :: Node -> Bool -> Node
179 c2c1ef0c Iustin Pop
setOffline t val = t { offline = val }
180 c2c1ef0c Iustin Pop
181 9188aeef Iustin Pop
-- | Sets the unnaccounted memory.
182 8c5b0a0d Iustin Pop
setXmem :: Node -> Int -> Node
183 2060348b Iustin Pop
setXmem t val = t { xMem = val }
184 8c5b0a0d Iustin Pop
185 844eff86 Iustin Pop
-- | Sets the max disk usage ratio
186 844eff86 Iustin Pop
setMdsk :: Node -> Double -> Node
187 2060348b Iustin Pop
setMdsk t val = t { mDsk = val,
188 2060348b Iustin Pop
                    loDsk = if val == noLimit
189 836533fa Iustin Pop
                             then noLimitInt
190 2060348b Iustin Pop
                             else floor (val * tDsk t) }
191 844eff86 Iustin Pop
192 844eff86 Iustin Pop
-- | Sets the max cpu usage ratio
193 844eff86 Iustin Pop
setMcpu :: Node -> Double -> Node
194 2060348b Iustin Pop
setMcpu t val = t { mCpu = val, hiCpu = floor (val * tCpu t) }
195 844eff86 Iustin Pop
196 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
197 e4f08c46 Iustin Pop
computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
198 9f6dcdea Iustin Pop
computeMaxRes = PeerMap.maxElem
199 e4f08c46 Iustin Pop
200 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
201 9cf4267a Iustin Pop
buildPeers :: Node -> Instance.List -> Node
202 9cf4267a Iustin Pop
buildPeers t il =
203 e4f08c46 Iustin Pop
    let mdata = map
204 e4f08c46 Iustin Pop
                (\i_idx -> let inst = Container.find i_idx il
205 2060348b Iustin Pop
                           in (Instance.pNode inst, Instance.mem inst))
206 2060348b Iustin Pop
                (sList t)
207 17c59f4b Iustin Pop
        pmap = PeerMap.accumArray (+) mdata
208 e4f08c46 Iustin Pop
        new_rmem = computeMaxRes pmap
209 2060348b Iustin Pop
        new_failN1 = fMem t <= new_rmem
210 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
211 2060348b Iustin Pop
    in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
212 e4f08c46 Iustin Pop
213 a488a217 Iustin Pop
-- | Assigns an instance to a node as primary and update the used VCPU
214 aa8d2e71 Iustin Pop
-- count and utilisation data.
215 a488a217 Iustin Pop
setPri :: Node -> Instance.Instance -> Node
216 aa8d2e71 Iustin Pop
setPri t inst = t { pList = Instance.idx inst:pList t
217 a488a217 Iustin Pop
                  , uCpu = new_count
218 aa8d2e71 Iustin Pop
                  , pCpu = fromIntegral new_count / tCpu t
219 aa8d2e71 Iustin Pop
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
220 aa8d2e71 Iustin Pop
                  }
221 a488a217 Iustin Pop
    where new_count = uCpu t + Instance.vcpus inst
222 9188aeef Iustin Pop
223 9188aeef Iustin Pop
-- | Assigns an instance to a node as secondary without other updates.
224 a488a217 Iustin Pop
setSec :: Node -> Instance.Instance -> Node
225 aa8d2e71 Iustin Pop
setSec t inst = t { sList = Instance.idx inst:sList t
226 aa8d2e71 Iustin Pop
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
227 aa8d2e71 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
228 aa8d2e71 Iustin Pop
                  }
229 aa8d2e71 Iustin Pop
    where old_load = utilLoad t
230 1a82215d Iustin Pop
231 9188aeef Iustin Pop
-- * Update functions
232 9188aeef Iustin Pop
233 9188aeef Iustin Pop
-- | Sets the free memory.
234 9188aeef Iustin Pop
setFmem :: Node -> Int -> Node
235 9188aeef Iustin Pop
setFmem t new_mem =
236 2060348b Iustin Pop
    let new_n1 = new_mem <= rMem t
237 2060348b Iustin Pop
        new_mp = fromIntegral new_mem / tMem t
238 bbd8efd2 Iustin Pop
    in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
239 9188aeef Iustin Pop
240 e4f08c46 Iustin Pop
-- | Removes a primary instance.
241 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
242 e4f08c46 Iustin Pop
removePri t inst =
243 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
244 2060348b Iustin Pop
        new_plist = delete iname (pList t)
245 2060348b Iustin Pop
        new_mem = fMem t + Instance.mem inst
246 2060348b Iustin Pop
        new_dsk = fDsk t + Instance.dsk inst
247 2060348b Iustin Pop
        new_mp = fromIntegral new_mem / tMem t
248 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
249 2060348b Iustin Pop
        new_failn1 = new_mem <= rMem t
250 2060348b Iustin Pop
        new_ucpu = uCpu t - Instance.vcpus inst
251 2060348b Iustin Pop
        new_rcpu = fromIntegral new_ucpu / tCpu t
252 aa8d2e71 Iustin Pop
        new_load = utilLoad t `T.subUtil` Instance.util inst
253 bbd8efd2 Iustin Pop
    in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
254 bbd8efd2 Iustin Pop
         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
255 bbd8efd2 Iustin Pop
         , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load }
256 e4f08c46 Iustin Pop
257 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
258 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
259 e4f08c46 Iustin Pop
removeSec t inst =
260 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
261 2060348b Iustin Pop
        pnode = Instance.pNode inst
262 2060348b Iustin Pop
        new_slist = delete iname (sList t)
263 2060348b Iustin Pop
        new_dsk = fDsk t + Instance.dsk inst
264 e4f08c46 Iustin Pop
        old_peers = peers t
265 e4f08c46 Iustin Pop
        old_peem = PeerMap.find pnode old_peers
266 9f6dcdea Iustin Pop
        new_peem =  old_peem - Instance.mem inst
267 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pnode new_peem old_peers
268 2060348b Iustin Pop
        old_rmem = rMem t
269 bbd8efd2 Iustin Pop
        new_rmem = if old_peem < old_rmem
270 bbd8efd2 Iustin Pop
                   then old_rmem
271 bbd8efd2 Iustin Pop
                   else computeMaxRes new_peers
272 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
273 2060348b Iustin Pop
        new_failn1 = fMem t <= new_rmem
274 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
275 aa8d2e71 Iustin Pop
        old_load = utilLoad t
276 aa8d2e71 Iustin Pop
        new_load = old_load { T.dskWeight = T.dskWeight old_load -
277 aa8d2e71 Iustin Pop
                                            T.dskWeight (Instance.util inst) }
278 bbd8efd2 Iustin Pop
    in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
279 bbd8efd2 Iustin Pop
         , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
280 bbd8efd2 Iustin Pop
         , pRem = new_prem, utilLoad = new_load }
281 e4f08c46 Iustin Pop
282 e4f08c46 Iustin Pop
-- | Adds a primary instance.
283 f2280553 Iustin Pop
addPri :: Node -> Instance.Instance -> T.OpResult Node
284 e4f08c46 Iustin Pop
addPri t inst =
285 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
286 2060348b Iustin Pop
        new_mem = fMem t - Instance.mem inst
287 2060348b Iustin Pop
        new_dsk = fDsk t - Instance.dsk inst
288 2060348b Iustin Pop
        new_failn1 = new_mem <= rMem t
289 2060348b Iustin Pop
        new_ucpu = uCpu t + Instance.vcpus inst
290 2060348b Iustin Pop
        new_pcpu = fromIntegral new_ucpu / tCpu t
291 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
292 2060348b Iustin Pop
        l_cpu = mCpu t
293 aa8d2e71 Iustin Pop
        new_load = utilLoad t `T.addUtil` Instance.util inst
294 c43c3354 Iustin Pop
    in if new_mem <= 0 then T.OpFail T.FailMem
295 2060348b Iustin Pop
       else if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
296 9f6dcdea Iustin Pop
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
297 c43c3354 Iustin Pop
       else if l_cpu >= 0 && l_cpu < new_pcpu then T.OpFail T.FailCPU
298 c43c3354 Iustin Pop
       else
299 2060348b Iustin Pop
           let new_plist = iname:pList t
300 2060348b Iustin Pop
               new_mp = fromIntegral new_mem / tMem t
301 bbd8efd2 Iustin Pop
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
302 bbd8efd2 Iustin Pop
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
303 bbd8efd2 Iustin Pop
                     , uCpu = new_ucpu, pCpu = new_pcpu, utilLoad = new_load }
304 c43c3354 Iustin Pop
           in T.OpGood r
305 e4f08c46 Iustin Pop
306 e4f08c46 Iustin Pop
-- | Adds a secondary instance.
307 f2280553 Iustin Pop
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
308 e4f08c46 Iustin Pop
addSec t inst pdx =
309 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
310 e4f08c46 Iustin Pop
        old_peers = peers t
311 2060348b Iustin Pop
        old_mem = fMem t
312 2060348b Iustin Pop
        new_dsk = fDsk t - Instance.dsk inst
313 e4f08c46 Iustin Pop
        new_peem = PeerMap.find pdx old_peers + Instance.mem inst
314 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pdx new_peem old_peers
315 2060348b Iustin Pop
        new_rmem = max (rMem t) new_peem
316 2060348b Iustin Pop
        new_prem = fromIntegral new_rmem / tMem t
317 c43c3354 Iustin Pop
        new_failn1 = old_mem <= new_rmem
318 2060348b Iustin Pop
        new_dp = fromIntegral new_dsk / tDsk t
319 aa8d2e71 Iustin Pop
        old_load = utilLoad t
320 aa8d2e71 Iustin Pop
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
321 aa8d2e71 Iustin Pop
                                            T.dskWeight (Instance.util inst) }
322 2060348b Iustin Pop
    in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
323 9f6dcdea Iustin Pop
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
324 2060348b Iustin Pop
       else let new_slist = iname:sList t
325 bbd8efd2 Iustin Pop
                r = t { sList = new_slist, fDsk = new_dsk
326 bbd8efd2 Iustin Pop
                      , peers = new_peers, failN1 = new_failn1
327 bbd8efd2 Iustin Pop
                      , rMem = new_rmem, pDsk = new_dp
328 bbd8efd2 Iustin Pop
                      , pRem = new_prem, utilLoad = new_load }
329 bbd8efd2 Iustin Pop
            in T.OpGood r
330 e4f08c46 Iustin Pop
331 fe3d6f02 Iustin Pop
-- * Stats functions
332 fe3d6f02 Iustin Pop
333 fe3d6f02 Iustin Pop
-- | Computes the amount of available disk on a given node
334 fe3d6f02 Iustin Pop
availDisk :: Node -> Int
335 fe3d6f02 Iustin Pop
availDisk t =
336 2060348b Iustin Pop
    let _f = fDsk t
337 2060348b Iustin Pop
        _l = loDsk t
338 fe3d6f02 Iustin Pop
    in
339 fe3d6f02 Iustin Pop
      if _l == noLimitInt
340 fe3d6f02 Iustin Pop
      then _f
341 fe3d6f02 Iustin Pop
      else if _f < _l
342 fe3d6f02 Iustin Pop
           then 0
343 fe3d6f02 Iustin Pop
           else _f - _l
344 fe3d6f02 Iustin Pop
345 9188aeef Iustin Pop
-- * Display functions
346 01f6a5d2 Iustin Pop
347 c5f7412e Iustin Pop
showField :: Node -> String -> String
348 c5f7412e Iustin Pop
showField t field =
349 c5f7412e Iustin Pop
    case field of
350 c5f7412e Iustin Pop
      "name" -> name t
351 c5f7412e Iustin Pop
      "status" -> if offline t then "-"
352 c5f7412e Iustin Pop
                  else if failN1 t then "*" else " "
353 c5f7412e Iustin Pop
      "tmem" -> printf "%5.0f" $ tMem t
354 c5f7412e Iustin Pop
      "nmem" -> printf "%5d" $ nMem t
355 c5f7412e Iustin Pop
      "xmem" -> printf "%5d" $ xMem t
356 c5f7412e Iustin Pop
      "fmem" -> printf "%5d" $ fMem t
357 c5f7412e Iustin Pop
      "imem" -> printf "%5d" imem
358 c5f7412e Iustin Pop
      "rmem" -> printf "%5d" $ rMem t
359 c5f7412e Iustin Pop
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
360 c5f7412e Iustin Pop
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
361 c5f7412e Iustin Pop
      "tcpu" -> printf "%4.0f" $ tCpu t
362 c5f7412e Iustin Pop
      "ucpu" -> printf "%4d" $ uCpu t
363 c5f7412e Iustin Pop
      "plist" -> printf "%3d" $ length (pList t)
364 c5f7412e Iustin Pop
      "slist" -> printf "%3d" $ length (sList t)
365 c5f7412e Iustin Pop
      "pfmem" -> printf "%6.4f" $ pMem t
366 c5f7412e Iustin Pop
      "pfdsk" -> printf "%6.4f" $ pDsk t
367 c5f7412e Iustin Pop
      "rcpu"  -> printf "%5.2f" $ pCpu t
368 c5f7412e Iustin Pop
      "cload" -> printf "%5.3f" uC
369 c5f7412e Iustin Pop
      "mload" -> printf "%5.3f" uM
370 c5f7412e Iustin Pop
      "dload" -> printf "%5.3f" uD
371 c5f7412e Iustin Pop
      "nload" -> printf "%5.3f" uN
372 c5f7412e Iustin Pop
      _ -> printf "<unknown field>"
373 c5f7412e Iustin Pop
    where
374 c5f7412e Iustin Pop
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
375 c5f7412e Iustin Pop
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
376 c5f7412e Iustin Pop
      imem = truncate (tMem t) - nMem t - xMem t - fMem t
377 c5f7412e Iustin Pop
378 c5f7412e Iustin Pop
379 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
380 c5f7412e Iustin Pop
list :: Node -> [String]
381 c5f7412e Iustin Pop
list t = map (showField t)
382 c5f7412e Iustin Pop
         [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
383 c5f7412e Iustin Pop
         , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
384 c5f7412e Iustin Pop
         , "pfmem", "pfdsk", "rcpu"
385 c5f7412e Iustin Pop
         , "cload", "mload", "dload", "nload" ]