Revision aa8d2e71

b/Ganeti/HTools/ExtLoader.hs
52 52

  
53 53
import Ganeti.HTools.Types
54 54
import Ganeti.HTools.CLI
55
import Ganeti.HTools.Utils (sepSplit, tryRead)
55 56

  
56 57
-- | Parse the environment and return the node\/instance names.
57 58
--
......
66 67
wrapIO :: IO (Result a) -> IO (Result a)
67 68
wrapIO = flip catch (return . Bad . show)
68 69

  
70
parseUtilisation :: String -> Result (String, DynUtil)
71
parseUtilisation line =
72
    let columns = sepSplit ' ' line
73
    in case columns of
74
         [name, cpu, mem, dsk, net] -> do
75
                      rcpu <- tryRead name cpu
76
                      rmem <- tryRead name mem
77
                      rdsk <- tryRead name dsk
78
                      rnet <- tryRead name net
79
                      let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
80
                                       , dskWeight = rdsk, netWeight = rnet }
81
                      return (name, du)
82
         _ -> Bad $ "Cannot parse line " ++ line
83

  
69 84
-- | External tool data loader from a variety of sources.
70 85
loadExternalData :: Options
71 86
                 -> IO (Node.List, Instance.List, String)
......
89 104
                           " files options should be given.")
90 105
         exitWith $ ExitFailure 1
91 106

  
107
  util_contents <- (case optDynuFile opts of
108
                      Just path -> readFile path
109
                      Nothing -> return "")
110
  let util_data = mapM parseUtilisation $ lines util_contents
111
  util_data' <- (case util_data of
112
                   Ok x -> return x
113
                   Bad y -> do
114
                     hPutStrLn stderr ("Error: can't parse utilisation" ++
115
                                       " data: " ++ show y)
116
                     exitWith $ ExitFailure 1)
92 117
  input_data <-
93 118
      case () of
94 119
        _ | setRapi ->
......
101 126
          | setSim -> Simu.loadData $ fromJust simdata
102 127
          | otherwise -> wrapIO $ Text.loadData nodef instf
103 128

  
104
  let ldresult = input_data >>= Loader.mergeData
129
  let ldresult = input_data >>= Loader.mergeData util_data'
105 130
  (loaded_nl, il, csf) <-
106 131
      (case ldresult of
107 132
         Ok x -> return x
b/Ganeti/HTools/IAlloc.hs
110 110
  let idata = fromJSObject ilist
111 111
  iobj <- mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x) idata
112 112
  let (kti, il) = assignIndices iobj
113
  (map_n, map_i, csf) <- mergeData (nl, il)
113
  (map_n, map_i, csf) <- mergeData [] (nl, il)
114 114
  req_nodes <- fromObj "required_nodes" request
115 115
  optype <- fromObj "type" request
116 116
  rqtype <-
b/Ganeti/HTools/Loader.hs
37 37
    , Request(..)
38 38
    ) where
39 39

  
40
import Control.Monad (foldM)
40 41
import Data.Function (on)
41 42
import Data.List
42 43
import Data.Maybe (fromJust)
......
96 97

  
97 98
-- | For each instance, add its index to its primary and secondary nodes.
98 99
fixNodes :: [(Ndx, Node.Node)]
99
         -> (Idx, Instance.Instance)
100
         -> Instance.Instance
100 101
         -> [(Ndx, Node.Node)]
101
fixNodes accu (_, inst) =
102
fixNodes accu inst =
102 103
    let
103 104
        pdx = Instance.pNode inst
104 105
        sdx = Instance.sNode inst
