Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ d605e261

History | View | Annotate | Download (11.4 kB)

1 a0090487 Agata Murawska
{-# LANGUAGE TemplateHaskell #-}
2 a0090487 Agata Murawska
3 6583e677 Iustin Pop
{-| Implementation of the Ganeti LUXI interface.
4 6583e677 Iustin Pop
5 6583e677 Iustin Pop
-}
6 6583e677 Iustin Pop
7 6583e677 Iustin Pop
{-
8 6583e677 Iustin Pop
9 71a4c605 Petr Pudlak
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
10 6583e677 Iustin Pop
11 6583e677 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 6583e677 Iustin Pop
it under the terms of the GNU General Public License as published by
13 6583e677 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 6583e677 Iustin Pop
(at your option) any later version.
15 6583e677 Iustin Pop
16 6583e677 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 6583e677 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 6583e677 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 6583e677 Iustin Pop
General Public License for more details.
20 6583e677 Iustin Pop
21 6583e677 Iustin Pop
You should have received a copy of the GNU General Public License
22 6583e677 Iustin Pop
along with this program; if not, write to the Free Software
23 6583e677 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 6583e677 Iustin Pop
02110-1301, USA.
25 6583e677 Iustin Pop
26 6583e677 Iustin Pop
-}
27 6583e677 Iustin Pop
28 6583e677 Iustin Pop
module Ganeti.Luxi
29 ebf38064 Iustin Pop
  ( LuxiOp(..)
30 95d0d502 Iustin Pop
  , LuxiReq(..)
31 ebf38064 Iustin Pop
  , Client
32 ccc817a2 Iustin Pop
  , JobId
33 c48711d5 Iustin Pop
  , fromJobId
34 c48711d5 Iustin Pop
  , makeJobId
35 0aff2293 Iustin Pop
  , RecvResult(..)
36 0aff2293 Iustin Pop
  , strOfOp
37 d605e261 Petr Pudlak
  , getLuxiClient
38 d605e261 Petr Pudlak
  , getLuxiServer
39 13f2321c Iustin Pop
  , acceptClient
40 ebf38064 Iustin Pop
  , closeClient
41 0aff2293 Iustin Pop
  , closeServer
42 ebf38064 Iustin Pop
  , callMethod
43 ebf38064 Iustin Pop
  , submitManyJobs
44 ebf38064 Iustin Pop
  , queryJobsStatus
45 cdd495ae Iustin Pop
  , buildCall
46 0aff2293 Iustin Pop
  , buildResponse
47 cdd495ae Iustin Pop
  , validateCall
48 cdd495ae Iustin Pop
  , decodeCall
49 13f2321c Iustin Pop
  , recvMsg
50 0aff2293 Iustin Pop
  , recvMsgExt
51 13f2321c Iustin Pop
  , sendMsg
52 471b6c46 Iustin Pop
  , allLuxiCalls
53 ebf38064 Iustin Pop
  ) where
54 6583e677 Iustin Pop
55 6583e677 Iustin Pop
import Control.Monad
56 71a4c605 Petr Pudlak
import qualified Data.ByteString.UTF8 as UTF8
57 0903280b Iustin Pop
import Text.JSON (encodeStrict, decodeStrict)
58 6583e677 Iustin Pop
import qualified Text.JSON as J
59 7adb7dff Iustin Pop
import Text.JSON.Pretty (pp_value)
60 6583e677 Iustin Pop
import Text.JSON.Types
61 6583e677 Iustin Pop
62 4cd79ca8 Iustin Pop
import Ganeti.BasicTypes
63 92678b3c Iustin Pop
import Ganeti.Constants
64 7adb7dff Iustin Pop
import Ganeti.Errors
65 7adb7dff Iustin Pop
import Ganeti.JSON
66 71a4c605 Petr Pudlak
import Ganeti.UDSServer
67 fa10983e Iustin Pop
import Ganeti.OpParams (pTagsObject)
68 367c4241 Dato Simó
import Ganeti.OpCodes
69 4cab6703 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
70 a0090487 Agata Murawska
import Ganeti.THH
71 c48711d5 Iustin Pop
import Ganeti.Types
72 6583e677 Iustin Pop
73 0aff2293 Iustin Pop
74 a0090487 Agata Murawska
-- | Currently supported Luxi operations and JSON serialization.
75 a0090487 Agata Murawska
$(genLuxiOp "LuxiOp"
76 72295708 Iustin Pop
  [ (luxiReqQuery,
77 88609f00 Iustin Pop
    [ simpleField "what"    [t| Qlang.ItemType |]
78 88609f00 Iustin Pop
    , simpleField "fields"  [t| [String]  |]
79 88609f00 Iustin Pop
    , simpleField "qfilter" [t| Qlang.Filter Qlang.FilterField |]
80 ebf38064 Iustin Pop
    ])
81 72295708 Iustin Pop
  , (luxiReqQueryFields,
82 88609f00 Iustin Pop
    [ simpleField "what"    [t| Qlang.ItemType |]
83 88609f00 Iustin Pop
    , simpleField "fields"  [t| [String]  |]
84 72295708 Iustin Pop
    ])
85 fae980e5 Iustin Pop
  , (luxiReqQueryNodes,
86 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
87 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
88 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
89 ebf38064 Iustin Pop
     ])
90 fae980e5 Iustin Pop
  , (luxiReqQueryGroups,
91 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
92 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
93 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
94 ebf38064 Iustin Pop
     ])
95 795d035d Klaus Aehlig
  , (luxiReqQueryNetworks,
96 795d035d Klaus Aehlig
     [ simpleField "names"  [t| [String] |]
97 795d035d Klaus Aehlig
     , simpleField "fields" [t| [String] |]
98 795d035d Klaus Aehlig
     , simpleField "lock"   [t| Bool     |]
99 795d035d Klaus Aehlig
     ])
100 fae980e5 Iustin Pop
  , (luxiReqQueryInstances,
101 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
102 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
103 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
104 ebf38064 Iustin Pop
     ])
