Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Loader.hs @ 3e02cd3c

History | View | Annotate | Download (12.6 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
  , lookupNode
34 ebf38064 Iustin Pop
  , lookupInstance
35 ebf38064 Iustin Pop
  , lookupGroup
36 ebf38064 Iustin Pop
  , commonSuffix
37 ebf38064 Iustin Pop
  , RqType(..)
38 ebf38064 Iustin Pop
  , Request(..)
39 ebf38064 Iustin Pop
  , ClusterData(..)
40 ebf38064 Iustin Pop
  , emptyCluster
41 ebf38064 Iustin Pop
  ) where
42 040afc35 Iustin Pop
43 55416810 Dato Simó
import Control.Monad
44 e4c5beaf Iustin Pop
import Data.List
45 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
46 e79f576c Dato Simó
import Data.Maybe
47 446d8827 Iustin Pop
import Text.Printf (printf)
48 55416810 Dato Simó
import System.Time (ClockTime(..))
49 e4c5beaf Iustin Pop
50 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
51 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
52 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
53 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
54 a7e1fd89 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
55 e4c5beaf Iustin Pop
56 2fc5653f Iustin Pop
import Ganeti.BasicTypes
57 55416810 Dato Simó
import qualified Ganeti.Constants as C
58 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
59 26d62e4c Iustin Pop
import Ganeti.Utils
60 e4c5beaf Iustin Pop
61 f5e67f55 Iustin Pop
-- * Constants
62 f5e67f55 Iustin Pop
63 525bfb36 Iustin Pop
-- | The exclusion tag prefix.
64 f5e67f55 Iustin Pop
exTagsPrefix :: String
65 f5e67f55 Iustin Pop
exTagsPrefix = "htools:iextags:"
66 f5e67f55 Iustin Pop
67 19f38ee8 Iustin Pop
-- * Types
68 19f38ee8 Iustin Pop
69 54365762 Iustin Pop
{-| The iallocator request type.
70 19f38ee8 Iustin Pop
71 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
72 19f38ee8 Iustin Pop
request-specific fields.
73 19f38ee8 Iustin Pop
74 19f38ee8 Iustin Pop
-}
75 19f38ee8 Iustin Pop
data RqType
76 2a9aff11 René Nussbaumer
  = Allocate Instance.Instance Int           -- ^ A new instance allocation
77 2a9aff11 René Nussbaumer
  | Relocate Idx Int [Ndx]                   -- ^ Choose a new secondary node
78 2a9aff11 René Nussbaumer
  | NodeEvacuate [Idx] EvacMode              -- ^ node-evacuate mode
79 2a9aff11 René Nussbaumer
  | ChangeGroup [Gdx] [Idx]                  -- ^ Multi-relocate mode
80 2a9aff11 René Nussbaumer
  | MultiAllocate [(Instance.Instance, Int)] -- ^ Multi-allocate mode
81 139c0683 Iustin Pop
    deriving (Show)
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 139c0683 Iustin Pop
               deriving (Show)
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 139c0683 Iustin Pop
  } deriving (Show, Eq)
95 7b6e99b3 Iustin Pop
96 7b6e99b3 Iustin Pop
-- | An empty cluster.
97 7b6e99b3 Iustin Pop
emptyCluster :: ClusterData
98 7b6e99b3 Iustin Pop
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
99 71375ef7 Iustin Pop
                 defIPolicy
100 7b6e99b3 Iustin Pop
101 19f38ee8 Iustin Pop
-- * Functions
102 19f38ee8 Iustin Pop
103 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
104 6ff78049 Iustin Pop
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
105 040afc35 Iustin Pop
lookupNode ktn inst node =
106 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst) return $
107 76ae2e5b Iustin Pop
    M.lookup node ktn
108 040afc35 Iustin Pop
109 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
110 6ff78049 Iustin Pop
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
111 5a1edeb6 Iustin Pop
lookupInstance kti inst =
112 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown instance '" ++ inst ++ "'") return $ M.lookup inst kti
113 5a1edeb6 Iustin Pop
114 f4531f51 Iustin Pop
-- | Lookups a group into an assoc list.
115 f4531f51 Iustin Pop
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
116 f4531f51 Iustin Pop
lookupGroup ktg nname gname =
117 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname) return $
118 76ae2e5b Iustin Pop
    M.lookup gname ktg
119 f4531f51 Iustin Pop
120 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
121 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
122 497e30a1 Iustin Pop
                 [(String, a)]
123 99b63608 Iustin Pop
              -> (NameAssoc, Container.Container a)
124 07ac4aaf Guido Trotter
assignIndices name_element =
125 07ac4aaf Guido Trotter
  let (name_idx, idx_element) =
