Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ b003b8c0

History | View | Annotate | Download (12.9 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 d6eec019 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  ( mergeData
31 ebf38064 Iustin Pop
  , checkData
32 ebf38064 Iustin Pop
  , assignIndices
33 ebf38064 Iustin Pop
  , lookupName
34 ebf38064 Iustin Pop
  , goodLookupResult
35 ebf38064 Iustin Pop
  , lookupNode
36 ebf38064 Iustin Pop
  , lookupInstance
37 ebf38064 Iustin Pop
  , lookupGroup
38 ebf38064 Iustin Pop
  , commonSuffix
39 ebf38064 Iustin Pop
  , RqType(..)
40 ebf38064 Iustin Pop
  , Request(..)
41 ebf38064 Iustin Pop
  , ClusterData(..)
42 ebf38064 Iustin Pop
  , emptyCluster
43 ebf38064 Iustin Pop
  , compareNameComponent
44 ebf38064 Iustin Pop
  , prefixMatch
45 ebf38064 Iustin Pop
  , LookupResult(..)
46 ebf38064 Iustin Pop
  , MatchPriority(..)
47 ebf38064 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 54365762 Iustin Pop
{-| The iallocator request type.
71 19f38ee8 Iustin Pop
72 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
73 19f38ee8 Iustin Pop
request-specific fields.
74 19f38ee8 Iustin Pop
75 19f38ee8 Iustin Pop
-}
76 19f38ee8 Iustin Pop
data RqType
77 ebf38064 Iustin Pop
  = Allocate Instance.Instance Int -- ^ A new instance allocation
78 ebf38064 Iustin Pop
  | Relocate Idx Int [Ndx]         -- ^ Choose a new secondary node
79 ebf38064 Iustin Pop
  | NodeEvacuate [Idx] EvacMode    -- ^ node-evacuate mode
80 ebf38064 Iustin Pop
  | ChangeGroup [Gdx] [Idx]        -- ^ Multi-relocate mode
81 6bc39970 Iustin Pop
    deriving (Show, Read)
82 19f38ee8 Iustin Pop
83 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
84 34c00528 Iustin Pop
data Request = Request RqType ClusterData
85 ebf38064 Iustin Pop
               deriving (Show, Read)
86 19f38ee8 Iustin Pop
87 7b6e99b3 Iustin Pop
-- | The cluster state.
88 7b6e99b3 Iustin Pop
data ClusterData = ClusterData
89 ebf38064 Iustin Pop
  { cdGroups    :: Group.List    -- ^ The node group list
90 ebf38064 Iustin Pop
  , cdNodes     :: Node.List     -- ^ The node list
91 ebf38064 Iustin Pop
  , cdInstances :: Instance.List -- ^ The instance list
92 ebf38064 Iustin Pop
  , cdTags      :: [String]      -- ^ The cluster tags
93 71375ef7 Iustin Pop
  , cdIPolicy   :: IPolicy       -- ^ The cluster instance policy
94 dce9bbb3 Iustin Pop
  } deriving (Show, Read, Eq)
95 7b6e99b3 Iustin Pop
96 efe98965 Guido Trotter
-- | The priority of a match in a lookup result.
97 efe98965 Guido Trotter
data MatchPriority = ExactMatch
98 efe98965 Guido Trotter
                   | MultipleMatch
99 efe98965 Guido Trotter
                   | PartialMatch
100 efe98965 Guido Trotter
                   | FailMatch
101 efe98965 Guido Trotter
                   deriving (Show, Read, Enum, Eq, Ord)
102 efe98965 Guido Trotter
103 efe98965 Guido Trotter
-- | The result of a name lookup in a list.
104 efe98965 Guido Trotter
data LookupResult = LookupResult
105 ebf38064 Iustin Pop
  { lrMatchPriority :: MatchPriority -- ^ The result type
106 ebf38064 Iustin Pop
  -- | Matching value (for ExactMatch, PartialMatch), Lookup string otherwise
107 ebf38064 Iustin Pop
  , lrContent :: String
108 ebf38064 Iustin Pop
  } deriving (Show, Read)
109 efe98965 Guido Trotter
110 efe98965 Guido Trotter
-- | Lookup results have an absolute preference ordering.
111 efe98965 Guido Trotter
instance Eq LookupResult where
112 efe98965 Guido Trotter
  (==) = (==) `on` lrMatchPriority
113 efe98965 Guido Trotter
114 efe98965 Guido Trotter
instance Ord LookupResult where
115 efe98965 Guido Trotter
  compare = compare `on` lrMatchPriority
116 efe98965 Guido Trotter
117 7b6e99b3 Iustin Pop
-- | An empty cluster.
118 7b6e99b3 Iustin Pop
emptyCluster :: ClusterData
119 7b6e99b3 Iustin Pop
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
120 71375ef7 Iustin Pop
                 defIPolicy
121 7b6e99b3 Iustin Pop
122 19f38ee8 Iustin Pop
-- * Functions
123 19f38ee8 Iustin Pop
124 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
125 6ff78049 Iustin Pop
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
126 040afc35 Iustin Pop
lookupNode ktn inst node =
127 ebf38064 Iustin Pop
  case M.lookup node ktn of
128 ebf38064 Iustin Pop
    Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
129 ebf38064 Iustin Pop
    Just idx -> return idx
130 040afc35 Iustin Pop
131 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
132 6ff78049 Iustin Pop
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
133 5a1edeb6 Iustin Pop
lookupInstance kti inst =
134 ebf38064 Iustin Pop
  case M.lookup inst kti of
135 ebf38064 Iustin Pop
    Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
136 ebf38064 Iustin Pop
    Just idx -> return idx
137 5a1edeb6 Iustin Pop
138 f4531f51 Iustin Pop
-- | Lookups a group into an assoc list.
139 f4531f51 Iustin Pop
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
140 f4531f51 Iustin Pop
lookupGroup ktg nname gname =
141 ebf38064 Iustin Pop
  case M.lookup gname ktg of
142 ebf38064 Iustin Pop
    Nothing -> fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname
143 ebf38064 Iustin Pop
    Just idx -> return idx
144 f4531f51 Iustin Pop
145 efe98965 Guido Trotter
-- | Check for prefix matches in names.
146 efe98965 Guido Trotter
-- Implemented in Ganeti core utils.text.MatchNameComponent
147 efe98965 Guido Trotter
-- as the regexp r"^%s(\..*)?$" % re.escape(key)
148 efe98965 Guido Trotter
prefixMatch :: String  -- ^ Lookup
149 efe98965 Guido Trotter
            -> String  -- ^ Full name
150 efe98965 Guido Trotter
            -> Bool    -- ^ Whether there is a prefix match
151 05ff7a00 Agata Murawska
prefixMatch = isPrefixOf . (++ ".")
152 efe98965 Guido Trotter
153 efe98965 Guido Trotter
-- | Is the lookup priority a "good" one?
154 efe98965 Guido Trotter
goodMatchPriority :: MatchPriority -> Bool
155 efe98965 Guido Trotter
goodMatchPriority ExactMatch = True
156 efe98965 Guido Trotter
goodMatchPriority PartialMatch = True
157 efe98965 Guido Trotter
goodMatchPriority _ = False
158 efe98965 Guido Trotter
159 efe98965 Guido Trotter
-- | Is the lookup result an actual match?
160 efe98965 Guido Trotter
goodLookupResult :: LookupResult -> Bool
161 efe98965 Guido Trotter
goodLookupResult = goodMatchPriority . lrMatchPriority
162 efe98965 Guido Trotter
163 efe98965 Guido Trotter
-- | Compares a canonical name and a lookup string.
164 efe98965 Guido Trotter
compareNameComponent :: String        -- ^ Canonical (target) name
165 efe98965 Guido Trotter
                     -> String        -- ^ Partial (lookup) name
166 efe98965 Guido Trotter
                     -> LookupResult  -- ^ Result of the lookup
167 efe98965 Guido Trotter
compareNameComponent cnl lkp =
168 efe98965 Guido Trotter
  select (LookupResult FailMatch lkp)
169 efe98965 Guido Trotter
  [ (cnl == lkp          , LookupResult ExactMatch cnl)
170 efe98965 Guido Trotter
  , (prefixMatch lkp cnl , LookupResult PartialMatch cnl)
171 efe98965 Guido Trotter
  ]
172 efe98965 Guido Trotter
173 efe98965 Guido Trotter
-- | Lookup a string and choose the best result.
174 efe98965 Guido Trotter
chooseLookupResult :: String       -- ^ Lookup key
175 efe98965 Guido Trotter
                   -> String       -- ^ String to compare to the lookup key
176 efe98965 Guido Trotter
                   -> LookupResult -- ^ Previous result
177 efe98965 Guido Trotter
                   -> LookupResult -- ^ New result
178 efe98965 Guido Trotter
chooseLookupResult lkp cstr old =
179 efe98965 Guido Trotter
  -- default: use class order to pick the minimum result
180 efe98965 Guido Trotter
  select (min new old)
181 efe98965 Guido Trotter
  -- special cases:
182 efe98965 Guido Trotter
  -- short circuit if the new result is an exact match
183 05ff7a00 Agata Murawska
  [ (lrMatchPriority new == ExactMatch, new)
184 efe98965 Guido Trotter
  -- if both are partial matches generate a multiple match
185 efe98965 Guido Trotter
  , (partial2, LookupResult MultipleMatch lkp)
186 efe98965 Guido Trotter
  ] where new = compareNameComponent cstr lkp
187 efe98965 Guido Trotter
          partial2 = all ((PartialMatch==) . lrMatchPriority) [old, new]
188 efe98965 Guido Trotter
189 efe98965 Guido Trotter
-- | Find the canonical name for a lookup string in a list of names.
190 efe98965 Guido Trotter
lookupName :: [String]      -- ^ List of keys
191 efe98965 Guido Trotter
           -> String        -- ^ Lookup string
192 efe98965 Guido Trotter
           -> LookupResult  -- ^ Result of the lookup
193 efe98965 Guido Trotter
lookupName l s = foldr (chooseLookupResult s)
194 efe98965 Guido Trotter
                       (LookupResult FailMatch s) l
195 efe98965 Guido Trotter
196 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
197 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
198 497e30a1 Iustin Pop
                 [(String, a)]
199 99b63608 Iustin Pop
              -> (NameAssoc, Container.Container a)
200 2d0ca2c5 Iustin Pop
assignIndices nodes =
201 2d0ca2c5 Iustin Pop
  let (na, idx_node) =
202 2d0ca2c5 Iustin Pop
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
203 2d0ca2c5 Iustin Pop
          . zip [0..] $ nodes
204 cb0c77ff Iustin Pop
  in (M.fromList na, Container.fromList idx_node)
205 78694255 Iustin Pop
206 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
207 99b63608 Iustin Pop
fixNodes :: Node.List
208 aa8d2e71 Iustin Pop
         -> Instance.Instance
209 99b63608 Iustin Pop
         -> Node.List
210 aa8d2e71 Iustin Pop
fixNodes accu inst =
211 ebf38064 Iustin Pop
  let pdx = Instance.pNode inst
212 ebf38064 Iustin Pop
      sdx = Instance.sNode inst
213 ebf38064 Iustin Pop
      pold = Container.find pdx accu
214 ebf38064 Iustin Pop
      pnew = Node.setPri pold inst
215 ebf38064 Iustin Pop
      ac2 = Container.add pdx pnew accu
216 ebf38064 Iustin Pop
  in if sdx /= Node.noSecondary
217 ebf38064 Iustin Pop
       then let sold = Container.find sdx accu
218 ebf38064 Iustin Pop
                snew = Node.setSec sold inst
219 ebf38064 Iustin Pop
            in Container.add sdx snew ac2
220 ebf38064 Iustin Pop
       else ac2
221 e4c5beaf Iustin Pop
222 d6eec019 Iustin Pop
-- | Set the node's policy to its group one. Note that this requires
223 d6eec019 Iustin Pop
-- the group to exist (should have been checked before), otherwise it
224 d6eec019 Iustin Pop
-- will abort with a runtime error.
225 d6eec019 Iustin Pop
setNodePolicy :: Group.List -> Node.Node -> Node.Node
226 d6eec019 Iustin Pop
setNodePolicy gl node =
227 d6eec019 Iustin Pop
  let grp = Container.find (Node.group node) gl
228 d6eec019 Iustin Pop
      gpol = Group.iPolicy grp
229 d6eec019 Iustin Pop
  in Node.setPolicy gpol node
230 d6eec019 Iustin Pop
231 525bfb36 Iustin Pop
-- | Remove non-selected tags from the exclusion list.
232 0f15cc76 Iustin Pop
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
233 0f15cc76 Iustin Pop
filterExTags tl inst =
234 ebf38064 Iustin Pop
  let old_tags = Instance.tags inst
235 ebf38064 Iustin Pop
      new_tags = filter (\tag -> any (`isPrefixOf` tag) tl) old_tags
236 ebf38064 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 a7667ba6 Iustin Pop
  if Instance.name inst `elem` exinsts ||
245 ebf38064 Iustin Pop
     not (null selinsts || Instance.name inst `elem` selinsts)
246 39f979b8 Iustin Pop
    then Instance.setMovable inst False
247 39f979b8 Iustin Pop
    else inst
248 39f979b8 Iustin Pop
249 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
250 525bfb36 Iustin Pop
-- starts with a dot.
251 8472a321 Iustin Pop
longestDomain :: [String] -> String
252 e4c5beaf Iustin Pop
longestDomain [] = ""
253 8472a321 Iustin Pop
longestDomain (x:xs) =
254 ebf38064 Iustin Pop
  foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
255 ebf38064 Iustin Pop
                            then suffix
256 ebf38064 Iustin Pop
                            else accu)
257 ebf38064 Iustin Pop
          "" $ filter (isPrefixOf ".") (tails x)
258 e4c5beaf Iustin Pop
259 525bfb36 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration.
260 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
261 f5e67f55 Iustin Pop
extractExTags =
262 ebf38064 Iustin Pop
  map (drop (length exTagsPrefix)) .
263 ebf38064 Iustin Pop
  filter (isPrefixOf exTagsPrefix)
264 f5e67f55 Iustin Pop
265 525bfb36 Iustin Pop
-- | Extracts the common suffix from node\/instance names.
266 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
267 3e4480e0 Iustin Pop
commonSuffix nl il =
268 ebf38064 Iustin Pop
  let node_names = map Node.name $ Container.elems nl
269 ebf38064 Iustin Pop
      inst_names = map Instance.name $ Container.elems il
270 ebf38064 Iustin Pop
  in longestDomain (node_names ++ inst_names)
271 3e4480e0 Iustin Pop
272 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
273 9188aeef Iustin Pop
-- list and massages it into the correct format.
274 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
275 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
276 2d1708e0 Guido Trotter
          -> [String]             -- ^ Selected instances (if not empty)
277 2d1708e0 Guido Trotter
          -> [String]             -- ^ Excluded instances
278 f4f6eb0b Iustin Pop
          -> ClusterData          -- ^ Data from backends
279 c0e31451 Iustin Pop
          -> Result ClusterData   -- ^ Fixed cluster data
280 d6eec019 Iustin Pop
mergeData um extags selinsts exinsts cdata@(ClusterData gl nl il2 tags _) =
281 99b63608 Iustin Pop
  let il = Container.elems il2
282 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
283 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
284 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
285 a5f8dcdc Iustin Pop
                          Just inst ->
286 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
287 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
288 a5f8dcdc Iustin Pop
                   ) il2 um
