Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ 97936d51

History | View | Annotate | Download (12.8 kB)

1 525bfb36 Iustin Pop
{-| Generic data loader.
2 040afc35 Iustin Pop
3 e8f89bb6 Iustin Pop
This module holds the common code for parsing the input data after it
4 e8f89bb6 Iustin Pop
has been loaded from external sources.
5 040afc35 Iustin Pop
6 040afc35 Iustin Pop
-}
7 040afc35 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 2a8e2dc9 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
14 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e2fa2baf Iustin Pop
(at your option) any later version.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e2fa2baf Iustin Pop
General Public License for more details.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
23 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
24 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e2fa2baf Iustin Pop
02110-1301, USA.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
-}
28 e2fa2baf Iustin Pop
29 040afc35 Iustin Pop
module Ganeti.HTools.Loader
30 446d8827 Iustin Pop
    ( mergeData
31 446d8827 Iustin Pop
    , checkData
32 446d8827 Iustin Pop
    , assignIndices
33 446d8827 Iustin Pop
    , lookupNode
34 5a1edeb6 Iustin Pop
    , lookupInstance
35 f4531f51 Iustin Pop
    , lookupGroup
36 3e4480e0 Iustin Pop
    , commonSuffix
37 2c3273e7 Iustin Pop
    , RelocMode(..)
38 1fe412bb Iustin Pop
    , EvacMode(..)
39 19f38ee8 Iustin Pop
    , RqType(..)
40 19f38ee8 Iustin Pop
    , Request(..)
41 7b6e99b3 Iustin Pop
    , ClusterData(..)
42 7b6e99b3 Iustin Pop
    , emptyCluster
43 efe98965 Guido Trotter
    , compareNameComponent
44 efe98965 Guido Trotter
    , prefixMatch
45 efe98965 Guido Trotter
    , LookupResult(..)
46 efe98965 Guido Trotter
    , MatchPriority(..)
47 446d8827 Iustin Pop
    ) where
48 040afc35 Iustin Pop
49 e4c5beaf Iustin Pop
import Data.List
50 efe98965 Guido Trotter
import Data.Function
51 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
52 446d8827 Iustin Pop
import Text.Printf (printf)
53 e4c5beaf Iustin Pop
54 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
55 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
56 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
57 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
58 e4c5beaf Iustin Pop
59 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
60 efe98965 Guido Trotter
import Ganeti.HTools.Utils
61 e4c5beaf Iustin Pop
62 f5e67f55 Iustin Pop
-- * Constants
63 f5e67f55 Iustin Pop
64 525bfb36 Iustin Pop
-- | The exclusion tag prefix.
65 f5e67f55 Iustin Pop
exTagsPrefix :: String
66 f5e67f55 Iustin Pop
exTagsPrefix = "htools:iextags:"
67 f5e67f55 Iustin Pop
68 19f38ee8 Iustin Pop
-- * Types
69 19f38ee8 Iustin Pop
70 2c3273e7 Iustin Pop
-- | The iallocator multi-evac group mode type.
71 2c3273e7 Iustin Pop
data RelocMode = KeepGroup
72 2c3273e7 Iustin Pop
               | ChangeGroup [Gdx]
73 2c3273e7 Iustin Pop
               | AnyGroup
74 2c3273e7 Iustin Pop
                 deriving (Show, Read)
75 2c3273e7 Iustin Pop
76 54365762 Iustin Pop
{-| The iallocator request type.
77 19f38ee8 Iustin Pop
78 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
79 19f38ee8 Iustin Pop
request-specific fields.
80 19f38ee8 Iustin Pop
81 19f38ee8 Iustin Pop
-}
82 19f38ee8 Iustin Pop
data RqType
83 19f38ee8 Iustin Pop
    = Allocate Instance.Instance Int -- ^ A new instance allocation
84 19f38ee8 Iustin Pop
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
85 19f38ee8 Iustin Pop
                                     -- secondary node
86 54365762 Iustin Pop
    | Evacuate [Ndx]                 -- ^ Evacuate nodes
87 2c3273e7 Iustin Pop
    | MultiReloc [Idx] RelocMode     -- ^ Multi-relocate mode
88 1fe412bb Iustin Pop
    | NodeEvacuate [Idx] EvacMode    -- ^ node-evacuate mode
