Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ 519edd9f

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