Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 74c35f2f

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