289 f5e67f55 Iustin Pop
      allextags = extags ++ extractExTags tags
290 424ec11d Guido Trotter
      inst_names = map Instance.name il
291 424ec11d Guido Trotter
      selinst_lkp = map (lookupName inst_names) selinsts
292 424ec11d Guido Trotter
      exinst_lkp = map (lookupName inst_names) exinsts
293 424ec11d Guido Trotter
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
294 424ec11d Guido Trotter
      selinst_names = map lrContent selinst_lkp
295 424ec11d Guido Trotter
      exinst_names = map lrContent exinst_lkp
296 99b63608 Iustin Pop
      node_names = map Node.name (Container.elems nl)
297 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
298 cdbab531 Iustin Pop
      il4 = Container.map (computeAlias common_suffix .
299 cdbab531 Iustin Pop
                           filterExTags allextags .
300 cdbab531 Iustin Pop
                           updateMovable selinst_names exinst_names) il3
301 cdbab531 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
302 d6eec019 Iustin Pop
      nl3 = Container.map (setNodePolicy gl .
303 d6eec019 Iustin Pop
                           computeAlias common_suffix .
304 cdbab531 Iustin Pop
                           (`Node.buildPeers` il4)) nl2
305 424ec11d Guido Trotter
  in if' (null lkp_unknown)
