Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 23fe06c2

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