Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 2c9336a4

History | View | Annotate | Download (14.1 kB)

1 43643696 Iustin Pop
{-| Implementation of the iallocator interface.
2 43643696 Iustin Pop
3 43643696 Iustin Pop
-}
4 43643696 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e8230242 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 43643696 Iustin Pop
module Ganeti.HTools.IAlloc
27 00152519 Iustin Pop
    ( readRequest
28 00152519 Iustin Pop
    , runIAllocator
29 6804faa0 Iustin Pop
    , processRelocate
30 43643696 Iustin Pop
    ) where
31 43643696 Iustin Pop
32 43643696 Iustin Pop
import Data.Either ()
33 00152519 Iustin Pop
import Data.Maybe (fromMaybe, isJust)
34 cabce2f4 Iustin Pop
import Data.List
35 43643696 Iustin Pop
import Control.Monad
36 34c5a24a Iustin Pop
import Text.JSON (JSObject, JSValue(JSArray),
37 34c5a24a Iustin Pop
                  makeObj, encodeStrict, decodeStrict, fromJSObject, showJSON)
38 cabce2f4 Iustin Pop
import System (exitWith, ExitCode(..))
39 cabce2f4 Iustin Pop
import System.IO
40 cabce2f4 Iustin Pop
41 cabce2f4 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
42 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
43 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
44 942403e6 Iustin Pop
import qualified Ganeti.HTools.Node as Node
45 942403e6 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
46 df5227dc Iustin Pop
import qualified Ganeti.Constants as C
47 cabce2f4 Iustin Pop
import Ganeti.HTools.CLI
48 e4c5beaf Iustin Pop
import Ganeti.HTools.Loader
49 cabce2f4 Iustin Pop
import Ganeti.HTools.ExtLoader (loadExternalData)
50 e4c5beaf Iustin Pop
import Ganeti.HTools.Utils
51 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
52 43643696 Iustin Pop
53 7c14b50a Iustin Pop
-- | Type alias for the result of an IAllocator call.
54 f9283686 Iustin Pop
type IAllocResult = (String, JSValue, Node.List, Instance.List)
55 7c14b50a Iustin Pop
56 9188aeef Iustin Pop
-- | Parse the basic specifications of an instance.
57 9188aeef Iustin Pop
--
58 9188aeef Iustin Pop
-- Instances in the cluster instance list and the instance in an
59 9188aeef Iustin Pop
-- 'Allocate' request share some common properties, which are read by
60 9188aeef Iustin Pop
-- this function.
61 e4c5beaf Iustin Pop
parseBaseInstance :: String
62 28f19313 Iustin Pop
                  -> JSRecord
63 e4c5beaf Iustin Pop
                  -> Result (String, Instance.Instance)
64 e4c5beaf Iustin Pop
parseBaseInstance n a = do
65 e8230242 Iustin Pop
  let extract x = tryFromObj ("invalid data for instance '" ++ n ++ "'") a x
66 e8230242 Iustin Pop
  disk  <- extract "disk_space_total"
67 e8230242 Iustin Pop
  mem   <- extract "memory"
68 e8230242 Iustin Pop
  vcpus <- extract "vcpus"
69 e8230242 Iustin Pop
  tags  <- extract "tags"
70 5a4a3b7f Iustin Pop
  dt    <- extract "disk_template"
71 e4c5beaf Iustin Pop
  let running = "running"
72 5a4a3b7f Iustin Pop
  return (n, Instance.create n mem disk vcpus running tags True 0 0 dt)
73 585d4420 Iustin Pop
74 525bfb36 Iustin Pop
-- | Parses an instance as found in the cluster instance list.
75 28f19313 Iustin Pop
parseInstance :: NameAssoc -- ^ The node name-to-index association list
76 28f19313 Iustin Pop
              -> String    -- ^ The name of the instance
77 28f19313 Iustin Pop
              -> JSRecord  -- ^ The JSON object
78 e4c5beaf Iustin Pop
              -> Result (String, Instance.Instance)
79 e4c5beaf Iustin Pop
parseInstance ktn n a = do
80 262f3e6c Iustin Pop
  base <- parseBaseInstance n a
81 e8230242 Iustin Pop
  nodes <- fromObj a "nodes"
82 e41f4ba0 Iustin Pop
  pnode <- if null nodes
83 e41f4ba0 Iustin Pop
           then Bad $ "empty node list for instance " ++ n
