Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Loader.hs @ b9202225

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