105 fae980e5 Iustin Pop
  , (luxiReqQueryJobs,
106 c48711d5 Iustin Pop
     [ simpleField "ids"    [t| [JobId]  |]
107 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
108 ebf38064 Iustin Pop
     ])
109 fae980e5 Iustin Pop
  , (luxiReqQueryExports,
110 88609f00 Iustin Pop
     [ simpleField "nodes" [t| [String] |]
111 88609f00 Iustin Pop
     , simpleField "lock"  [t| Bool     |]
112 ebf38064 Iustin Pop
     ])
113 fae980e5 Iustin Pop
  , (luxiReqQueryConfigValues,
114 88609f00 Iustin Pop
     [ simpleField "fields" [t| [String] |] ]
115 ebf38064 Iustin Pop
    )
116 fae980e5 Iustin Pop
  , (luxiReqQueryClusterInfo, [])
117 fae980e5 Iustin Pop
  , (luxiReqQueryTags,
118 34af39e8 Jose A. Lopes
     [ pTagsObject 
119 34af39e8 Jose A. Lopes
     , simpleField "name" [t| String |]
120 34af39e8 Jose A. Lopes
     ])
121 fae980e5 Iustin Pop
  , (luxiReqSubmitJob,
122 7e723913 Iustin Pop
     [ simpleField "job" [t| [MetaOpCode] |] ]
123 ebf38064 Iustin Pop
    )
124 346c3037 Klaus Aehlig
  , (luxiReqSubmitJobToDrainedQueue,
125 346c3037 Klaus Aehlig
     [ simpleField "job" [t| [MetaOpCode] |] ]
126 346c3037 Klaus Aehlig
    )
127 fae980e5 Iustin Pop
  , (luxiReqSubmitManyJobs,
128 7e723913 Iustin Pop
     [ simpleField "ops" [t| [[MetaOpCode]] |] ]
129 ebf38064 Iustin Pop
    )
130 fae980e5 Iustin Pop
  , (luxiReqWaitForJobChange,
131 c48711d5 Iustin Pop
     [ simpleField "job"      [t| JobId   |]
132 88609f00 Iustin Pop
     , simpleField "fields"   [t| [String]|]
133 88609f00 Iustin Pop
     , simpleField "prev_job" [t| JSValue |]
134 88609f00 Iustin Pop
     , simpleField "prev_log" [t| JSValue |]
135 88609f00 Iustin Pop
     , simpleField "tmout"    [t| Int     |]
136 ebf38064 Iustin Pop
     ])