89 6bc39970 Iustin Pop
    deriving (Show, Read)
90 19f38ee8 Iustin Pop
91 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
92 34c00528 Iustin Pop
data Request = Request RqType ClusterData
93 6bc39970 Iustin Pop
    deriving (Show, Read)
94 19f38ee8 Iustin Pop
95 7b6e99b3 Iustin Pop
-- | The cluster state.
96 7b6e99b3 Iustin Pop
data ClusterData = ClusterData
97 7b6e99b3 Iustin Pop
    { cdGroups    :: Group.List    -- ^ The node group list
98 7b6e99b3 Iustin Pop
    , cdNodes     :: Node.List     -- ^ The node list
99 7b6e99b3 Iustin Pop
    , cdInstances :: Instance.List -- ^ The instance list
100 7b6e99b3 Iustin Pop
    , cdTags      :: [String]      -- ^ The cluster tags
101 6bc39970 Iustin Pop
    } deriving (Show, Read)
102 7b6e99b3 Iustin Pop
103 efe98965 Guido Trotter
-- | The priority of a match in a lookup result.
104 efe98965 Guido Trotter
data MatchPriority = ExactMatch
105 efe98965 Guido Trotter
                   | MultipleMatch
106 efe98965 Guido Trotter
                   | PartialMatch
107 efe98965 Guido Trotter
                   | FailMatch
108 efe98965 Guido Trotter
                   deriving (Show, Read, Enum, Eq, Ord)
109 efe98965 Guido Trotter
110 efe98965 Guido Trotter
-- | The result of a name lookup in a list.
111 efe98965 Guido Trotter
data LookupResult = LookupResult
112 efe98965 Guido Trotter
    { lrMatchPriority :: MatchPriority -- ^ The result type
113 efe98965 Guido Trotter
    -- | Matching value (for ExactMatch, PartialMatch), Lookup string otherwise
114 efe98965 Guido Trotter
    , lrContent :: String
115 efe98965 Guido Trotter
    } deriving (Show, Read)
116 efe98965 Guido Trotter
117 efe98965 Guido Trotter
-- | Lookup results have an absolute preference ordering.
118 efe98965 Guido Trotter
instance Eq LookupResult where
119 efe98965 Guido Trotter
  (==) = (==) `on` lrMatchPriority
120 efe98965 Guido Trotter
121 efe98965 Guido Trotter
instance Ord LookupResult where
122 efe98965 Guido Trotter
  compare = compare `on` lrMatchPriority
123 efe98965 Guido Trotter
124 7b6e99b3 Iustin Pop
-- | An empty cluster.
125 7b6e99b3 Iustin Pop
emptyCluster :: ClusterData
126 7b6e99b3 Iustin Pop
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
127 7b6e99b3 Iustin Pop
128 19f38ee8 Iustin Pop
-- * Functions
129 19f38ee8 Iustin Pop
130 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
131 6ff78049 Iustin Pop
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
132 040afc35 Iustin Pop
lookupNode ktn inst node =
133 2d0ca2c5 Iustin Pop
    case M.lookup node ktn of
134 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
135 040afc35 Iustin Pop
      Just idx -> return idx
136 040afc35 Iustin Pop
137 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
138 6ff78049 Iustin Pop
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
139 5a1edeb6 Iustin Pop
lookupInstance kti inst =
140 2d0ca2c5 Iustin Pop
    case M.lookup inst kti of
141 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
142 5a1edeb6 Iustin Pop
      Just idx -> return idx
143 5a1edeb6 Iustin Pop
144 f4531f51 Iustin Pop
-- | Lookups a group into an assoc list.
145 f4531f51 Iustin Pop
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
146 f4531f51 Iustin Pop
lookupGroup ktg nname gname =
147 f4531f51 Iustin Pop
    case M.lookup gname ktg of
148 f4531f51 Iustin Pop
      Nothing -> fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname
149 f4531f51 Iustin Pop
      Just idx -> return idx
150 f4531f51 Iustin Pop
151 efe98965 Guido Trotter
-- | Check for prefix matches in names.
152 efe98965 Guido Trotter
-- Implemented in Ganeti core utils.text.MatchNameComponent
153 efe98965 Guido Trotter
-- as the regexp r"^%s(\..*)?$" % re.escape(key)
154 efe98965 Guido Trotter
prefixMatch :: String  -- ^ Lookup
155 efe98965 Guido Trotter
            -> String  -- ^ Full name