306 cdbab531 Iustin Pop
         (Ok cdata { cdNodes = nl3, cdInstances = il4 })
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 61bbbed7 Agata Murawska
                 dilst = filter Instance.instanceDown 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 bdd8c739 Iustin Pop
                 umsg1 =
330 bdd8c739 Iustin Pop
                   if delta_mem > 512 || delta_dsk > 1024
331 3603605a Iustin Pop
                      then printf "node %s is missing %d MB ram \
332 3603605a Iustin Pop
                                  \and %d GB disk"
333 3603605a Iustin Pop
                                  nname delta_mem (delta_dsk `div` 1024):msgs
334 bdd8c739 Iustin Pop
                      else msgs
335 bdd8c739 Iustin Pop
             in (umsg1, newn)
336 446d8827 Iustin Pop
        ) [] nl
337 446d8827 Iustin Pop
338 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
339 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
340 446d8827 Iustin Pop
nodeImem node il =
341 ebf38064 Iustin Pop
  let rfind = flip Container.find il
342 ebf38064 Iustin Pop
      il' = map rfind $ Node.pList node
343 7959cbb9 Iustin Pop
      oil' = filter Instance.notOffline il'
344 ebf38064 Iustin Pop
  in sum . map Instance.mem $ oil'
345 61bbbed7 Agata Murawska
346 446d8827 Iustin Pop
347 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
348 446d8827 Iustin Pop
-- or secondary).
349 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
350 446d8827 Iustin Pop
nodeIdsk node il =
351 ebf38064 Iustin Pop
  let rfind = flip Container.find il
352 ebf38064 Iustin Pop
  in sum . map (Instance.dsk . rfind)
353 ebf38064 Iustin Pop
       $ Node.pList node ++ Node.sList node