84 e41f4ba0 Iustin Pop
           else readEitherString $ head nodes
85 262f3e6c Iustin Pop
  pidx <- lookupNode ktn n pnode
86 262f3e6c Iustin Pop
  let snodes = tail nodes
87 262f3e6c Iustin Pop
  sidx <- (if null snodes then return Node.noSecondary
88 262f3e6c Iustin Pop
           else readEitherString (head snodes) >>= lookupNode ktn n)
89 262f3e6c Iustin Pop
  return (n, Instance.setBoth (snd base) pidx sidx)
90 585d4420 Iustin Pop
91 9188aeef Iustin Pop
-- | Parses a node as found in the cluster node list.
92 28f19313 Iustin Pop
parseNode :: NameAssoc   -- ^ The group association
93 28f19313 Iustin Pop
          -> String      -- ^ The node's name
94 28f19313 Iustin Pop
          -> JSRecord    -- ^ The JSON object
95 9188aeef Iustin Pop
          -> Result (String, Node.Node)
96 10ef6b4e Iustin Pop
parseNode ktg n a = do
97 3eeea90f Iustin Pop
  let desc = "invalid data for node '" ++ n ++ "'"
98 3eeea90f Iustin Pop
      extract x = tryFromObj desc a x
99 e8230242 Iustin Pop
  offline <- extract "offline"
100 e8230242 Iustin Pop
  drained <- extract "drained"
101 e8230242 Iustin Pop
  guuid   <- extract "group"
102 3eeea90f Iustin Pop
  vm_capable  <- annotateResult desc $ maybeFromObj a "vm_capable"
103 3eeea90f Iustin Pop
  let vm_capable' = fromMaybe True vm_capable
104 10ef6b4e Iustin Pop
  gidx <- lookupGroup ktg n guuid
105 3eeea90f Iustin Pop
  node <- (if offline || drained || not vm_capable'
106 10ef6b4e Iustin Pop
           then return $ Node.create n 0 0 0 0 0 0 True gidx
107 262f3e6c Iustin Pop
           else do
108 e8230242 Iustin Pop
             mtotal <- extract "total_memory"
109 e8230242 Iustin Pop
             mnode  <- extract "reserved_memory"
110 e8230242 Iustin Pop
             mfree  <- extract "free_memory"
111 e8230242 Iustin Pop
             dtotal <- extract "total_disk"
112 e8230242 Iustin Pop
             dfree  <- extract "free_disk"
113 e8230242 Iustin Pop
             ctotal <- extract "total_cpus"
114 262f3e6c Iustin Pop
             return $ Node.create n mtotal mnode mfree
115 10ef6b4e Iustin Pop
                    dtotal dfree ctotal False gidx)
116 262f3e6c Iustin Pop
  return (n, node)
117 144f190b Iustin Pop
118 a679e9dc Iustin Pop
-- | Parses a group as found in the cluster group list.
119 28f19313 Iustin Pop
parseGroup :: String     -- ^ The group UUID
120 28f19313 Iustin Pop
           -> JSRecord   -- ^ The JSON object
121 a679e9dc Iustin Pop
           -> Result (String, Group.Group)
122 a679e9dc Iustin Pop
parseGroup u a = do
123 1b2cb110 Iustin Pop
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
124 1b2cb110 Iustin Pop
  name <- extract "name"
125 1b2cb110 Iustin Pop
  apol <- extract "alloc_policy"
126 1b2cb110 Iustin Pop
  return (u, Group.create name u apol)
127 a679e9dc Iustin Pop
128 9188aeef Iustin Pop
-- | Top-level parser.
129 96a12113 Iustin Pop
--
130 96a12113 Iustin Pop
-- The result is a tuple of eventual warning messages and the parsed
131 96a12113 Iustin Pop
-- request; if parsing the input data fails, we'll return a 'Bad'
132 96a12113 Iustin Pop
-- value.
133 96a12113 Iustin Pop
parseData :: String -- ^ The JSON message as received from Ganeti
134 96a12113 Iustin Pop
          -> Result ([String], Request) -- ^ Result tuple
135 e4c5beaf Iustin Pop
parseData body = do
136 c96d44df Iustin Pop
  decoded <- fromJResult "Parsing input IAllocator message" (decodeStrict body)
137 262f3e6c Iustin Pop
  let obj = fromJSObject decoded
138 e8230242 Iustin Pop
      extrObj x = tryFromObj "invalid iallocator message" obj x