156 efe98965 Guido Trotter
            -> Bool    -- ^ Whether there is a prefix match
157 efe98965 Guido Trotter
prefixMatch lkp = isPrefixOf (lkp ++ ".")
158 efe98965 Guido Trotter
159 efe98965 Guido Trotter
-- | Is the lookup priority a "good" one?
160 efe98965 Guido Trotter
goodMatchPriority :: MatchPriority -> Bool
161 efe98965 Guido Trotter
goodMatchPriority ExactMatch = True
162 efe98965 Guido Trotter
goodMatchPriority PartialMatch = True
163 efe98965 Guido Trotter
goodMatchPriority _ = False
164 efe98965 Guido Trotter
165 efe98965 Guido Trotter
-- | Is the lookup result an actual match?
166 efe98965 Guido Trotter
goodLookupResult :: LookupResult -> Bool
167 efe98965 Guido Trotter
goodLookupResult = goodMatchPriority . lrMatchPriority
168 efe98965 Guido Trotter
169 efe98965 Guido Trotter
-- | Compares a canonical name and a lookup string.
170 efe98965 Guido Trotter
compareNameComponent :: String        -- ^ Canonical (target) name
171 efe98965 Guido Trotter
                     -> String        -- ^ Partial (lookup) name
172 efe98965 Guido Trotter
                     -> LookupResult  -- ^ Result of the lookup
173 efe98965 Guido Trotter
compareNameComponent cnl lkp =
174 efe98965 Guido Trotter
  select (LookupResult FailMatch lkp)
175 efe98965 Guido Trotter
  [ (cnl == lkp          , LookupResult ExactMatch cnl)
176 efe98965 Guido Trotter
  , (prefixMatch lkp cnl , LookupResult PartialMatch cnl)
177 efe98965 Guido Trotter
  ]
178 efe98965 Guido Trotter
179 efe98965 Guido Trotter
-- | Lookup a string and choose the best result.
180 efe98965 Guido Trotter
chooseLookupResult :: String       -- ^ Lookup key
181 efe98965 Guido Trotter
                   -> String       -- ^ String to compare to the lookup key
182 efe98965 Guido Trotter
                   -> LookupResult -- ^ Previous result
183 efe98965 Guido Trotter
                   -> LookupResult -- ^ New result
184 efe98965 Guido Trotter
chooseLookupResult lkp cstr old =
185 efe98965 Guido Trotter
  -- default: use class order to pick the minimum result
186 efe98965 Guido Trotter
  select (min new old)
187 efe98965 Guido Trotter
  -- special cases:
188 efe98965 Guido Trotter
  -- short circuit if the new result is an exact match
189 efe98965 Guido Trotter
  [ ((lrMatchPriority new) == ExactMatch, new)
190 efe98965 Guido Trotter
  -- if both are partial matches generate a multiple match
191 efe98965 Guido Trotter
  , (partial2, LookupResult MultipleMatch lkp)
192 efe98965 Guido Trotter
  ] where new = compareNameComponent cstr lkp
193 efe98965 Guido Trotter
          partial2 = all ((PartialMatch==) . lrMatchPriority) [old, new]
194 efe98965 Guido Trotter
195 efe98965 Guido Trotter
-- | Find the canonical name for a lookup string in a list of names.
196 efe98965 Guido Trotter
lookupName :: [String]      -- ^ List of keys
197 efe98965 Guido Trotter
           -> String        -- ^ Lookup string
198 efe98965 Guido Trotter
           -> LookupResult  -- ^ Result of the lookup
199 efe98965 Guido Trotter
lookupName l s = foldr (chooseLookupResult s)
200 efe98965 Guido Trotter
                       (LookupResult FailMatch s) l
201 efe98965 Guido Trotter
202 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
203 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
204 497e30a1 Iustin Pop
                 [(String, a)]
205 99b63608 Iustin Pop
              -> (NameAssoc, Container.Container a)
206 2d0ca2c5 Iustin Pop
assignIndices nodes =
207 2d0ca2c5 Iustin Pop
  let (na, idx_node) =
208 2d0ca2c5 Iustin Pop
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
209 2d0ca2c5 Iustin Pop
          . zip [0..] $ nodes
