Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ 619e89c8

History | View | Annotate | Download (12.7 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 fae980e5 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  , QrViaLuxi(..)
31 ebf38064 Iustin Pop
  , ResultStatus(..)
32 95d0d502 Iustin Pop
  , LuxiReq(..)
33 ebf38064 Iustin Pop
  , Client
34 ccc817a2 Iustin Pop
  , JobId
35 ebf38064 Iustin Pop
  , checkRS
36 ebf38064 Iustin Pop
  , getClient
37 ebf38064 Iustin Pop
  , closeClient
38 ebf38064 Iustin Pop
  , callMethod
39 ebf38064 Iustin Pop
  , submitManyJobs
40 ebf38064 Iustin Pop
  , queryJobsStatus
41 cdd495ae Iustin Pop
  , buildCall
42 cdd495ae Iustin Pop
  , validateCall
43 cdd495ae Iustin Pop
  , decodeCall
44 ebf38064 Iustin Pop
  ) where
45 6583e677 Iustin Pop
46 6583e677 Iustin Pop
import Data.IORef
47 6583e677 Iustin Pop
import Control.Monad
48 0903280b Iustin Pop
import Text.JSON (encodeStrict, decodeStrict)
49 6583e677 Iustin Pop
import qualified Text.JSON as J
50 6583e677 Iustin Pop
import Text.JSON.Types
51 6583e677 Iustin Pop
import System.Timeout
52 6583e677 Iustin Pop
import qualified Network.Socket as S
53 6583e677 Iustin Pop
54 b69be409 Iustin Pop
import Ganeti.HTools.JSON
55 6583e677 Iustin Pop
import Ganeti.HTools.Types
56 cdd495ae Iustin Pop
import Ganeti.HTools.Utils
57 6583e677 Iustin Pop
58 92678b3c Iustin Pop
import Ganeti.Constants
59 9a2ff880 Iustin Pop
import Ganeti.Jobs (JobStatus)
60 683b1ca7 Iustin Pop
import Ganeti.OpCodes (OpCode)
61 a0090487 Agata Murawska
import Ganeti.THH
62 9a2ff880 Iustin Pop
63 6583e677 Iustin Pop
-- * Utility functions
64 6583e677 Iustin Pop
65 6583e677 Iustin Pop
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
66 6583e677 Iustin Pop
withTimeout :: Int -> String -> IO a -> IO a
67 6583e677 Iustin Pop
withTimeout secs descr action = do
68 ebf38064 Iustin Pop
  result <- timeout (secs * 1000000) action
69 3603605a Iustin Pop
  case result of
70 3603605a Iustin Pop
    Nothing -> fail $ "Timeout in " ++ descr
71 3603605a Iustin Pop
    Just v -> return v