137 d9d1e541 Klaus Aehlig
  , (luxiReqPickupJob,
138 d9d1e541 Klaus Aehlig
     [ simpleField "job" [t| JobId |] ]
139 d9d1e541 Klaus Aehlig
    )
140 fae980e5 Iustin Pop
  , (luxiReqArchiveJob,
141 c48711d5 Iustin Pop
     [ simpleField "job" [t| JobId |] ]
142 ebf38064 Iustin Pop
    )
143 fae980e5 Iustin Pop
  , (luxiReqAutoArchiveJobs,
144 88609f00 Iustin Pop
     [ simpleField "age"   [t| Int |]
145 88609f00 Iustin Pop
     , simpleField "tmout" [t| Int |]
146 ebf38064 Iustin Pop
     ])
147 fae980e5 Iustin Pop
  , (luxiReqCancelJob,
148 c48711d5 Iustin Pop
     [ simpleField "job" [t| JobId |] ]
149 ebf38064 Iustin Pop
    )
150 f63ffb37 Michael Hanselmann
  , (luxiReqChangeJobPriority,
151 c48711d5 Iustin Pop
     [ simpleField "job"      [t| JobId |]
152 f63ffb37 Michael Hanselmann
     , simpleField "priority" [t| Int |] ]
153 f63ffb37 Michael Hanselmann
    )
154 fae980e5 Iustin Pop
  , (luxiReqSetDrainFlag,
155 88609f00 Iustin Pop
     [ simpleField "flag" [t| Bool |] ]
156 ebf38064 Iustin Pop
    )
157 fae980e5 Iustin Pop
  , (luxiReqSetWatcherPause,
158 88609f00 Iustin Pop
     [ simpleField "duration" [t| Double |] ]
159 ebf38064 Iustin Pop
    )
160 a0090487 Agata Murawska
  ])
161 6583e677 Iustin Pop
162 95d0d502 Iustin Pop
$(makeJSONInstance ''LuxiReq)
163 95d0d502 Iustin Pop
164 471b6c46 Iustin Pop
-- | List of all defined Luxi calls.
165 471b6c46 Iustin Pop
$(genAllConstr (drop 3) ''LuxiReq "allLuxiCalls")
166 471b6c46 Iustin Pop
167 6583e677 Iustin Pop
-- | The serialisation of LuxiOps into strings in messages.
168 a0090487 Agata Murawska
$(genStrOfOp ''LuxiOp "strOfOp")
169 6583e677 Iustin Pop
170 cdd495ae Iustin Pop
-- | Type holding the initial (unparsed) Luxi call.
171 cdd495ae Iustin Pop
data LuxiCall = LuxiCall LuxiReq JSValue
172 cdd495ae Iustin Pop
173 6583e677 Iustin Pop
-- | Serialize a request to String.
174 6583e677 Iustin Pop
buildCall :: LuxiOp  -- ^ The method
175 6583e677 Iustin Pop
          -> String  -- ^ The serialized form
176 683b1ca7 Iustin Pop
buildCall lo =
177 2cdaf225 Iustin Pop
  let ja = [ (strOfKey Method, J.showJSON $ strOfOp lo)
178 2cdaf225 Iustin Pop
           , (strOfKey Args, opToArgs lo)
179 ebf38064 Iustin Pop
           ]
180 ebf38064 Iustin Pop
      jo = toJSObject ja
181 ebf38064 Iustin Pop
  in encodeStrict jo
182 6583e677 Iustin Pop
183 cdd495ae Iustin Pop
-- | Check that luxi request contains the required keys and parse it.
184 cdd495ae Iustin Pop
validateCall :: String -> Result LuxiCall
185 cdd495ae Iustin Pop
validateCall s = do
186 0aff2293 Iustin Pop
  arr <- fromJResult "parsing top-level luxi message" $
187 0aff2293 Iustin Pop
         decodeStrict s::Result (JSObject JSValue)