126 2d0ca2c5 Iustin Pop
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
127 07ac4aaf Guido Trotter
          . zip [0..] $ name_element
128 07ac4aaf Guido Trotter
  in (M.fromList name_idx, Container.fromList idx_element)
129 78694255 Iustin Pop
130 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
131 99b63608 Iustin Pop
fixNodes :: Node.List
132 aa8d2e71 Iustin Pop
         -> Instance.Instance
133 99b63608 Iustin Pop
         -> Node.List
134 aa8d2e71 Iustin Pop
fixNodes accu inst =
135 ebf38064 Iustin Pop
  let pdx = Instance.pNode inst
136 ebf38064 Iustin Pop
      sdx = Instance.sNode inst
137 ebf38064 Iustin Pop
      pold = Container.find pdx accu
138 ebf38064 Iustin Pop
      pnew = Node.setPri pold inst
139 ebf38064 Iustin Pop
      ac2 = Container.add pdx pnew accu
140 ebf38064 Iustin Pop
  in if sdx /= Node.noSecondary
141 ebf38064 Iustin Pop
       then let sold = Container.find sdx accu
142 ebf38064 Iustin Pop
                snew = Node.setSec sold inst
143 ebf38064 Iustin Pop
            in Container.add sdx snew ac2
144 ebf38064 Iustin Pop
       else ac2
145 e4c5beaf Iustin Pop
146 d6eec019 Iustin Pop
-- | Set the node's policy to its group one. Note that this requires
147 d6eec019 Iustin Pop
-- the group to exist (should have been checked before), otherwise it
148 d6eec019 Iustin Pop
-- will abort with a runtime error.
149 d6eec019 Iustin Pop
setNodePolicy :: Group.List -> Node.Node -> Node.Node
150 d6eec019 Iustin Pop
setNodePolicy gl node =
151 d6eec019 Iustin Pop
  let grp = Container.find (Node.group node) gl
152 d6eec019 Iustin Pop
      gpol = Group.iPolicy grp
153 d6eec019 Iustin Pop
  in Node.setPolicy gpol node
154 d6eec019 Iustin Pop
155 2f907bad Dato Simó
-- | Update instance with exclusion tags list.
156 2f907bad Dato Simó
updateExclTags :: [String] -> Instance.Instance -> Instance.Instance
157 2f907bad Dato Simó
updateExclTags tl inst =
158 2f907bad Dato Simó
  let allTags = Instance.allTags inst
159 2f907bad Dato Simó
      exclTags = filter (\tag -> any (`isPrefixOf` tag) tl) allTags
160 2f907bad Dato Simó
  in inst { Instance.exclTags = exclTags }
161 0f15cc76 Iustin Pop
162 525bfb36 Iustin Pop
-- | Update the movable attribute.
163 c6ccc073 Guido Trotter
updateMovable :: [String]           -- ^ Selected instances (if not empty)
164 c6ccc073 Guido Trotter
              -> [String]           -- ^ Excluded instances
165 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance
166 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance with updated attribute
167 c6ccc073 Guido Trotter
updateMovable selinsts exinsts inst =
168 a7667ba6 Iustin Pop
  if Instance.name inst `elem` exinsts ||
169 ebf38064 Iustin Pop
     not (null selinsts || Instance.name inst `elem` selinsts)
170 39f979b8 Iustin Pop
    then Instance.setMovable inst False
171 39f979b8 Iustin Pop
    else inst
172 39f979b8 Iustin Pop
173 a7e1fd89 Iustin Pop
-- | Disables moves for instances with a split group.
174 a7e1fd89 Iustin Pop
disableSplitMoves :: Node.List -> Instance.Instance -> Instance.Instance
175 a7e1fd89 Iustin Pop
disableSplitMoves nl inst =
176 a7e1fd89 Iustin Pop
  if not . isOk . Cluster.instanceGroup nl $ inst
177 a7e1fd89 Iustin Pop
    then Instance.setMovable inst False
178 a7e1fd89 Iustin Pop
    else inst
179 a7e1fd89 Iustin Pop
180 55416810 Dato Simó
-- | Set the auto-repair policy for an instance.
181 55416810 Dato Simó
setArPolicy :: [String]       -- ^ Cluster tags
182 55416810 Dato Simó
            -> Group.List     -- ^ List of node groups
183 55416810 Dato Simó
            -> Node.List      -- ^ List of nodes
184 55416810 Dato Simó
            -> Instance.List  -- ^ List of instances
185 ef947a42 Dato Simó
            -> ClockTime      -- ^ Current timestamp, to evaluate ArSuspended
186 55416810 Dato Simó
            -> Instance.List  -- ^ Updated list of instances
187 ef947a42 Dato Simó
setArPolicy ctags gl nl il time =
188 ef947a42 Dato Simó
  let getArPolicy' = flip getArPolicy time
