Revision 00dd69a2 htools/Ganeti/HTools/IAlloc.hs

b/htools/Ganeti/HTools/IAlloc.hs
24 24
-}
25 25

  
26 26
module Ganeti.HTools.IAlloc
27
    ( readRequest
28
    , runIAllocator
29
    , processRelocate
30
    ) where
27
  ( readRequest
28
  , runIAllocator
29
  , processRelocate
30
  ) where
31 31

  
32 32
import Data.Either ()
33 33
import Data.Maybe (fromMaybe, isJust)
......
163 163
      map_g = cdGroups cdata
164 164
  optype <- extrReq "type"
165 165
  rqtype <-
166
      case () of
167
        _ | optype == C.iallocatorModeAlloc ->
168
              do
169
                rname     <- extrReq "name"
170
                req_nodes <- extrReq "required_nodes"
171
                inew      <- parseBaseInstance rname request
172
                let io = snd inew
173
                return $ Allocate io req_nodes
174
          | optype == C.iallocatorModeReloc ->
175
              do
176
                rname     <- extrReq "name"
177
                ridx      <- lookupInstance kti rname
178
                req_nodes <- extrReq "required_nodes"
179
                ex_nodes  <- extrReq "relocate_from"
180
                ex_idex   <- mapM (Container.findByName map_n) ex_nodes
181
                return $ Relocate ridx req_nodes (map Node.idx ex_idex)
182
          | optype == C.iallocatorModeChgGroup ->
183
              do
184
                rl_names <- extrReq "instances"
185
                rl_insts <- mapM (liftM Instance.idx .
186
                                  Container.findByName map_i) rl_names
187
                gr_uuids <- extrReq "target_groups"
188
                gr_idxes <- mapM (liftM Group.idx .
189
                                  Container.findByName map_g) gr_uuids
190
                return $ ChangeGroup rl_insts gr_idxes
191
          | optype == C.iallocatorModeNodeEvac ->
192
              do
193
                rl_names <- extrReq "instances"
194
                rl_insts <- mapM (Container.findByName map_i) rl_names
195
                let rl_idx = map Instance.idx rl_insts
196
                rl_mode <- extrReq "evac_mode"
197
                return $ NodeEvacuate rl_idx rl_mode
166
    case () of
167
      _ | optype == C.iallocatorModeAlloc ->
168
            do
169
              rname     <- extrReq "name"
170
              req_nodes <- extrReq "required_nodes"
171
              inew      <- parseBaseInstance rname request
172
              let io = snd inew
173
              return $ Allocate io req_nodes
174
        | optype == C.iallocatorModeReloc ->
175
            do
176
              rname     <- extrReq "name"
177
              ridx      <- lookupInstance kti rname
178
              req_nodes <- extrReq "required_nodes"
179
              ex_nodes  <- extrReq "relocate_from"
180
              ex_idex   <- mapM (Container.findByName map_n) ex_nodes
181
              return $ Relocate ridx req_nodes (map Node.idx ex_idex)
182
        | optype == C.iallocatorModeChgGroup ->
183
            do
184
              rl_names <- extrReq "instances"
185
              rl_insts <- mapM (liftM Instance.idx .
186
                                Container.findByName map_i) rl_names
187
              gr_uuids <- extrReq "target_groups"
188
              gr_idxes <- mapM (liftM Group.idx .
189
                                Container.findByName map_g) gr_uuids
190
              return $ ChangeGroup rl_insts gr_idxes
191
        | optype == C.iallocatorModeNodeEvac ->
192
            do
193
              rl_names <- extrReq "instances"
194
              rl_insts <- mapM (Container.findByName map_i) rl_names
195
              let rl_idx = map Instance.idx rl_insts
196
              rl_mode <- extrReq "evac_mode"
197
              return $ NodeEvacuate rl_idx rl_mode
198 198

  
199
          | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
199
        | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
200 200
  return (msgs, Request rqtype cdata)
201 201

  
202 202
-- | Formats the result into a valid IAllocator response message.
......
205 205
               -> JSValue  -- ^ The JSON encoded result
206 206
               -> String   -- ^ The full JSON-formatted message
207 207
formatResponse success info result =
208
    let
209
        e_success = ("success", showJSON success)
210
        e_info = ("info", showJSON info)
211
        e_result = ("result", result)
212
    in encodeStrict $ makeObj [e_success, e_info, e_result]
208
  let e_success = ("success", showJSON success)
209
      e_info = ("info", showJSON info)