210 cb0c77ff Iustin Pop
  in (M.fromList na, Container.fromList idx_node)
211 78694255 Iustin Pop
212 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
213 99b63608 Iustin Pop
fixNodes :: Node.List
214 aa8d2e71 Iustin Pop
         -> Instance.Instance
215 99b63608 Iustin Pop
         -> Node.List
216 aa8d2e71 Iustin Pop
fixNodes accu inst =
217 d71d0a1d Iustin Pop
    let
218 2060348b Iustin Pop
        pdx = Instance.pNode inst
219 2060348b Iustin Pop
        sdx = Instance.sNode inst
220 99b63608 Iustin Pop
        pold = Container.find pdx accu
221 a488a217 Iustin Pop
        pnew = Node.setPri pold inst
222 99b63608 Iustin Pop
        ac2 = Container.add pdx pnew accu
223 d71d0a1d Iustin Pop
    in
224 d71d0a1d Iustin Pop
      if sdx /= Node.noSecondary
225 99b63608 Iustin Pop
      then let sold = Container.find sdx accu
226 a488a217 Iustin Pop
               snew = Node.setSec sold inst
227 99b63608 Iustin Pop
           in Container.add sdx snew ac2
228 d71d0a1d Iustin Pop
      else ac2
229 e4c5beaf Iustin Pop
230 525bfb36 Iustin Pop
-- | Remove non-selected tags from the exclusion list.
231 0f15cc76 Iustin Pop
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
232 0f15cc76 Iustin Pop
filterExTags tl inst =
233 0f15cc76 Iustin Pop
    let old_tags = Instance.tags inst
234 5182e970 Iustin Pop
        new_tags = filter (\tag -> any (`isPrefixOf` tag) tl)
235 0f15cc76 Iustin Pop
                   old_tags
236 0f15cc76 Iustin Pop
    in inst { Instance.tags = new_tags }
237 0f15cc76 Iustin Pop
238 525bfb36 Iustin Pop
-- | Update the movable attribute.
239 c6ccc073 Guido Trotter
updateMovable :: [String]           -- ^ Selected instances (if not empty)
240 c6ccc073 Guido Trotter
              -> [String]           -- ^ Excluded instances
241 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance
242 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance with updated attribute
243 c6ccc073 Guido Trotter
updateMovable selinsts exinsts inst =
244 39f979b8 Iustin Pop
    if Instance.sNode inst == Node.noSecondary ||
245 c6ccc073 Guido Trotter
       Instance.name inst `elem` exinsts ||
246 c6ccc073 Guido Trotter
       not (null selinsts || Instance.name inst `elem` selinsts)
247 39f979b8 Iustin Pop
    then Instance.setMovable inst False
248 39f979b8 Iustin Pop
    else inst
249 39f979b8 Iustin Pop
250 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
251 525bfb36 Iustin Pop
-- starts with a dot.
252 8472a321 Iustin Pop
longestDomain :: [String] -> String
253 e4c5beaf Iustin Pop
longestDomain [] = ""
254 8472a321 Iustin Pop
longestDomain (x:xs) =
255 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
256 e4c5beaf Iustin Pop
                              then suffix
257 e4c5beaf Iustin Pop
                              else accu)
258 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
259 e4c5beaf Iustin Pop
260 525bfb36 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration.
261 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
262 f5e67f55 Iustin Pop
extractExTags =
263 f5e67f55 Iustin Pop
    map (drop (length exTagsPrefix)) .
264 f5e67f55 Iustin Pop
    filter (isPrefixOf exTagsPrefix)
265 f5e67f55 Iustin Pop
266 525bfb36 Iustin Pop
-- | Extracts the common suffix from node\/instance names.
267 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
268 3e4480e0 Iustin Pop
commonSuffix nl il =
269 3e4480e0 Iustin Pop
    let node_names = map Node.name $ Container.elems nl
270 3e4480e0 Iustin Pop
        inst_names = map Instance.name $ Container.elems il
271 3e4480e0 Iustin Pop
    in longestDomain (node_names ++ inst_names)
272 3e4480e0 Iustin Pop
273 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
274 9188aeef Iustin Pop
-- list and massages it into the correct format.
275 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
276 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
277 2d1708e0 Guido Trotter
          -> [String]             -- ^ Selected instances (if not empty)