189 ef947a42 Dato Simó
      cpol = fromMaybe ArNotEnabled $ getArPolicy' ctags
190 ef947a42 Dato Simó
      gpols = Container.map (fromMaybe cpol . getArPolicy' . Group.allTags) gl
191 ef947a42 Dato Simó
      ipolfn = getArPolicy' . Instance.allTags
192 55416810 Dato Simó
      nlookup = flip Container.find nl . Instance.pNode
193 55416810 Dato Simó
      glookup = flip Container.find gpols . Node.group . nlookup
194 55416810 Dato Simó
      updateInstance inst = inst {
195 55416810 Dato Simó
        Instance.arPolicy = fromMaybe (glookup inst) $ ipolfn inst }
196 55416810 Dato Simó
  in
197 55416810 Dato Simó
   Container.map updateInstance il
198 55416810 Dato Simó
199 55416810 Dato Simó
-- | Get the auto-repair policy from a list of tags.
200 55416810 Dato Simó
--
201 55416810 Dato Simó
-- This examines the ganeti:watcher:autorepair and
202 55416810 Dato Simó
-- ganeti:watcher:autorepair:suspend tags to determine the policy. If none of
203 55416810 Dato Simó
-- these tags are present, Nothing (and not ArNotEnabled) is returned.
204 ef947a42 Dato Simó
getArPolicy :: [String] -> ClockTime -> Maybe AutoRepairPolicy
205 ef947a42 Dato Simó
getArPolicy tags time =
206 55416810 Dato Simó
  let enabled = mapMaybe (autoRepairTypeFromRaw <=<
207 55416810 Dato Simó
                          chompPrefix C.autoRepairTagEnabled) tags
208 55416810 Dato Simó
      suspended = mapMaybe (chompPrefix C.autoRepairTagSuspended) tags
209 ef947a42 Dato Simó
      futureTs = filter (> time) . map (flip TOD 0) $
210 ef947a42 Dato Simó
                   mapMaybe (tryRead "auto-repair suspend time") suspended
211 55416810 Dato Simó
  in
212 55416810 Dato Simó
   case () of
213 55416810 Dato Simó
     -- Note how we must return ArSuspended even if "enabled" is empty, so that
214 55416810 Dato Simó
     -- node groups or instances can suspend repairs that were enabled at an
215 55416810 Dato Simó
     -- upper scope (cluster or node group).
216 ef947a42 Dato Simó
     _ | "" `elem` suspended -> Just $ ArSuspended Forever
217 ef947a42 Dato Simó
       | not $ null futureTs -> Just . ArSuspended . Until . maximum $ futureTs
218 ef947a42 Dato Simó
       | not $ null enabled  -> Just $ ArEnabled (minimum enabled)
219 ef947a42 Dato Simó
       | otherwise           -> Nothing
220 55416810 Dato Simó
221 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
222 525bfb36 Iustin Pop
-- starts with a dot.
223 8472a321 Iustin Pop
longestDomain :: [String] -> String
224 e4c5beaf Iustin Pop
longestDomain [] = ""
225 8472a321 Iustin Pop
longestDomain (x:xs) =
226 ebf38064 Iustin Pop
  foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
227 ebf38064 Iustin Pop
                            then suffix
228 ebf38064 Iustin Pop
                            else accu)
229 ebf38064 Iustin Pop
          "" $ filter (isPrefixOf ".") (tails x)
230 e4c5beaf Iustin Pop
231 525bfb36 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration.
232 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
233 e79f576c Dato Simó
extractExTags = filter (not . null) . mapMaybe (chompPrefix exTagsPrefix)
234 f5e67f55 Iustin Pop
235 525bfb36 Iustin Pop
-- | Extracts the common suffix from node\/instance names.
236 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
237 3e4480e0 Iustin Pop
commonSuffix nl il =
238 ebf38064 Iustin Pop
  let node_names = map Node.name $ Container.elems nl
239 ebf38064 Iustin Pop
      inst_names = map Instance.name $ Container.elems il
240 ebf38064 Iustin Pop
  in longestDomain (node_names ++ inst_names)
241 3e4480e0 Iustin Pop
242 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
243 9188aeef Iustin Pop
-- list and massages it into the correct format.
244 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
245 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
246 2d1708e0 Guido Trotter
          -> [String]             -- ^ Selected instances (if not empty)
247 2d1708e0 Guido Trotter
          -> [String]             -- ^ Excluded instances
248 ef947a42 Dato Simó
          -> ClockTime            -- ^ The current timestamp
249 f4f6eb0b Iustin Pop
          -> ClusterData          -- ^ Data from backends