210
      e_result = ("result", result)
211
  in encodeStrict $ makeObj [e_success, e_info, e_result]
213 212

  
214 213
-- | Flatten the log of a solution into a string.
215 214
describeSolution :: Cluster.AllocSolution -> String
......
222 221
  case Cluster.asSolution as of
223 222
    Nothing -> fail info
224 223
    Just (nl, inst, nodes, _) ->
225
        do
226
          let il' = Container.add (Instance.idx inst) inst il
227
          return (info, showJSON $ map Node.name nodes, nl, il')
224
      do
225
        let il' = Container.add (Instance.idx inst) inst il
226
        return (info, showJSON $ map Node.name nodes, nl, il')
228 227

  
229 228
-- | Convert a node-evacuation/change group result.
230 229
formatNodeEvac :: Group.List
......
233 232
               -> (Node.List, Instance.List, Cluster.EvacSolution)
234 233
               -> Result IAllocResult
235 234
formatNodeEvac gl nl il (fin_nl, fin_il, es) =
236
    let iname = Instance.name . flip Container.find il
237
        nname = Node.name . flip Container.find nl
238
        gname = Group.name . flip Container.find gl
239
        fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
240
        mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
241
              $ Cluster.esMoved es
242
        failed = length fes
243
        moved  = length mes
244
        info = show failed ++ " instances failed to move and " ++ show moved ++
245
               " were moved successfully"
246
    in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
235
  let iname = Instance.name . flip Container.find il
236
      nname = Node.name . flip Container.find nl
237
      gname = Group.name . flip Container.find gl
238
      fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
239
      mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
240
            $ Cluster.esMoved es
241
      failed = length fes
242
      moved  = length mes
243
      info = show failed ++ " instances failed to move and " ++ show moved ++
244
             " were moved successfully"
245
  in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
247 246

  
248 247
-- | Runs relocate for a single instance.
249 248
--
......
298 297
formatRelocate :: (Node.List, Instance.List, [Ndx])
299 298
               -> Result IAllocResult
300 299
formatRelocate (nl, il, ndxs) =
301
    let nodes = map (`Container.find` nl) ndxs
302
        names = map Node.name nodes
303
    in Ok ("success", showJSON names, nl, il)
300
  let nodes = map (`Container.find` nl) ndxs
301
      names = map Node.name nodes
302
  in Ok ("success", showJSON names, nl, il)
304 303

  
305 304
-- | Process a request and return new node lists.
306 305
processRequest :: Request -> Result IAllocResult
......
308 307
  let Request rqtype (ClusterData gl nl il _) = request
309 308
  in case rqtype of
310 309
       Allocate xi reqn ->
311
           Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
310
         Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
312 311
       Relocate idx reqn exnodes ->
313
           processRelocate gl nl il idx reqn exnodes >>= formatRelocate
312
         processRelocate gl nl il idx reqn exnodes >>= formatRelocate
314 313
       ChangeGroup gdxs idxs ->
315
           Cluster.tryChangeGroup gl nl il idxs gdxs >>=
316
                  formatNodeEvac gl nl il
314
         Cluster.tryChangeGroup gl nl il idxs gdxs >>=
315
                formatNodeEvac gl nl il
317 316
       NodeEvacuate xi mode ->
318
           Cluster.tryNodeEvac gl nl il mode xi >>=
319
                  formatNodeEvac gl nl il
317
         Cluster.tryNodeEvac gl nl il mode xi >>=
318
                formatNodeEvac gl nl il
320 319

  
321 320
-- | Reads the request from the data file(s).
322 321
readRequest :: Options -> [String] -> IO Request
323 322
readRequest opts args = do
324 323
  when (null args) $ do
325
         hPutStrLn stderr "Error: this program needs an input file."
326
         exitWith $ ExitFailure 1
324
    hPutStrLn stderr "Error: this program needs an input file."
325
    exitWith $ ExitFailure 1
327 326

  
328 327
  input_data <- readFile (head args)
329 328
  r1 <- case parseData input_data of
......
342 341
runIAllocator :: Request -> (Maybe (Node.List, Instance.List), String)
343 342
runIAllocator request =
344 343
  let (ok, info, result, cdata) =
345
          case processRequest request of
346
            Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
347
                                    Just (nl, il))
348
            Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
344
        case processRequest request of
345
          Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
346
                                  Just (nl, il))
347
          Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
349 348
      rstring = formatResponse ok info result
350 349
  in (cdata, rstring)

Also available in: Unified diff