72 6583e677 Iustin Pop
73 6583e677 Iustin Pop
-- * Generic protocol functionality
74 6583e677 Iustin Pop
75 ccc817a2 Iustin Pop
-- | The Ganeti job type.
76 ccc817a2 Iustin Pop
type JobId = String
77 ccc817a2 Iustin Pop
78 92678b3c Iustin Pop
$(declareSADT "QrViaLuxi"
79 ebf38064 Iustin Pop
  [ ("QRLock", 'qrLock)
80 ebf38064 Iustin Pop
  , ("QRInstance", 'qrInstance)
81 ebf38064 Iustin Pop
  , ("QRNode", 'qrNode)
82 ebf38064 Iustin Pop
  , ("QRGroup", 'qrGroup)
83 ebf38064 Iustin Pop
  , ("QROs", 'qrOs)
84 ebf38064 Iustin Pop
  ])
85 92678b3c Iustin Pop
$(makeJSONInstance ''QrViaLuxi)
86 92678b3c Iustin Pop
87 a0090487 Agata Murawska
-- | Currently supported Luxi operations and JSON serialization.
88 a0090487 Agata Murawska
$(genLuxiOp "LuxiOp"
89 fae980e5 Iustin Pop
  [(luxiReqQuery,
90 ebf38064 Iustin Pop
    [ ("what",    [t| QrViaLuxi |], [| id |])
91 ebf38064 Iustin Pop
    , ("fields",  [t| [String]  |], [| id |])
92 ebf38064 Iustin Pop
    , ("qfilter", [t| ()        |], [| const JSNull |])
93 ebf38064 Iustin Pop
    ])
94 fae980e5 Iustin Pop
  , (luxiReqQueryNodes,
95 ebf38064 Iustin Pop
     [ ("names",  [t| [String] |], [| id |])
96 ebf38064 Iustin Pop
     , ("fields", [t| [String] |], [| id |])
97 ebf38064 Iustin Pop
     , ("lock",   [t| Bool     |], [| id |])
98 ebf38064 Iustin Pop
     ])
99 fae980e5 Iustin Pop
  , (luxiReqQueryGroups,
100 ebf38064 Iustin Pop
     [ ("names",  [t| [String] |], [| id |])
101 ebf38064 Iustin Pop
     , ("fields", [t| [String] |], [| id |])
102 ebf38064 Iustin Pop
     , ("lock",   [t| Bool     |], [| id |])
103 ebf38064 Iustin Pop
     ])
104 fae980e5 Iustin Pop
  , (luxiReqQueryInstances,
105 ebf38064 Iustin Pop
     [ ("names",  [t| [String] |], [| id |])
106 ebf38064 Iustin Pop
     , ("fields", [t| [String] |], [| id |])
107 ebf38064 Iustin Pop
     , ("lock",   [t| Bool     |], [| id |])
108 ebf38064 Iustin Pop
     ])
109 fae980e5 Iustin Pop
  , (luxiReqQueryJobs,
110 ebf38064 Iustin Pop
     [ ("ids",    [t| [Int]    |], [| map show |])
111 ebf38064 Iustin Pop
     , ("fields", [t| [String] |], [| id |])
112 ebf38064 Iustin Pop
     ])
113 fae980e5 Iustin Pop
  , (luxiReqQueryExports,
114 ebf38064 Iustin Pop
     [ ("nodes", [t| [String] |], [| id |])
115 ebf38064 Iustin Pop
     , ("lock",  [t| Bool     |], [| id |])
116 ebf38064 Iustin Pop
     ])
117 fae980e5 Iustin Pop
  , (luxiReqQueryConfigValues,
118 ebf38064 Iustin Pop
     [ ("fields", [t| [String] |], [| id |]) ]
119 ebf38064 Iustin Pop
    )
120 fae980e5 Iustin Pop
  , (luxiReqQueryClusterInfo, [])
121 fae980e5 Iustin Pop
  , (luxiReqQueryTags,
122 ebf38064 Iustin Pop
     [ ("kind", [t| String |], [| id |])
123 ebf38064 Iustin Pop
     , ("name", [t| String |], [| id |])
124 ebf38064 Iustin Pop
     ])
125 fae980e5 Iustin Pop
  , (luxiReqSubmitJob,
126 ebf38064 Iustin Pop
     [ ("job", [t| [OpCode] |], [| id |]) ]
127 ebf38064 Iustin Pop
    )
128 fae980e5 Iustin Pop
  , (luxiReqSubmitManyJobs,
129 ebf38064 Iustin Pop
     [ ("ops", [t| [[OpCode]] |], [| id |]) ]
130 ebf38064 Iustin Pop
    )
131 fae980e5 Iustin Pop
  , (luxiReqWaitForJobChange,
132 cdd495ae Iustin Pop
     [ ("job",      [t| Int     |], [| show |])
133 ebf38064 Iustin Pop
     , ("fields",   [t| [String]|], [| id |])
134 ebf38064 Iustin Pop
     , ("prev_job", [t| JSValue |], [| id |])
135 ebf38064 Iustin Pop
     , ("prev_log", [t| JSValue |], [| id |])
136 ebf38064 Iustin Pop
     , ("tmout",    [t| Int     |], [| id |])
137 ebf38064 Iustin Pop
     ])
138 fae980e5 Iustin Pop
  , (luxiReqArchiveJob,
139 ebf38064 Iustin Pop
     [ ("job", [t| Int |], [| show |]) ]
140 ebf38064 Iustin Pop
    )
141 fae980e5 Iustin Pop
  , (luxiReqAutoArchiveJobs,
142 ebf38064 Iustin Pop
     [ ("age",   [t| Int |], [| id |])
143 ebf38064 Iustin Pop
     , ("tmout", [t| Int |], [| id |])
144 ebf38064 Iustin Pop
     ])
145 fae980e5 Iustin Pop
  , (luxiReqCancelJob,
146 ebf38064 Iustin Pop
     [ ("job", [t| Int |], [| show |]) ]
147 ebf38064 Iustin Pop
    )
148 fae980e5 Iustin Pop
  , (luxiReqSetDrainFlag,
149 ebf38064 Iustin Pop
     [ ("flag", [t| Bool |], [| id |]) ]
150 ebf38064 Iustin Pop
    )
151 fae980e5 Iustin Pop
  , (luxiReqSetWatcherPause,
152 ebf38064 Iustin Pop
     [ ("duration", [t| Double |], [| id |]) ]
153 ebf38064 Iustin Pop
    )
154 a0090487 Agata Murawska
  ])
155 6583e677 Iustin Pop
156 95d0d502 Iustin Pop
$(makeJSONInstance ''LuxiReq)
157 95d0d502 Iustin Pop
158 6583e677 Iustin Pop
-- | The serialisation of LuxiOps into strings in messages.
159 a0090487 Agata Murawska
$(genStrOfOp ''LuxiOp "strOfOp")
160 6583e677 Iustin Pop
161 260d0bda Agata Murawska
$(declareIADT "ResultStatus"
162 ebf38064 Iustin Pop
  [ ("RSNormal", 'rsNormal)
163 ebf38064 Iustin Pop
  , ("RSUnknown", 'rsUnknown)
164 ebf38064 Iustin Pop
  , ("RSNoData", 'rsNodata)
165 ebf38064 Iustin Pop
  , ("RSUnavailable", 'rsUnavail)
166 ebf38064 Iustin Pop
  , ("RSOffline", 'rsOffline)
167 ebf38064 Iustin Pop
  ])
168 5f828ce4 Agata Murawska
169 5f828ce4 Agata Murawska
$(makeJSONInstance ''ResultStatus)
170 260d0bda Agata Murawska
171 cdd495ae Iustin Pop
-- | Type holding the initial (unparsed) Luxi call.
172 cdd495ae Iustin Pop
data LuxiCall = LuxiCall LuxiReq JSValue
173 cdd495ae Iustin Pop
174 260d0bda Agata Murawska
-- | Check that ResultStatus is success or fail with descriptive message.
175 260d0bda Agata Murawska
checkRS :: (Monad m) => ResultStatus -> a -> m a
176 260d0bda Agata Murawska
checkRS RSNormal val    = return val
177 260d0bda Agata Murawska
checkRS RSUnknown _     = fail "Unknown field"
178 260d0bda Agata Murawska
checkRS RSNoData _      = fail "No data for a field"
179 260d0bda Agata Murawska
checkRS RSUnavailable _ = fail "Ganeti reports unavailable data"
180 260d0bda Agata Murawska
checkRS RSOffline _     = fail "Ganeti reports resource as offline"
181 260d0bda Agata Murawska
182 6583e677 Iustin Pop
-- | The end-of-message separator.
183 6583e677 Iustin Pop
eOM :: Char
184 6583e677 Iustin Pop
eOM = '\3'
185 6583e677 Iustin Pop
186 6583e677 Iustin Pop
-- | Valid keys in the requests and responses.
187 6583e677 Iustin Pop
data MsgKeys = Method
188 6583e677 Iustin Pop
             | Args
189 6583e677 Iustin Pop
             | Success
190 6583e677 Iustin Pop
             | Result
191 6583e677 Iustin Pop
192 6583e677 Iustin Pop
-- | The serialisation of MsgKeys into strings in messages.
193 a0090487 Agata Murawska
$(genStrOfKey ''MsgKeys "strOfKey")
194 6583e677 Iustin Pop
195 6583e677 Iustin Pop
-- | Luxi client encapsulation.
196 6583e677 Iustin Pop
data Client = Client { socket :: S.Socket   -- ^ The socket of the client
197 6583e677 Iustin Pop
                     , rbuf :: IORef String -- ^ Already received buffer
198 6583e677 Iustin Pop
                     }
199 6583e677 Iustin Pop
200 6583e677 Iustin Pop
-- | Connects to the master daemon and returns a luxi Client.
201 6583e677 Iustin Pop
getClient :: String -> IO Client
202 6583e677 Iustin Pop
getClient path = do
203 ebf38064 Iustin Pop
  s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
204 ebf38064 Iustin Pop
  withTimeout connTimeout "creating luxi connection" $
205 ebf38064 Iustin Pop
              S.connect s (S.SockAddrUnix path)
206 ebf38064 Iustin Pop
  rf <- newIORef ""
207 ebf38064 Iustin Pop
  return Client { socket=s, rbuf=rf}
208 6583e677 Iustin Pop
209 6583e677 Iustin Pop
-- | Closes the client socket.
210 6583e677 Iustin Pop
closeClient :: Client -> IO ()
211 6583e677 Iustin Pop
closeClient = S.sClose . socket
212 6583e677 Iustin Pop
213 6583e677 Iustin Pop
-- | Sends a message over a luxi transport.
214 6583e677 Iustin Pop
sendMsg :: Client -> String -> IO ()
215 6583e677 Iustin Pop
sendMsg s buf =
216 ebf38064 Iustin Pop
  let _send obuf = do
217 ebf38064 Iustin Pop
        sbytes <- withTimeout queryTimeout
218 ebf38064 Iustin Pop
                  "sending luxi message" $
219 ebf38064 Iustin Pop
                  S.send (socket s) obuf
220 ebf38064 Iustin Pop
        unless (sbytes == length obuf) $ _send (drop sbytes obuf)
221 ebf38064 Iustin Pop
  in _send (buf ++ [eOM])
222 6583e677 Iustin Pop
223 6583e677 Iustin Pop
-- | Waits for a message over a luxi transport.
224 6583e677 Iustin Pop
recvMsg :: Client -> IO String
225 6583e677 Iustin Pop
recvMsg s = do
226 6583e677 Iustin Pop
  let _recv obuf = do
227 6583e677 Iustin Pop
              nbuf <- withTimeout queryTimeout "reading luxi response" $
228 6583e677 Iustin Pop
                      S.recv (socket s) 4096
229 95f490de Iustin Pop
              let (msg, remaining) = break (eOM ==) nbuf
230 3603605a Iustin Pop
              if null remaining
231 3603605a Iustin Pop
                then _recv (obuf ++ msg)
232 3603605a Iustin Pop
                else return (obuf ++ msg, tail remaining)
233 6583e677 Iustin Pop
  cbuf <- readIORef $ rbuf s
234 95f490de Iustin Pop
  let (imsg, ibuf) = break (eOM ==) cbuf
235 95f490de Iustin Pop
  (msg, nbuf) <-
236 3603605a Iustin Pop
    if null ibuf      -- if old buffer didn't contain a full message
237 3603605a Iustin Pop
      then _recv cbuf   -- then we read from network
238 3603605a Iustin Pop
      else return (imsg, tail ibuf) -- else we return data from our buffer
239 6583e677 Iustin Pop
  writeIORef (rbuf s) nbuf
240 6583e677 Iustin Pop
  return msg
241 6583e677 Iustin Pop
242 6583e677 Iustin Pop
-- | Serialize a request to String.
243 6583e677 Iustin Pop
buildCall :: LuxiOp  -- ^ The method
244 6583e677 Iustin Pop
          -> String  -- ^ The serialized form
245 683b1ca7 Iustin Pop
buildCall lo =
246 ebf38064 Iustin Pop
  let ja = [ (strOfKey Method, JSString $ toJSString $ strOfOp lo::JSValue)
247 ebf38064 Iustin Pop
           , (strOfKey Args, opToArgs lo::JSValue)
248 ebf38064 Iustin Pop
           ]
249 ebf38064 Iustin Pop
      jo = toJSObject ja
250 ebf38064 Iustin Pop
  in encodeStrict jo
251 6583e677 Iustin Pop
252 cdd495ae Iustin Pop
-- | Check that luxi request contains the required keys and parse it.
253 cdd495ae Iustin Pop
validateCall :: String -> Result LuxiCall
254 cdd495ae Iustin Pop
validateCall s = do
255 cdd495ae Iustin Pop
  arr <- fromJResult "luxi call" $ decodeStrict s::Result (JSObject JSValue)
256 cdd495ae Iustin Pop
  let aobj = fromJSObject arr
257 cdd495ae Iustin Pop
  call <- fromObj aobj (strOfKey Method)::Result LuxiReq
258 cdd495ae Iustin Pop
  args <- fromObj aobj (strOfKey Args)
259 cdd495ae Iustin Pop
  return (LuxiCall call args)
260 cdd495ae Iustin Pop
261 cdd495ae Iustin Pop
-- | Converts Luxi call arguments into a 'LuxiOp' data structure.
262 cdd495ae Iustin Pop
--
263 cdd495ae Iustin Pop
-- This is currently hand-coded until we make it more uniform so that
264 cdd495ae Iustin Pop
-- it can be generated using TH.
265 cdd495ae Iustin Pop
decodeCall :: LuxiCall -> Result LuxiOp
266 cdd495ae Iustin Pop
decodeCall (LuxiCall call args) =
267 cdd495ae Iustin Pop
  case call of
268 cdd495ae Iustin Pop
    ReqQueryJobs -> do
269 cdd495ae Iustin Pop
              (jid, jargs) <- fromJVal args
270 cdd495ae Iustin Pop
              rid <- mapM (tryRead "parsing job ID" . fromJSString) jid
271 cdd495ae Iustin Pop
              let rargs = map fromJSString jargs
272 cdd495ae Iustin Pop
              return $ QueryJobs rid rargs
273 cdd495ae Iustin Pop
    ReqQueryInstances -> do
274 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
275 cdd495ae Iustin Pop
              return $ QueryInstances names fields locking
276 cdd495ae Iustin Pop
    ReqQueryNodes -> do
277 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
278 cdd495ae Iustin Pop
              return $ QueryNodes names fields locking
279 cdd495ae Iustin Pop
    ReqQueryGroups -> do
280 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
281 cdd495ae Iustin Pop
              return $ QueryGroups names fields locking
282 cdd495ae Iustin Pop
    ReqQueryClusterInfo -> do
283 cdd495ae Iustin Pop
              return QueryClusterInfo
284 cdd495ae Iustin Pop
    ReqQuery -> do
285 cdd495ae Iustin Pop
              (what, fields, _) <-
286 cdd495ae Iustin Pop
                fromJVal args::Result (QrViaLuxi, [String], JSValue)
287 cdd495ae Iustin Pop
              return $ Query what fields ()
288 cdd495ae Iustin Pop
    ReqSubmitJob -> do
289 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
290 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
291 cdd495ae Iustin Pop
              return $ SubmitJob ops2
292 cdd495ae Iustin Pop
    ReqSubmitManyJobs -> do
293 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
294 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
295 cdd495ae Iustin Pop
              return $ SubmitManyJobs ops2
296 cdd495ae Iustin Pop
    ReqWaitForJobChange -> do
297 cdd495ae Iustin Pop
              (jid, fields, pinfo, pidx, wtmout) <-
298 cdd495ae Iustin Pop
                -- No instance for 5-tuple, code copied from the
299 cdd495ae Iustin Pop
                -- json sources and adapted
300 cdd495ae Iustin Pop
                fromJResult "Parsing WaitForJobChange message" $
301 cdd495ae Iustin Pop
                case args of
302 cdd495ae Iustin Pop
                  JSArray [a, b, c, d, e] ->
303 cdd495ae Iustin Pop
                    (,,,,) `fmap`
304 cdd495ae Iustin Pop
                    J.readJSON a `ap`
305 cdd495ae Iustin Pop
                    J.readJSON b `ap`
306 cdd495ae Iustin Pop
                    J.readJSON c `ap`
307 cdd495ae Iustin Pop
                    J.readJSON d `ap`
308 cdd495ae Iustin Pop
                    J.readJSON e
309 cdd495ae Iustin Pop
                  _ -> J.Error "Not enough values"
310 cdd495ae Iustin Pop
              rid <- tryRead "parsing job ID" jid
311 cdd495ae Iustin Pop
              return $ WaitForJobChange rid fields pinfo pidx wtmout
312 cdd495ae Iustin Pop
    ReqArchiveJob -> do
313 cdd495ae Iustin Pop
              [jid] <- fromJVal args
314 cdd495ae Iustin Pop
              rid <- tryRead "parsing job ID" jid
315 cdd495ae Iustin Pop
              return $ ArchiveJob rid
316 cdd495ae Iustin Pop
    ReqAutoArchiveJobs -> do
317 cdd495ae Iustin Pop
              (age, tmout) <- fromJVal args
318 cdd495ae Iustin Pop
              return $ AutoArchiveJobs age tmout
319 cdd495ae Iustin Pop
    ReqQueryExports -> do
320 cdd495ae Iustin Pop
              (nodes, lock) <- fromJVal args
321 cdd495ae Iustin Pop
              return $ QueryExports nodes lock
322 cdd495ae Iustin Pop
    ReqQueryConfigValues -> do
323 cdd495ae Iustin Pop
              [fields] <- fromJVal args
324 cdd495ae Iustin Pop
              return $ QueryConfigValues fields
325 cdd495ae Iustin Pop
    ReqQueryTags -> do
326 cdd495ae Iustin Pop
              (kind, name) <- fromJVal args
327 cdd495ae Iustin Pop
              return $ QueryTags kind name
328 cdd495ae Iustin Pop
    ReqCancelJob -> do
329 cdd495ae Iustin Pop
              [job] <- fromJVal args
330 cdd495ae Iustin Pop
              rid <- tryRead "parsing job ID" job
331 cdd495ae Iustin Pop
              return $ CancelJob rid
332 cdd495ae Iustin Pop
    ReqSetDrainFlag -> do
333 cdd495ae Iustin Pop
              [flag] <- fromJVal args
334 cdd495ae Iustin Pop
              return $ SetDrainFlag flag
335 cdd495ae Iustin Pop
    ReqSetWatcherPause -> do
336 cdd495ae Iustin Pop
              [duration] <- fromJVal args
337 cdd495ae Iustin Pop
              return $ SetWatcherPause duration
338 cdd495ae Iustin Pop
339 6583e677 Iustin Pop
-- | Check that luxi responses contain the required keys and that the
340 6583e677 Iustin Pop
-- call was successful.
341 6583e677 Iustin Pop
validateResult :: String -> Result JSValue
342 6583e677 Iustin Pop
validateResult s = do
343 c96d44df Iustin Pop
  oarr <- fromJResult "Parsing LUXI response"
344 c96d44df Iustin Pop
          (decodeStrict s)::Result (JSObject JSValue)
345 262f3e6c Iustin Pop
  let arr = J.fromJSObject oarr
346 e8230242 Iustin Pop
  status <- fromObj arr (strOfKey Success)::Result Bool
347 6583e677 Iustin Pop
  let rkey = strOfKey Result
348 3603605a Iustin Pop
  if status
349 3603605a Iustin Pop
    then fromObj arr rkey
350 3603605a Iustin Pop
    else fromObj arr rkey >>= fail
351 6583e677 Iustin Pop
352 6583e677 Iustin Pop
-- | Generic luxi method call.
353 683b1ca7 Iustin Pop
callMethod :: LuxiOp -> Client -> IO (Result JSValue)
354 683b1ca7 Iustin Pop
callMethod method s = do
355 683b1ca7 Iustin Pop
  sendMsg s $ buildCall method
356 6583e677 Iustin Pop
  result <- recvMsg s
357 6583e677 Iustin Pop
  let rval = validateResult result
358 6583e677 Iustin Pop
  return rval
359 9a2ff880 Iustin Pop
360 619e89c8 Iustin Pop
-- | Parses a job ID.
361 619e89c8 Iustin Pop
parseJobId :: JSValue -> Result JobId
362 619e89c8 Iustin Pop
parseJobId (JSString x) = Ok $ fromJSString x
363 619e89c8 Iustin Pop
parseJobId x = Bad $ "Wrong type/value for job id: " ++ show x
364 619e89c8 Iustin Pop
365 619e89c8 Iustin Pop
-- | Parse job submission result.
366 619e89c8 Iustin Pop
parseSubmitJobResult :: JSValue -> Result JobId
367 619e89c8 Iustin Pop
parseSubmitJobResult (JSArray [JSBool True, v]) = parseJobId v
368 619e89c8 Iustin Pop
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
369 619e89c8 Iustin Pop
  Bad (fromJSString x)
370 619e89c8 Iustin Pop
parseSubmitJobResult v = Bad $ "Unknown result from the master daemon" ++
371 619e89c8 Iustin Pop
                         show v
372 619e89c8 Iustin Pop
373 9a2ff880 Iustin Pop
-- | Specialized submitManyJobs call.
374 ccc817a2 Iustin Pop
submitManyJobs :: Client -> [[OpCode]] -> IO (Result [JobId])
375 9a2ff880 Iustin Pop
submitManyJobs s jobs = do
376 683b1ca7 Iustin Pop
  rval <- callMethod (SubmitManyJobs jobs) s
377 9a2ff880 Iustin Pop
  -- map each result (status, payload) pair into a nice Result ADT
378 9a2ff880 Iustin Pop
  return $ case rval of
379 9a2ff880 Iustin Pop
             Bad x -> Bad x
380 619e89c8 Iustin Pop
             Ok (JSArray r) -> mapM parseSubmitJobResult r
381 9a2ff880 Iustin Pop
             x -> Bad ("Cannot parse response from Ganeti: " ++ show x)
382 9a2ff880 Iustin Pop
383 9a2ff880 Iustin Pop
-- | Custom queryJobs call.
384 ccc817a2 Iustin Pop
queryJobsStatus :: Client -> [JobId] -> IO (Result [JobStatus])
385 9a2ff880 Iustin Pop
queryJobsStatus s jids = do
386 683b1ca7 Iustin Pop
  rval <- callMethod (QueryJobs (map read jids) ["status"]) s
387 9a2ff880 Iustin Pop
  return $ case rval of
388 9a2ff880 Iustin Pop
             Bad x -> Bad x
389 9a2ff880 Iustin Pop
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
390 9a2ff880 Iustin Pop
                       J.Ok vals -> if any null vals
391 9a2ff880 Iustin Pop
                                    then Bad "Missing job status field"
392 9a2ff880 Iustin Pop
                                    else Ok (map head vals)
393 9a2ff880 Iustin Pop
                       J.Error x -> Bad x