250 c0e31451 Iustin Pop
          -> Result ClusterData   -- ^ Fixed cluster data
251 ef947a42 Dato Simó
mergeData um extags selinsts exinsts time cdata@(ClusterData gl nl il ctags _) =
252 ef947a42 Dato Simó
  let il2 = setArPolicy ctags gl nl il time
253 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
254 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
255 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
256 a5f8dcdc Iustin Pop
                          Just inst ->
257 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
258 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
259 a5f8dcdc Iustin Pop
                   ) il2 um
260 55416810 Dato Simó
      allextags = extags ++ extractExTags ctags
261 55416810 Dato Simó
      inst_names = map Instance.name $ Container.elems il3
262 424ec11d Guido Trotter
      selinst_lkp = map (lookupName inst_names) selinsts
263 424ec11d Guido Trotter
      exinst_lkp = map (lookupName inst_names) exinsts
264 424ec11d Guido Trotter
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
265 424ec11d Guido Trotter
      selinst_names = map lrContent selinst_lkp
266 424ec11d Guido Trotter
      exinst_names = map lrContent exinst_lkp
267 99b63608 Iustin Pop
      node_names = map Node.name (Container.elems nl)
268 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
269 cdbab531 Iustin Pop
      il4 = Container.map (computeAlias common_suffix .
270 2f907bad Dato Simó
                           updateExclTags allextags .
271 cdbab531 Iustin Pop
                           updateMovable selinst_names exinst_names) il3
272 cdbab531 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
273 d6eec019 Iustin Pop
      nl3 = Container.map (setNodePolicy gl .
274 d6eec019 Iustin Pop
                           computeAlias common_suffix .
275 cdbab531 Iustin Pop
                           (`Node.buildPeers` il4)) nl2
276 a7e1fd89 Iustin Pop
      il5 = Container.map (disableSplitMoves nl3) il4
277 424ec11d Guido Trotter
  in if' (null lkp_unknown)
278 a7e1fd89 Iustin Pop
         (Ok cdata { cdNodes = nl3, cdInstances = il5 })
279 424ec11d Guido Trotter
         (Bad $ "Unknown instance(s): " ++ show(map lrContent lkp_unknown))
280 446d8827 Iustin Pop
281 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
282 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
283 262a08a2 Iustin Pop
          -> ([String], Node.List)
284 dbd6700b Iustin Pop
checkData nl il =
285 446d8827 Iustin Pop
    Container.mapAccum
286 446d8827 Iustin Pop
        (\ msgs node ->
287 dbd6700b Iustin Pop
             let nname = Node.name node
288 5182e970 Iustin Pop
                 nilst = map (`Container.find` il) (Node.pList node)
289 61bbbed7 Agata Murawska
                 dilst = filter Instance.instanceDown nilst
290 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
291 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
292 2060348b Iustin Pop
                             - Node.nMem node
293 2060348b Iustin Pop
                             - Node.fMem node
294 9f6dcdea Iustin Pop
                             - nodeImem node il
295 446d8827 Iustin Pop
                             + adj_mem
296 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
297 2060348b Iustin Pop
                             - Node.fDsk node
298 9f6dcdea Iustin Pop
                             - nodeIdsk node il
299 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
300 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
301 bdd8c739 Iustin Pop
                 umsg1 =
302 bdd8c739 Iustin Pop
                   if delta_mem > 512 || delta_dsk > 1024
303 3603605a Iustin Pop
                      then printf "node %s is missing %d MB ram \
304 3603605a Iustin Pop
                                  \and %d GB disk"
305 3603605a Iustin Pop
                                  nname delta_mem (delta_dsk `div` 1024):msgs
306 bdd8c739 Iustin Pop
                      else msgs
307 bdd8c739 Iustin Pop
             in (umsg1, newn)
308 446d8827 Iustin Pop
        ) [] nl
309 446d8827 Iustin Pop
310 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
311 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
312 446d8827 Iustin Pop
nodeImem node il =
313 ebf38064 Iustin Pop
  let rfind = flip Container.find il
314 ebf38064 Iustin Pop
      il' = map rfind $ Node.pList node
315 7959cbb9 Iustin Pop
      oil' = filter Instance.notOffline il'
316 ebf38064 Iustin Pop
  in sum . map Instance.mem $ oil'
317 61bbbed7 Agata Murawska
318 446d8827 Iustin Pop
319 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
320 446d8827 Iustin Pop
-- or secondary).
321 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
322 446d8827 Iustin Pop
nodeIdsk node il =
323 ebf38064 Iustin Pop
  let rfind = flip Container.find il
324 ebf38064 Iustin Pop
  in sum . map (Instance.dsk . rfind)
325 ebf38064 Iustin Pop
       $ Node.pList node ++ Node.sList node