188 cdd495ae Iustin Pop
  let aobj = fromJSObject arr
189 cdd495ae Iustin Pop
  call <- fromObj aobj (strOfKey Method)::Result LuxiReq
190 cdd495ae Iustin Pop
  args <- fromObj aobj (strOfKey Args)
191 cdd495ae Iustin Pop
  return (LuxiCall call args)
192 cdd495ae Iustin Pop
193 cdd495ae Iustin Pop
-- | Converts Luxi call arguments into a 'LuxiOp' data structure.
194 cdd495ae Iustin Pop
--
195 cdd495ae Iustin Pop
-- This is currently hand-coded until we make it more uniform so that
196 cdd495ae Iustin Pop
-- it can be generated using TH.
197 cdd495ae Iustin Pop
decodeCall :: LuxiCall -> Result LuxiOp
198 cdd495ae Iustin Pop
decodeCall (LuxiCall call args) =
199 cdd495ae Iustin Pop
  case call of
200 cdd495ae Iustin Pop
    ReqQueryJobs -> do
201 c48711d5 Iustin Pop
              (jids, jargs) <- fromJVal args
202 d2970809 Iustin Pop
              jids' <- case jids of
203 d2970809 Iustin Pop
                         JSNull -> return []
204 d2970809 Iustin Pop
                         _ -> fromJVal jids
205 d2970809 Iustin Pop
              return $ QueryJobs jids' jargs
206 cdd495ae Iustin Pop
    ReqQueryInstances -> do
207 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
208 cdd495ae Iustin Pop
              return $ QueryInstances names fields locking
209 cdd495ae Iustin Pop
    ReqQueryNodes -> do
210 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
211 cdd495ae Iustin Pop
              return $ QueryNodes names fields locking
212 cdd495ae Iustin Pop
    ReqQueryGroups -> do
213 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
214 cdd495ae Iustin Pop
              return $ QueryGroups names fields locking
215 5b11f8db Iustin Pop
    ReqQueryClusterInfo ->
216 cdd495ae Iustin Pop
              return QueryClusterInfo
217 795d035d Klaus Aehlig
    ReqQueryNetworks -> do
218 795d035d Klaus Aehlig
              (names, fields, locking) <- fromJVal args
219 795d035d Klaus Aehlig
              return $ QueryNetworks names fields locking
220 cdd495ae Iustin Pop
    ReqQuery -> do
221 9a94c848 Iustin Pop
              (what, fields, qfilter) <- fromJVal args
222 9a94c848 Iustin Pop
              return $ Query what fields qfilter
223 72295708 Iustin Pop
    ReqQueryFields -> do
224 72295708 Iustin Pop
              (what, fields) <- fromJVal args
225 72295708 Iustin Pop
              fields' <- case fields of
226 72295708 Iustin Pop
                           JSNull -> return []
227 72295708 Iustin Pop
                           _ -> fromJVal fields
228 72295708 Iustin Pop
              return $ QueryFields what fields'
229 cdd495ae Iustin Pop
    ReqSubmitJob -> do
230 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
231 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
232 cdd495ae Iustin Pop
              return $ SubmitJob ops2
233 346c3037 Klaus Aehlig
    ReqSubmitJobToDrainedQueue -> do
234 346c3037 Klaus Aehlig
              [ops1] <- fromJVal args
235 346c3037 Klaus Aehlig
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
236 346c3037 Klaus Aehlig
              return $ SubmitJobToDrainedQueue ops2
237 cdd495ae Iustin Pop
    ReqSubmitManyJobs -> do
238 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
239 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
240 cdd495ae Iustin Pop
              return $ SubmitManyJobs ops2
241 cdd495ae Iustin Pop
    ReqWaitForJobChange -> do
242 cdd495ae Iustin Pop
              (jid, fields, pinfo, pidx, wtmout) <-
243 cdd495ae Iustin Pop
                -- No instance for 5-tuple, code copied from the
244 cdd495ae Iustin Pop
                -- json sources and adapted
245 cdd495ae Iustin Pop
                fromJResult "Parsing WaitForJobChange message" $
246 cdd495ae Iustin Pop
                case args of
247 cdd495ae Iustin Pop
                  JSArray [a, b, c, d, e] ->