139 e4c5beaf Iustin Pop
  -- request parser
140 e8230242 Iustin Pop
  request <- liftM fromJSObject (extrObj "request")
141 e8230242 Iustin Pop
  let extrReq x = tryFromObj "invalid request dict" request x
142 a679e9dc Iustin Pop
  -- existing group parsing
143 e8230242 Iustin Pop
  glist <- liftM fromJSObject (extrObj "nodegroups")
144 a679e9dc Iustin Pop
  gobj <- mapM (\(x, y) -> asJSObject y >>= parseGroup x . fromJSObject) glist
145 10ef6b4e Iustin Pop
  let (ktg, gl) = assignIndices gobj
146 e4c5beaf Iustin Pop
  -- existing node parsing
147 e8230242 Iustin Pop
  nlist <- liftM fromJSObject (extrObj "nodes")
148 10ef6b4e Iustin Pop
  nobj <- mapM (\(x,y) ->
149 10ef6b4e Iustin Pop
                    asJSObject y >>= parseNode ktg x . fromJSObject) nlist
150 497e30a1 Iustin Pop
  let (ktn, nl) = assignIndices nobj
151 e4c5beaf Iustin Pop
  -- existing instance parsing
152 e8230242 Iustin Pop
  ilist <- extrObj "instances"
153 e4c5beaf Iustin Pop
  let idata = fromJSObject ilist
154 262f3e6c Iustin Pop
  iobj <- mapM (\(x,y) ->
155 262f3e6c Iustin Pop
                    asJSObject y >>= parseInstance ktn x . fromJSObject) idata
156 88df1fa9 Iustin Pop
  let (kti, il) = assignIndices iobj
157 669ea132 Iustin Pop
  -- cluster tags
158 e8230242 Iustin Pop
  ctags <- extrObj "cluster_tags"
159 96a12113 Iustin Pop
  cdata1 <- mergeData [] [] [] [] (ClusterData gl nl il ctags)
160 96a12113 Iustin Pop
  let (msgs, fix_nl) = checkData (cdNodes cdata1) (cdInstances cdata1)
161 96a12113 Iustin Pop
      cdata = cdata1 { cdNodes = fix_nl }
162 88df1fa9 Iustin Pop
      map_n = cdNodes cdata
163 695c1bab Iustin Pop
      map_i = cdInstances cdata
164 695c1bab Iustin Pop
      map_g = cdGroups cdata
165 e8230242 Iustin Pop
  optype <- extrReq "type"
166 e4c5beaf Iustin Pop
  rqtype <-
167 df5227dc Iustin Pop
      case () of
168 df5227dc Iustin Pop
        _ | optype == C.iallocatorModeAlloc ->
169 df5227dc Iustin Pop
              do
170 df5227dc Iustin Pop
                rname     <- extrReq "name"
171 df5227dc Iustin Pop
                req_nodes <- extrReq "required_nodes"
172 df5227dc Iustin Pop
                inew      <- parseBaseInstance rname request
173 df5227dc Iustin Pop
                let io = snd inew
174 df5227dc Iustin Pop
                return $ Allocate io req_nodes
175 88df1fa9 Iustin Pop
          | optype == C.iallocatorModeReloc ->
176 88df1fa9 Iustin Pop
              do
177 88df1fa9 Iustin Pop
                rname     <- extrReq "name"
178 88df1fa9 Iustin Pop
                ridx      <- lookupInstance kti rname
179 88df1fa9 Iustin Pop
                req_nodes <- extrReq "required_nodes"
180 88df1fa9 Iustin Pop
                ex_nodes  <- extrReq "relocate_from"
181 88df1fa9 Iustin Pop
                ex_idex   <- mapM (Container.findByName map_n) ex_nodes
182 88df1fa9 Iustin Pop
                return $ Relocate ridx req_nodes (map Node.idx ex_idex)
183 57f07ff2 Iustin Pop
          | optype == C.iallocatorModeChgGroup ->
184 695c1bab Iustin Pop
              do
185 695c1bab Iustin Pop
                rl_names <- extrReq "instances"
186 57f07ff2 Iustin Pop
                rl_insts <- mapM (liftM Instance.idx .
187 57f07ff2 Iustin Pop
                                  Container.findByName map_i) rl_names
188 57f07ff2 Iustin Pop
                gr_uuids <- extrReq "target_groups"