278 2d1708e0 Guido Trotter
          -> [String]             -- ^ Excluded instances
279 f4f6eb0b Iustin Pop
          -> ClusterData          -- ^ Data from backends
280 c0e31451 Iustin Pop
          -> Result ClusterData   -- ^ Fixed cluster data
281 2d1708e0 Guido Trotter
mergeData um extags selinsts exinsts cdata@(ClusterData _ nl il2 tags) =
282 99b63608 Iustin Pop
  let il = Container.elems il2
283 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
284 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
285 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
286 a5f8dcdc Iustin Pop
                          Just inst ->
287 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
288 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
289 a5f8dcdc Iustin Pop
                   ) il2 um
290 f5e67f55 Iustin Pop
      allextags = extags ++ extractExTags tags
291 424ec11d Guido Trotter
      inst_names = map Instance.name il
292 424ec11d Guido Trotter
      selinst_lkp = map (lookupName inst_names) selinsts
293 424ec11d Guido Trotter
      exinst_lkp = map (lookupName inst_names) exinsts
294 424ec11d Guido Trotter
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
295 424ec11d Guido Trotter
      selinst_names = map lrContent selinst_lkp
296 424ec11d Guido Trotter
      exinst_names = map lrContent exinst_lkp
297 39f979b8 Iustin Pop
      il4 = Container.map (filterExTags allextags .
298 424ec11d Guido Trotter
                           updateMovable selinst_names exinst_names) il3
299 0f15cc76 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
300 2a8e2dc9 Iustin Pop
      nl3 = Container.map (flip Node.buildPeers il4) nl2
301 99b63608 Iustin Pop
      node_names = map Node.name (Container.elems nl)
302 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
303 3e4480e0 Iustin Pop
      snl = Container.map (computeAlias common_suffix) nl3
304 3e4480e0 Iustin Pop
      sil = Container.map (computeAlias common_suffix) il4
305 424ec11d Guido Trotter
  in if' (null lkp_unknown)
306 424ec11d Guido Trotter
         (Ok cdata { cdNodes = snl, cdInstances = sil })
307 424ec11d Guido Trotter
         (Bad $ "Unknown instance(s): " ++ show(map lrContent lkp_unknown))
308 446d8827 Iustin Pop
309 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
310 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
311 262a08a2 Iustin Pop
          -> ([String], Node.List)
312 dbd6700b Iustin Pop
checkData nl il =
313 446d8827 Iustin Pop
    Container.mapAccum
314 446d8827 Iustin Pop
        (\ msgs node ->
315 dbd6700b Iustin Pop
             let nname = Node.name node
316 5182e970 Iustin Pop
                 nilst = map (`Container.find` il) (Node.pList node)
317 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
318 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
319 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
320 2060348b Iustin Pop
                             - Node.nMem node
321 2060348b Iustin Pop
                             - Node.fMem node
322 9f6dcdea Iustin Pop
                             - nodeImem node il
323 446d8827 Iustin Pop
                             + adj_mem
324 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
325 2060348b Iustin Pop
                             - Node.fDsk node
326 9f6dcdea Iustin Pop
                             - nodeIdsk node il
327 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
328 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
329 9f6dcdea Iustin Pop
                 umsg1 = [printf "node %s is missing %d MB ram \
330 9f6dcdea Iustin Pop
                                 \and %d GB disk"
331 9f6dcdea Iustin Pop
                                 nname delta_mem (delta_dsk `div` 1024) |
332 9f6dcdea Iustin Pop
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
333 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
334 446d8827 Iustin Pop
        ) [] nl
335 446d8827 Iustin Pop
336 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
337 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
338 446d8827 Iustin Pop
nodeImem node il =
339 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
340 9f6dcdea Iustin Pop
    in sum . map (Instance.mem . rfind)
341 2060348b Iustin Pop
           $ Node.pList node
342 446d8827 Iustin Pop
343 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
344 446d8827 Iustin Pop
-- or secondary).
345 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
346 446d8827 Iustin Pop
nodeIdsk node il =
347 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
348 9f6dcdea Iustin Pop
    in sum . map (Instance.dsk . rfind)
349 2060348b Iustin Pop
           $ Node.pList node ++ Node.sList node