248 cdd495ae Iustin Pop
                    (,,,,) `fmap`
249 cdd495ae Iustin Pop
                    J.readJSON a `ap`
250 cdd495ae Iustin Pop
                    J.readJSON b `ap`
251 cdd495ae Iustin Pop
                    J.readJSON c `ap`
252 cdd495ae Iustin Pop
                    J.readJSON d `ap`
253 cdd495ae Iustin Pop
                    J.readJSON e
254 cdd495ae Iustin Pop
                  _ -> J.Error "Not enough values"
255 c48711d5 Iustin Pop
              return $ WaitForJobChange jid fields pinfo pidx wtmout
256 d9d1e541 Klaus Aehlig
    ReqPickupJob -> do
257 d9d1e541 Klaus Aehlig
              [jid] <- fromJVal args
258 d9d1e541 Klaus Aehlig
              return $ PickupJob jid
259 cdd495ae Iustin Pop
    ReqArchiveJob -> do
260 cdd495ae Iustin Pop
              [jid] <- fromJVal args
261 c48711d5 Iustin Pop
              return $ ArchiveJob jid
262 cdd495ae Iustin Pop
    ReqAutoArchiveJobs -> do
263 cdd495ae Iustin Pop
              (age, tmout) <- fromJVal args
264 cdd495ae Iustin Pop
              return $ AutoArchiveJobs age tmout
265 cdd495ae Iustin Pop
    ReqQueryExports -> do
266 cdd495ae Iustin Pop
              (nodes, lock) <- fromJVal args
267 cdd495ae Iustin Pop
              return $ QueryExports nodes lock
268 cdd495ae Iustin Pop
    ReqQueryConfigValues -> do
269 cdd495ae Iustin Pop
              [fields] <- fromJVal args
270 cdd495ae Iustin Pop
              return $ QueryConfigValues fields
271 cdd495ae Iustin Pop
    ReqQueryTags -> do
272 cdd495ae Iustin Pop
              (kind, name) <- fromJVal args
273 34af39e8 Jose A. Lopes
              return $ QueryTags kind name
274 cdd495ae Iustin Pop
    ReqCancelJob -> do
275 c48711d5 Iustin Pop
              [jid] <- fromJVal args
276 c48711d5 Iustin Pop
              return $ CancelJob jid
277 f63ffb37 Michael Hanselmann
    ReqChangeJobPriority -> do
278 c48711d5 Iustin Pop
              (jid, priority) <- fromJVal args
279 c48711d5 Iustin Pop
              return $ ChangeJobPriority jid priority
280 cdd495ae Iustin Pop
    ReqSetDrainFlag -> do
281 cdd495ae Iustin Pop
              [flag] <- fromJVal args
282 cdd495ae Iustin Pop
              return $ SetDrainFlag flag
283 cdd495ae Iustin Pop
    ReqSetWatcherPause -> do
284 cdd495ae Iustin Pop
              [duration] <- fromJVal args
285 cdd495ae Iustin Pop
              return $ SetWatcherPause duration
286 cdd495ae Iustin Pop
287 6583e677 Iustin Pop
-- | Check that luxi responses contain the required keys and that the
288 6583e677 Iustin Pop
-- call was successful.
289 7adb7dff Iustin Pop
validateResult :: String -> ErrorResult JSValue
290 6583e677 Iustin Pop
validateResult s = do
291 e821050d Iustin Pop
  when (UTF8.replacement_char `elem` s) $
292 e821050d Iustin Pop
       fail "Failed to decode UTF-8, detected replacement char after decoding"
293 7adb7dff Iustin Pop
  oarr <- fromJResult "Parsing LUXI response" (decodeStrict s)
294 262f3e6c Iustin Pop
  let arr = J.fromJSObject oarr
295 7adb7dff Iustin Pop
  status <- fromObj arr (strOfKey Success)
296 7adb7dff Iustin Pop
  result <- fromObj arr (strOfKey Result)
297 3603605a Iustin Pop
  if status
298 7adb7dff Iustin Pop
    then return result
299 7adb7dff Iustin Pop
    else decodeError result