189 57f07ff2 Iustin Pop
                gr_idxes <- mapM (liftM Group.idx .
190 57f07ff2 Iustin Pop
                                  Container.findByName map_g) gr_uuids
191 57f07ff2 Iustin Pop
                return $ ChangeGroup rl_insts gr_idxes
192 4e84ca27 Iustin Pop
          | optype == C.iallocatorModeNodeEvac ->
193 4e84ca27 Iustin Pop
              do
194 4e84ca27 Iustin Pop
                rl_names <- extrReq "instances"
195 4e84ca27 Iustin Pop
                rl_insts <- mapM (Container.findByName map_i) rl_names
196 4e84ca27 Iustin Pop
                let rl_idx = map Instance.idx rl_insts
197 9f8b97ce Iustin Pop
                rl_mode <- extrReq "evac_mode"
198 4e84ca27 Iustin Pop
                return $ NodeEvacuate rl_idx rl_mode
199 695c1bab Iustin Pop
200 df5227dc Iustin Pop
          | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
201 1b0a6356 Iustin Pop
  return (msgs, Request rqtype cdata)
202 942403e6 Iustin Pop
203 d6cf394e Iustin Pop
-- | Formats the result into a valid IAllocator response message.
204 9188aeef Iustin Pop
formatResponse :: Bool     -- ^ Whether the request was successful
205 9188aeef Iustin Pop
               -> String   -- ^ Information text
206 d6cf394e Iustin Pop
               -> JSValue  -- ^ The JSON encoded result
207 d6cf394e Iustin Pop
               -> String   -- ^ The full JSON-formatted message
208 d6cf394e Iustin Pop
formatResponse success info result =
209 43643696 Iustin Pop
    let
210 34c5a24a Iustin Pop
        e_success = ("success", showJSON success)
211 34c5a24a Iustin Pop
        e_info = ("info", showJSON info)
212 d6cf394e Iustin Pop
        e_result = ("result", result)
213 b5cec17a Iustin Pop
    in encodeStrict $ makeObj [e_success, e_info, e_result]
214 cabce2f4 Iustin Pop
215 7c14b50a Iustin Pop
-- | Flatten the log of a solution into a string.
216 7c14b50a Iustin Pop
describeSolution :: Cluster.AllocSolution -> String
217 7c14b50a Iustin Pop
describeSolution = intercalate ", " . Cluster.asLog
218 cabce2f4 Iustin Pop
219 7c14b50a Iustin Pop
-- | Convert allocation/relocation results into the result format.
220 f9283686 Iustin Pop
formatAllocate :: Instance.List -> Cluster.AllocSolution -> Result IAllocResult
221 f9283686 Iustin Pop
formatAllocate il as = do
222 7c14b50a Iustin Pop
  let info = describeSolution as
223 129734d3 Iustin Pop
  case Cluster.asSolution as of
224 129734d3 Iustin Pop
    Nothing -> fail info
225 129734d3 Iustin Pop
    Just (nl, inst, nodes, _) ->
226 f9283686 Iustin Pop
        do
227 f9283686 Iustin Pop
          let il' = Container.add (Instance.idx inst) inst il