......
130 131

  
131 132
-- | Initializer function that loads the data from a node and instance
132 133
-- list and massages it into the correct format.
133
mergeData :: (Node.AssocList,
134
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
135
          -> (Node.AssocList,
134 136
              Instance.AssocList) -- ^ Data from either Text.loadData
135 137
                                  -- or Rapi.loadData
136 138
          -> Result (Node.List, Instance.List, String)
137
mergeData (nl, il) = do
138
  let
139
      nl2 = foldl' fixNodes nl il
140
      il3 = Container.fromAssocList il
141
      nl3 = Container.fromAssocList
139
mergeData um (nl, il) = do
140
  let il2 = Container.fromAssocList il
141
  il3 <- foldM (\im (name, n_util) -> do
142
                  idx <- Container.findByName im name
143
                  let inst = Container.find idx im
144
                      new_i = inst { Instance.util = n_util }
145
                  return $ Container.add idx new_i im
146
               ) il2 um
147
  let nl2 = foldl' fixNodes nl (Container.elems il3)
148
  let nl3 = Container.fromAssocList
142 149
            (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
143 150
      node_names = map Node.name $ Container.elems nl3
144 151
      inst_names = map Instance.name $ Container.elems il3
b/Ganeti/HTools/Node.hs
26 26
-}
27 27

  
28 28
module Ganeti.HTools.Node
29
    ( Node(failN1, name, idx,
30
           tMem, nMem, fMem, rMem, xMem,
31
           tDsk, fDsk,
32
           tCpu, uCpu,
33
           pMem, pDsk, pRem, pCpu,
34
           mDsk, mCpu, loDsk, hiCpu,
35
           pList, sList, offline)
29
    ( Node(..)
36 30
    , List
37 31
    -- * Constructor
38 32
    , create
......
217 211
    in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
218 212

  
219 213
-- | Assigns an instance to a node as primary and update the used VCPU
220
-- count.
214
-- count and utilisation data.
221 215
setPri :: Node -> Instance.Instance -> Node
222
setPri t inst = t { pList = (Instance.idx inst):pList t
216
setPri t inst = t { pList = Instance.idx inst:pList t
223 217
                  , uCpu = new_count
224
                  , pCpu = fromIntegral new_count / tCpu t }
218
                  , pCpu = fromIntegral new_count / tCpu t
219
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
220
                  }
225 221
    where new_count = uCpu t + Instance.vcpus inst
226 222

  
227 223
-- | Assigns an instance to a node as secondary without other updates.
228 224
setSec :: Node -> Instance.Instance -> Node
229
setSec t inst = t { sList = (Instance.idx inst):sList t }
225
setSec t inst = t { sList = Instance.idx inst:sList t
226
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
227
                                          T.dskWeight (Instance.util inst) }
228
                  }
229
    where old_load = utilLoad t
230 230

  
231 231
-- * Update functions
232 232

  
......
250 250
        new_failn1 = new_mem <= rMem t
251 251
        new_ucpu = uCpu t - Instance.vcpus inst
252 252
        new_rcpu = fromIntegral new_ucpu / tCpu t
253
        new_load = utilLoad t `T.subUtil` Instance.util inst
253 254
    in t {pList = new_plist, fMem = new_mem, fDsk = new_dsk,
254 255
          failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
255
          uCpu = new_ucpu, pCpu = new_rcpu}
256
          uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load}
256 257

  
257 258
-- | Removes a secondary instance.
258 259
removeSec :: Node -> Instance.Instance -> Node
......
273 274
        new_prem = fromIntegral new_rmem / tMem t
274 275
        new_failn1 = fMem t <= new_rmem
275 276
        new_dp = fromIntegral new_dsk / tDsk t
277
        old_load = utilLoad t
278
        new_load = old_load { T.dskWeight = T.dskWeight old_load -
279
                                            T.dskWeight (Instance.util inst) }
276 280
    in t {sList = new_slist, fDsk = new_dsk, peers = new_peers,
277 281
          failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp,
278
          pRem = new_prem}
282
          pRem = new_prem, utilLoad = new_load}
279 283

  
280 284
-- | Adds a primary instance.
281 285
addPri :: Node -> Instance.Instance -> T.OpResult Node
......
288 292
        new_pcpu = fromIntegral new_ucpu / tCpu t
289 293
        new_dp = fromIntegral new_dsk / tDsk t
290 294
        l_cpu = mCpu t
295
        new_load = utilLoad t `T.addUtil` Instance.util inst
291 296
    in if new_mem <= 0 then T.OpFail T.FailMem
292 297
       else if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
293 298
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
......
297 302
               new_mp = fromIntegral new_mem / tMem t
298 303
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk,
299 304
                       failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
300
                       uCpu = new_ucpu, pCpu = new_pcpu }
305
                       uCpu = new_ucpu, pCpu = new_pcpu, utilLoad = new_load }
301 306
           in T.OpGood r
302 307

  
303 308
-- | Adds a secondary instance.
......
313 318
        new_prem = fromIntegral new_rmem / tMem t
314 319
        new_failn1 = old_mem <= new_rmem
315 320
        new_dp = fromIntegral new_dsk / tDsk t
321
        old_load = utilLoad t
322
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
323
                                            T.dskWeight (Instance.util inst) }
316 324
    in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
317 325
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
318 326
       else let new_slist = iname:sList t
319 327
                r = t { sList = new_slist, fDsk = new_dsk,
320 328
                        peers = new_peers, failN1 = new_failn1,
321 329
                        rMem = new_rmem, pDsk = new_dp,
322
                        pRem = new_prem }
330
                        pRem = new_prem, utilLoad = new_load }
323 331
           in T.OpGood r
324 332

  
325 333
-- * Stats functions
b/hbal.hs
72 72
    , oMaxCpu
73 73
    , oMinDisk
74 74
    , oDiskMoves
75
    , oDynuFile
75 76
    , oShowVer
76 77
    , oShowHelp
77 78
    ]
b/hscan.hs
135 135
              printf "%-*s " nlen name
136 136
              hFlush stdout
137 137
              input_data <- Rapi.loadData name
138
              let ldresult = input_data >>= Loader.mergeData
138
              let ldresult = input_data >>= Loader.mergeData []
139 139
              (case ldresult of
140 140
                 Bad err -> printf "\nError: failed to load data. \
141 141
                                   \Details:\n%s\n" err

Also available in: Unified diff