300 7adb7dff Iustin Pop
301 7adb7dff Iustin Pop
-- | Try to decode an error from the server response. This function
302 7adb7dff Iustin Pop
-- will always fail, since it's called only on the error path (when
303 7adb7dff Iustin Pop
-- status is False).
304 7adb7dff Iustin Pop
decodeError :: JSValue -> ErrorResult JSValue
305 7adb7dff Iustin Pop
decodeError val =
306 7adb7dff Iustin Pop
  case fromJVal val of
307 7adb7dff Iustin Pop
    Ok e -> Bad e
308 7adb7dff Iustin Pop
    Bad msg -> Bad $ GenericError msg
309 6583e677 Iustin Pop
310 6583e677 Iustin Pop
-- | Generic luxi method call.
311 7adb7dff Iustin Pop
callMethod :: LuxiOp -> Client -> IO (ErrorResult JSValue)
312 683b1ca7 Iustin Pop
callMethod method s = do
313 683b1ca7 Iustin Pop
  sendMsg s $ buildCall method
314 6583e677 Iustin Pop
  result <- recvMsg s
315 6583e677 Iustin Pop
  let rval = validateResult result
316 6583e677 Iustin Pop
  return rval
317 9a2ff880 Iustin Pop
318 619e89c8 Iustin Pop
-- | Parse job submission result.
319 7adb7dff Iustin Pop
parseSubmitJobResult :: JSValue -> ErrorResult JobId
320 7adb7dff Iustin Pop
parseSubmitJobResult (JSArray [JSBool True, v]) =
321 c48711d5 Iustin Pop
  case J.readJSON v of
322 c48711d5 Iustin Pop
    J.Error msg -> Bad $ LuxiError msg
323 c48711d5 Iustin Pop
    J.Ok v' -> Ok v'
324 619e89c8 Iustin Pop
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
325 7adb7dff Iustin Pop
  Bad . LuxiError $ fromJSString x
326 7adb7dff Iustin Pop
parseSubmitJobResult v =
327 7adb7dff Iustin Pop
  Bad . LuxiError $ "Unknown result from the master daemon: " ++
328 7adb7dff Iustin Pop
      show (pp_value v)
329 619e89c8 Iustin Pop
330 9a2ff880 Iustin Pop
-- | Specialized submitManyJobs call.
331 7e723913 Iustin Pop
submitManyJobs :: Client -> [[MetaOpCode]] -> IO (ErrorResult [JobId])
332 9a2ff880 Iustin Pop
submitManyJobs s jobs = do
333 683b1ca7 Iustin Pop
  rval <- callMethod (SubmitManyJobs jobs) s
334 9a2ff880 Iustin Pop
  -- map each result (status, payload) pair into a nice Result ADT
335 9a2ff880 Iustin Pop
  return $ case rval of
336 9a2ff880 Iustin Pop
             Bad x -> Bad x
337 619e89c8 Iustin Pop
             Ok (JSArray r) -> mapM parseSubmitJobResult r
338 7adb7dff Iustin Pop
             x -> Bad . LuxiError $
339 7adb7dff Iustin Pop
                  "Cannot parse response from Ganeti: " ++ show x
340 9a2ff880 Iustin Pop
341 9a2ff880 Iustin Pop
-- | Custom queryJobs call.
342 7adb7dff Iustin Pop
queryJobsStatus :: Client -> [JobId] -> IO (ErrorResult [JobStatus])
343 9a2ff880 Iustin Pop
queryJobsStatus s jids = do
344 76b62028 Iustin Pop
  rval <- callMethod (QueryJobs jids ["status"]) s
345 9a2ff880 Iustin Pop
  return $ case rval of
346 9a2ff880 Iustin Pop
             Bad x -> Bad x
347 9a2ff880 Iustin Pop
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
348 9a2ff880 Iustin Pop
                       J.Ok vals -> if any null vals
349 7adb7dff Iustin Pop
                                    then Bad $
350 7adb7dff Iustin Pop
                                         LuxiError "Missing job status field"
351 9a2ff880 Iustin Pop
                                    else Ok (map head vals)
352 7adb7dff Iustin Pop
                       J.Error x -> Bad $ LuxiError x