228 1b0a6356 Iustin Pop
          return (info, showJSON $ map Node.name nodes, nl, il')
229 cabce2f4 Iustin Pop
230 47eed3f4 Iustin Pop
-- | Convert a node-evacuation/change group result.
231 5440c877 Iustin Pop
formatNodeEvac :: Group.List
232 5440c877 Iustin Pop
               -> Node.List
233 5440c877 Iustin Pop
               -> Instance.List
234 4036f63a Iustin Pop
               -> (Node.List, Instance.List, Cluster.EvacSolution)
235 5440c877 Iustin Pop
               -> Result IAllocResult
236 f9283686 Iustin Pop
formatNodeEvac gl nl il (fin_nl, fin_il, es) =
237 5440c877 Iustin Pop
    let iname = Instance.name . flip Container.find il
238 5440c877 Iustin Pop
        nname = Node.name . flip Container.find nl
239 5440c877 Iustin Pop
        gname = Group.name . flip Container.find gl
240 5440c877 Iustin Pop
        fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
241 5440c877 Iustin Pop
        mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
242 5440c877 Iustin Pop
              $ Cluster.esMoved es
243 47eed3f4 Iustin Pop
        failed = length fes
244 47eed3f4 Iustin Pop
        moved  = length mes
245 47eed3f4 Iustin Pop
        info = show failed ++ " instances failed to move and " ++ show moved ++
246 47eed3f4 Iustin Pop
               " were moved successfully"
247 f9283686 Iustin Pop
    in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
248 47eed3f4 Iustin Pop
249 88df1fa9 Iustin Pop
-- | Runs relocate for a single instance.
250 88df1fa9 Iustin Pop
--
251 88df1fa9 Iustin Pop
-- This is wrapper over the 'Cluster.tryNodeEvac' function that is run
252 88df1fa9 Iustin Pop
-- with a single instance (ours), and further it checks that the
253 88df1fa9 Iustin Pop
-- result it got (in the nodes field) is actually consistent, as
254 88df1fa9 Iustin Pop
-- tryNodeEvac is designed to output primarily an opcode list, not a
255 88df1fa9 Iustin Pop
-- node list.
256 88df1fa9 Iustin Pop
processRelocate :: Group.List      -- ^ The group list
257 88df1fa9 Iustin Pop
                -> Node.List       -- ^ The node list
258 88df1fa9 Iustin Pop
                -> Instance.List   -- ^ The instance list
259 88df1fa9 Iustin Pop
                -> Idx             -- ^ The index of the instance to move
260 88df1fa9 Iustin Pop
                -> Int             -- ^ The number of nodes required
261 88df1fa9 Iustin Pop
                -> [Ndx]           -- ^ Nodes which should not be used
262 88df1fa9 Iustin Pop
                -> Result (Node.List, Instance.List, [Ndx]) -- ^ Solution list
263 88df1fa9 Iustin Pop
processRelocate gl nl il idx 1 exndx = do
264 88df1fa9 Iustin Pop
  let orig = Container.find idx il
265 88df1fa9 Iustin Pop
      sorig = Instance.sNode orig
266 88df1fa9 Iustin Pop
  when (exndx /= [sorig]) $
267 88df1fa9 Iustin Pop
       -- FIXME: we can't use the excluded nodes here; the logic is
268 88df1fa9 Iustin Pop
       -- already _but only partially_ implemented in tryNodeEvac...
269 88df1fa9 Iustin Pop
       fail $ "Unsupported request: excluded nodes not equal to\
270 88df1fa9 Iustin Pop
              \ instance's secondary node (" ++ show sorig ++ " versus " ++
271 88df1fa9 Iustin Pop
              show exndx ++ ")"
272 88df1fa9 Iustin Pop
  (nl', il', esol) <- Cluster.tryNodeEvac gl nl il ChangeSecondary [idx]
273 88df1fa9 Iustin Pop
  nodes <- case lookup idx (Cluster.esFailed esol) of
274 88df1fa9 Iustin Pop
             Just msg -> fail msg
275 88df1fa9 Iustin Pop
             Nothing ->
276 88df1fa9 Iustin Pop
                 case lookup idx (map (\(a, _, b) -> (a, b))
277 88df1fa9 Iustin Pop
                                  (Cluster.esMoved esol)) of
278 88df1fa9 Iustin Pop
                   Nothing ->
279 88df1fa9 Iustin Pop
                       fail "Internal error: lost instance idx during move"
280 88df1fa9 Iustin Pop
                   Just n -> return n
281 88df1fa9 Iustin Pop
  let inst = Container.find idx il'
282 88df1fa9 Iustin Pop
      pnode = Instance.pNode inst
283 88df1fa9 Iustin Pop
      snode = Instance.sNode inst
284 88df1fa9 Iustin Pop
  when (snode == sorig) $
285 88df1fa9 Iustin Pop
       fail "Internal error: instance didn't change secondary node?!"
286 f25508be Iustin Pop
  when (snode == pnode) $
287 f25508be Iustin Pop
       fail "Internal error: selected primary as new secondary?!"
288 88df1fa9 Iustin Pop
289 88df1fa9 Iustin Pop
  nodes' <- if (nodes == [pnode, snode])
290 88df1fa9 Iustin Pop
            then return [snode] -- only the new secondary is needed
291 88df1fa9 Iustin Pop
            else fail $ "Internal error: inconsistent node list (" ++
292 88df1fa9 Iustin Pop
                 show nodes ++ ") versus instance nodes (" ++ show pnode ++
293 88df1fa9 Iustin Pop
                 "," ++ show snode ++ ")"
294 88df1fa9 Iustin Pop
  return (nl', il', nodes')
295 88df1fa9 Iustin Pop
296 88df1fa9 Iustin Pop
processRelocate _ _ _ _ reqn _ =
297 88df1fa9 Iustin Pop
  fail $ "Exchange " ++ show reqn ++ " nodes mode is not implemented"
298 88df1fa9 Iustin Pop
299 88df1fa9 Iustin Pop
formatRelocate :: (Node.List, Instance.List, [Ndx])
300 88df1fa9 Iustin Pop
               -> Result IAllocResult
301 88df1fa9 Iustin Pop
formatRelocate (nl, il, ndxs) =
302 88df1fa9 Iustin Pop
    let nodes = map (`Container.find` nl) ndxs
303 88df1fa9 Iustin Pop
        names = map Node.name nodes
304 88df1fa9 Iustin Pop
    in Ok ("success", showJSON names, nl, il)
305 88df1fa9 Iustin Pop
306 179c0828 Iustin Pop
-- | Process a request and return new node lists.
307 7c14b50a Iustin Pop
processRequest :: Request -> Result IAllocResult
308 cabce2f4 Iustin Pop
processRequest request =
309 cabce2f4 Iustin Pop
  let Request rqtype (ClusterData gl nl il _) = request
310 cabce2f4 Iustin Pop
  in case rqtype of
311 7c14b50a Iustin Pop
       Allocate xi reqn ->
312 f9283686 Iustin Pop
           Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
313 88df1fa9 Iustin Pop
       Relocate idx reqn exnodes ->
314 88df1fa9 Iustin Pop
           processRelocate gl nl il idx reqn exnodes >>= formatRelocate
315 20b376ff Iustin Pop
       ChangeGroup gdxs idxs ->
316 5440c877 Iustin Pop
           Cluster.tryChangeGroup gl nl il idxs gdxs >>=
317 5440c877 Iustin Pop
                  formatNodeEvac gl nl il
318 47eed3f4 Iustin Pop
       NodeEvacuate xi mode ->
319 5440c877 Iustin Pop
           Cluster.tryNodeEvac gl nl il mode xi >>=
320 5440c877 Iustin Pop
                  formatNodeEvac gl nl il
321 cabce2f4 Iustin Pop
322 179c0828 Iustin Pop
-- | Reads the request from the data file(s).
323 cabce2f4 Iustin Pop
readRequest :: Options -> [String] -> IO Request
324 cabce2f4 Iustin Pop
readRequest opts args = do
325 cabce2f4 Iustin Pop
  when (null args) $ do
326 cabce2f4 Iustin Pop
         hPutStrLn stderr "Error: this program needs an input file."
327 cabce2f4 Iustin Pop
         exitWith $ ExitFailure 1
328 cabce2f4 Iustin Pop
329 cabce2f4 Iustin Pop
  input_data <- readFile (head args)
330 cabce2f4 Iustin Pop
  r1 <- case parseData input_data of
331 cabce2f4 Iustin Pop
          Bad err -> do
332 cabce2f4 Iustin Pop
            hPutStrLn stderr $ "Error: " ++ err
333 cabce2f4 Iustin Pop
            exitWith $ ExitFailure 1
334 96a12113 Iustin Pop
          Ok (fix_msgs, rq) -> maybeShowWarnings fix_msgs >> return rq
335 cabce2f4 Iustin Pop
  (if isJust (optDataFile opts) ||  (not . null . optNodeSim) opts
336 cabce2f4 Iustin Pop
   then do
337 cabce2f4 Iustin Pop
     cdata <- loadExternalData opts
338 cabce2f4 Iustin Pop
     let Request rqt _ = r1
339 cabce2f4 Iustin Pop
     return $ Request rqt cdata
340 cabce2f4 Iustin Pop
   else return r1)
341 00152519 Iustin Pop
342 00152519 Iustin Pop
-- | Main iallocator pipeline.
343 f9283686 Iustin Pop
runIAllocator :: Request -> (Maybe (Node.List, Instance.List), String)
344 00152519 Iustin Pop
runIAllocator request =
345 f9283686 Iustin Pop
  let (ok, info, result, cdata) =
346 7c14b50a Iustin Pop
          case processRequest request of
347 f9283686 Iustin Pop
            Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
348 f9283686 Iustin Pop
                                    Just (nl, il))
349 ce6a0b53 Iustin Pop
            Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
350 ce6a0b53 Iustin Pop
      rstring = formatResponse ok info result
351 f9283686 Iustin Pop
  in (cdata, rstring)