Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ cb44e3db

History | View | Annotate | Download (15.3 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 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 ebf38064 Iustin Pop
  , getClient
38 13f2321c Iustin Pop
  , getServer
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 0aff2293 Iustin Pop
import Control.Exception (catch)
56 6583e677 Iustin Pop
import Data.IORef
57 e821050d Iustin Pop
import qualified Data.ByteString as B
58 62d5242b Iustin Pop
import qualified Data.ByteString.Lazy as BL
59 e821050d Iustin Pop
import qualified Data.ByteString.UTF8 as UTF8
60 62d5242b Iustin Pop
import qualified Data.ByteString.Lazy.UTF8 as UTF8L
61 e821050d Iustin Pop
import Data.Word (Word8)
62 6583e677 Iustin Pop
import Control.Monad
63 0903280b Iustin Pop
import Text.JSON (encodeStrict, decodeStrict)
64 6583e677 Iustin Pop
import qualified Text.JSON as J
65 7adb7dff Iustin Pop
import Text.JSON.Pretty (pp_value)
66 6583e677 Iustin Pop
import Text.JSON.Types
67 0aff2293 Iustin Pop
import System.Directory (removeFile)
68 e821050d Iustin Pop
import System.IO (hClose, hFlush, hWaitForInput, Handle, IOMode(..))
69 0aff2293 Iustin Pop
import System.IO.Error (isEOFError)
70 6583e677 Iustin Pop
import System.Timeout
71 6583e677 Iustin Pop
import qualified Network.Socket as S
72 6583e677 Iustin Pop
73 4cd79ca8 Iustin Pop
import Ganeti.BasicTypes
74 92678b3c Iustin Pop
import Ganeti.Constants
75 7adb7dff Iustin Pop
import Ganeti.Errors
76 7adb7dff Iustin Pop
import Ganeti.JSON
77 fa10983e Iustin Pop
import Ganeti.OpParams (pTagsObject)
78 367c4241 Dato Simó
import Ganeti.OpCodes
79 4cab6703 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
80 a0090487 Agata Murawska
import Ganeti.THH
81 c48711d5 Iustin Pop
import Ganeti.Types
82 9a2ff880 Iustin Pop
83 6583e677 Iustin Pop
-- * Utility functions
84 6583e677 Iustin Pop
85 6583e677 Iustin Pop
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
86 6583e677 Iustin Pop
withTimeout :: Int -> String -> IO a -> IO a
87 6583e677 Iustin Pop
withTimeout secs descr action = do
88 ebf38064 Iustin Pop
  result <- timeout (secs * 1000000) action
89 3603605a Iustin Pop
  case result of
90 3603605a Iustin Pop
    Nothing -> fail $ "Timeout in " ++ descr
91 3603605a Iustin Pop
    Just v -> return v
92 6583e677 Iustin Pop
93 6583e677 Iustin Pop
-- * Generic protocol functionality
94 6583e677 Iustin Pop
95 0aff2293 Iustin Pop
-- | Result of receiving a message from the socket.
96 0aff2293 Iustin Pop
data RecvResult = RecvConnClosed    -- ^ Connection closed
97 0aff2293 Iustin Pop
                | RecvError String  -- ^ Any other error
98 0aff2293 Iustin Pop
                | RecvOk String     -- ^ Successfull receive
99 139c0683 Iustin Pop
                  deriving (Show, Eq)
100 0aff2293 Iustin Pop
101 a0090487 Agata Murawska
-- | Currently supported Luxi operations and JSON serialization.
102 a0090487 Agata Murawska
$(genLuxiOp "LuxiOp"
103 72295708 Iustin Pop
  [ (luxiReqQuery,
104 88609f00 Iustin Pop
    [ simpleField "what"    [t| Qlang.ItemType |]
105 88609f00 Iustin Pop
    , simpleField "fields"  [t| [String]  |]
106 88609f00 Iustin Pop
    , simpleField "qfilter" [t| Qlang.Filter Qlang.FilterField |]
107 ebf38064 Iustin Pop
    ])
108 72295708 Iustin Pop
  , (luxiReqQueryFields,
109 88609f00 Iustin Pop
    [ simpleField "what"    [t| Qlang.ItemType |]
110 88609f00 Iustin Pop
    , simpleField "fields"  [t| [String]  |]
111 72295708 Iustin Pop
    ])
112 fae980e5 Iustin Pop
  , (luxiReqQueryNodes,
113 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
114 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
115 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
116 ebf38064 Iustin Pop
     ])
117 fae980e5 Iustin Pop
  , (luxiReqQueryGroups,
118 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
119 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
120 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
121 ebf38064 Iustin Pop
     ])
122 fae980e5 Iustin Pop
  , (luxiReqQueryInstances,
123 88609f00 Iustin Pop
     [ simpleField "names"  [t| [String] |]
124 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
125 88609f00 Iustin Pop
     , simpleField "lock"   [t| Bool     |]
126 ebf38064 Iustin Pop
     ])
127 fae980e5 Iustin Pop
  , (luxiReqQueryJobs,
128 c48711d5 Iustin Pop
     [ simpleField "ids"    [t| [JobId]  |]
129 88609f00 Iustin Pop
     , simpleField "fields" [t| [String] |]
130 ebf38064 Iustin Pop
     ])
131 fae980e5 Iustin Pop
  , (luxiReqQueryExports,
132 88609f00 Iustin Pop
     [ simpleField "nodes" [t| [String] |]
133 88609f00 Iustin Pop
     , simpleField "lock"  [t| Bool     |]
134 ebf38064 Iustin Pop
     ])
135 fae980e5 Iustin Pop
  , (luxiReqQueryConfigValues,
136 88609f00 Iustin Pop
     [ simpleField "fields" [t| [String] |] ]
137 ebf38064 Iustin Pop
    )
138 fae980e5 Iustin Pop
  , (luxiReqQueryClusterInfo, [])
139 fae980e5 Iustin Pop
  , (luxiReqQueryTags,
140 fa10983e Iustin Pop
     [ pTagsObject ])
141 fae980e5 Iustin Pop
  , (luxiReqSubmitJob,
142 7e723913 Iustin Pop
     [ simpleField "job" [t| [MetaOpCode] |] ]
143 ebf38064 Iustin Pop
    )
144 fae980e5 Iustin Pop
  , (luxiReqSubmitManyJobs,
145 7e723913 Iustin Pop
     [ simpleField "ops" [t| [[MetaOpCode]] |] ]
146 ebf38064 Iustin Pop
    )
147 fae980e5 Iustin Pop
  , (luxiReqWaitForJobChange,
148 c48711d5 Iustin Pop
     [ simpleField "job"      [t| JobId   |]
149 88609f00 Iustin Pop
     , simpleField "fields"   [t| [String]|]
150 88609f00 Iustin Pop
     , simpleField "prev_job" [t| JSValue |]
151 88609f00 Iustin Pop
     , simpleField "prev_log" [t| JSValue |]
152 88609f00 Iustin Pop
     , simpleField "tmout"    [t| Int     |]
153 ebf38064 Iustin Pop
     ])
154 fae980e5 Iustin Pop
  , (luxiReqArchiveJob,
155 c48711d5 Iustin Pop
     [ simpleField "job" [t| JobId |] ]
156 ebf38064 Iustin Pop
    )
157 fae980e5 Iustin Pop
  , (luxiReqAutoArchiveJobs,
158 88609f00 Iustin Pop
     [ simpleField "age"   [t| Int |]
159 88609f00 Iustin Pop
     , simpleField "tmout" [t| Int |]
160 ebf38064 Iustin Pop
     ])
161 fae980e5 Iustin Pop
  , (luxiReqCancelJob,
162 c48711d5 Iustin Pop
     [ simpleField "job" [t| JobId |] ]
163 ebf38064 Iustin Pop
    )
164 f63ffb37 Michael Hanselmann
  , (luxiReqChangeJobPriority,
165 c48711d5 Iustin Pop
     [ simpleField "job"      [t| JobId |]
166 f63ffb37 Michael Hanselmann
     , simpleField "priority" [t| Int |] ]
167 f63ffb37 Michael Hanselmann
    )
168 fae980e5 Iustin Pop
  , (luxiReqSetDrainFlag,
169 88609f00 Iustin Pop
     [ simpleField "flag" [t| Bool |] ]
170 ebf38064 Iustin Pop
    )
171 fae980e5 Iustin Pop
  , (luxiReqSetWatcherPause,
172 88609f00 Iustin Pop
     [ simpleField "duration" [t| Double |] ]
173 ebf38064 Iustin Pop
    )
174 a0090487 Agata Murawska
  ])
175 6583e677 Iustin Pop
176 95d0d502 Iustin Pop
$(makeJSONInstance ''LuxiReq)
177 95d0d502 Iustin Pop
178 471b6c46 Iustin Pop
-- | List of all defined Luxi calls.
179 471b6c46 Iustin Pop
$(genAllConstr (drop 3) ''LuxiReq "allLuxiCalls")
180 471b6c46 Iustin Pop
181 6583e677 Iustin Pop
-- | The serialisation of LuxiOps into strings in messages.
182 a0090487 Agata Murawska
$(genStrOfOp ''LuxiOp "strOfOp")
183 6583e677 Iustin Pop
184 cdd495ae Iustin Pop
-- | Type holding the initial (unparsed) Luxi call.
185 cdd495ae Iustin Pop
data LuxiCall = LuxiCall LuxiReq JSValue
186 cdd495ae Iustin Pop
187 6583e677 Iustin Pop
-- | The end-of-message separator.
188 e821050d Iustin Pop
eOM :: Word8
189 e821050d Iustin Pop
eOM = 3
190 e821050d Iustin Pop
191 e821050d Iustin Pop
-- | The end-of-message encoded as a ByteString.
192 e821050d Iustin Pop
bEOM :: B.ByteString
193 e821050d Iustin Pop
bEOM = B.singleton eOM
194 6583e677 Iustin Pop
195 6583e677 Iustin Pop
-- | Valid keys in the requests and responses.
196 6583e677 Iustin Pop
data MsgKeys = Method
197 6583e677 Iustin Pop
             | Args
198 6583e677 Iustin Pop
             | Success
199 6583e677 Iustin Pop
             | Result
200 6583e677 Iustin Pop
201 6583e677 Iustin Pop
-- | The serialisation of MsgKeys into strings in messages.
202 a0090487 Agata Murawska
$(genStrOfKey ''MsgKeys "strOfKey")
203 6583e677 Iustin Pop
204 6583e677 Iustin Pop
-- | Luxi client encapsulation.
205 e821050d Iustin Pop
data Client = Client { socket :: Handle           -- ^ The socket of the client
206 e821050d Iustin Pop
                     , rbuf :: IORef B.ByteString -- ^ Already received buffer
207 6583e677 Iustin Pop
                     }
208 6583e677 Iustin Pop
209 6583e677 Iustin Pop
-- | Connects to the master daemon and returns a luxi Client.
210 6583e677 Iustin Pop
getClient :: String -> IO Client
211 6583e677 Iustin Pop
getClient path = do
212 ebf38064 Iustin Pop
  s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
213 4cd79ca8 Iustin Pop
  withTimeout luxiDefCtmo "creating luxi connection" $
214 ebf38064 Iustin Pop
              S.connect s (S.SockAddrUnix path)
215 e821050d Iustin Pop
  rf <- newIORef B.empty
216 e821050d Iustin Pop
  h <- S.socketToHandle s ReadWriteMode
217 e821050d Iustin Pop
  return Client { socket=h, rbuf=rf }
218 6583e677 Iustin Pop
219 13f2321c Iustin Pop
-- | Creates and returns a server endpoint.
220 13f2321c Iustin Pop
getServer :: FilePath -> IO S.Socket
221 13f2321c Iustin Pop
getServer path = do
222 13f2321c Iustin Pop
  s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
223 13f2321c Iustin Pop
  S.bindSocket s (S.SockAddrUnix path)
224 13f2321c Iustin Pop
  S.listen s 5 -- 5 is the max backlog
225 13f2321c Iustin Pop
  return s
226 13f2321c Iustin Pop
227 0aff2293 Iustin Pop
-- | Closes a server endpoint.
228 0aff2293 Iustin Pop
-- FIXME: this should be encapsulated into a nicer type.
229 0aff2293 Iustin Pop
closeServer :: FilePath -> S.Socket -> IO ()
230 0aff2293 Iustin Pop
closeServer path sock = do
231 0aff2293 Iustin Pop
  S.sClose sock
232 0aff2293 Iustin Pop
  removeFile path
233 0aff2293 Iustin Pop
234 13f2321c Iustin Pop
-- | Accepts a client
235 13f2321c Iustin Pop
acceptClient :: S.Socket -> IO Client
236 13f2321c Iustin Pop
acceptClient s = do
237 13f2321c Iustin Pop
  -- second return is the address of the client, which we ignore here
238 13f2321c Iustin Pop
  (client_socket, _) <- S.accept s
239 13f2321c Iustin Pop
  new_buffer <- newIORef B.empty
240 13f2321c Iustin Pop
  handle <- S.socketToHandle client_socket ReadWriteMode
241 13f2321c Iustin Pop
  return Client { socket=handle, rbuf=new_buffer }
242 13f2321c Iustin Pop
243 6583e677 Iustin Pop
-- | Closes the client socket.
244 6583e677 Iustin Pop
closeClient :: Client -> IO ()
245 e821050d Iustin Pop
closeClient = hClose . socket
246 6583e677 Iustin Pop
247 6583e677 Iustin Pop
-- | Sends a message over a luxi transport.
248 6583e677 Iustin Pop
sendMsg :: Client -> String -> IO ()
249 4cd79ca8 Iustin Pop
sendMsg s buf = withTimeout luxiDefRwto "sending luxi message" $ do
250 62d5242b Iustin Pop
  let encoded = UTF8L.fromString buf
251 e821050d Iustin Pop
      handle = socket s
252 62d5242b Iustin Pop
  BL.hPut handle encoded
253 e821050d Iustin Pop
  B.hPut handle bEOM
254 e821050d Iustin Pop
  hFlush handle
255 e821050d Iustin Pop
256 e821050d Iustin Pop
-- | Given a current buffer and the handle, it will read from the
257 e821050d Iustin Pop
-- network until we get a full message, and it will return that
258 e821050d Iustin Pop
-- message and the leftover buffer contents.
259 e821050d Iustin Pop
recvUpdate :: Handle -> B.ByteString -> IO (B.ByteString, B.ByteString)
260 e821050d Iustin Pop
recvUpdate handle obuf = do
261 4cd79ca8 Iustin Pop
  nbuf <- withTimeout luxiDefRwto "reading luxi response" $ do
262 e821050d Iustin Pop
            _ <- hWaitForInput handle (-1)
263 e821050d Iustin Pop
            B.hGetNonBlocking handle 4096
264 e821050d Iustin Pop
  let (msg, remaining) = B.break (eOM ==) nbuf
265 e821050d Iustin Pop
      newbuf = B.append obuf msg
266 e821050d Iustin Pop
  if B.null remaining
267 e821050d Iustin Pop
    then recvUpdate handle newbuf
268 e821050d Iustin Pop
    else return (newbuf, B.tail remaining)
269 6583e677 Iustin Pop
270 6583e677 Iustin Pop
-- | Waits for a message over a luxi transport.
271 6583e677 Iustin Pop
recvMsg :: Client -> IO String
272 6583e677 Iustin Pop
recvMsg s = do
273 6583e677 Iustin Pop
  cbuf <- readIORef $ rbuf s
274 e821050d Iustin Pop
  let (imsg, ibuf) = B.break (eOM ==) cbuf
275 95f490de Iustin Pop
  (msg, nbuf) <-
276 e821050d Iustin Pop
    if B.null ibuf      -- if old buffer didn't contain a full message
277 e821050d Iustin Pop
      then recvUpdate (socket s) cbuf   -- then we read from network
278 e821050d Iustin Pop
      else return (imsg, B.tail ibuf)   -- else we return data from our buffer
279 6583e677 Iustin Pop
  writeIORef (rbuf s) nbuf
280 e821050d Iustin Pop
  return $ UTF8.toString msg
281 6583e677 Iustin Pop
282 0aff2293 Iustin Pop
-- | Extended wrapper over recvMsg.
283 0aff2293 Iustin Pop
recvMsgExt :: Client -> IO RecvResult
284 0aff2293 Iustin Pop
recvMsgExt s =
285 7ae5d703 Iustin Pop
  Control.Exception.catch (liftM RecvOk (recvMsg s)) $ \e ->
286 66ad857a Iustin Pop
    return $ if isEOFError e
287 66ad857a Iustin Pop
               then RecvConnClosed
288 66ad857a Iustin Pop
               else RecvError (show e)
289 0aff2293 Iustin Pop
290 6583e677 Iustin Pop
-- | Serialize a request to String.
291 6583e677 Iustin Pop
buildCall :: LuxiOp  -- ^ The method
292 6583e677 Iustin Pop
          -> String  -- ^ The serialized form
293 683b1ca7 Iustin Pop
buildCall lo =
294 2cdaf225 Iustin Pop
  let ja = [ (strOfKey Method, J.showJSON $ strOfOp lo)
295 2cdaf225 Iustin Pop
           , (strOfKey Args, opToArgs lo)
296 ebf38064 Iustin Pop
           ]
297 ebf38064 Iustin Pop
      jo = toJSObject ja
298 ebf38064 Iustin Pop
  in encodeStrict jo
299 6583e677 Iustin Pop
300 0aff2293 Iustin Pop
-- | Serialize the response to String.
301 0aff2293 Iustin Pop
buildResponse :: Bool    -- ^ Success
302 0aff2293 Iustin Pop
              -> JSValue -- ^ The arguments
303 0aff2293 Iustin Pop
              -> String  -- ^ The serialized form
304 0aff2293 Iustin Pop
buildResponse success args =
305 0aff2293 Iustin Pop
  let ja = [ (strOfKey Success, JSBool success)
306 0aff2293 Iustin Pop
           , (strOfKey Result, args)]
307 0aff2293 Iustin Pop
      jo = toJSObject ja
308 0aff2293 Iustin Pop
  in encodeStrict jo
309 0aff2293 Iustin Pop
310 cdd495ae Iustin Pop
-- | Check that luxi request contains the required keys and parse it.
311 cdd495ae Iustin Pop
validateCall :: String -> Result LuxiCall
312 cdd495ae Iustin Pop
validateCall s = do
313 0aff2293 Iustin Pop
  arr <- fromJResult "parsing top-level luxi message" $
314 0aff2293 Iustin Pop
         decodeStrict s::Result (JSObject JSValue)
315 cdd495ae Iustin Pop
  let aobj = fromJSObject arr
316 cdd495ae Iustin Pop
  call <- fromObj aobj (strOfKey Method)::Result LuxiReq
317 cdd495ae Iustin Pop
  args <- fromObj aobj (strOfKey Args)
318 cdd495ae Iustin Pop
  return (LuxiCall call args)
319 cdd495ae Iustin Pop
320 cdd495ae Iustin Pop
-- | Converts Luxi call arguments into a 'LuxiOp' data structure.
321 cdd495ae Iustin Pop
--
322 cdd495ae Iustin Pop
-- This is currently hand-coded until we make it more uniform so that
323 cdd495ae Iustin Pop
-- it can be generated using TH.
324 cdd495ae Iustin Pop
decodeCall :: LuxiCall -> Result LuxiOp
325 cdd495ae Iustin Pop
decodeCall (LuxiCall call args) =
326 cdd495ae Iustin Pop
  case call of
327 cdd495ae Iustin Pop
    ReqQueryJobs -> do
328 c48711d5 Iustin Pop
              (jids, jargs) <- fromJVal args
329 d2970809 Iustin Pop
              jids' <- case jids of
330 d2970809 Iustin Pop
                         JSNull -> return []
331 d2970809 Iustin Pop
                         _ -> fromJVal jids
332 d2970809 Iustin Pop
              return $ QueryJobs jids' jargs
333 cdd495ae Iustin Pop
    ReqQueryInstances -> do
334 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
335 cdd495ae Iustin Pop
              return $ QueryInstances names fields locking
336 cdd495ae Iustin Pop
    ReqQueryNodes -> do
337 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
338 cdd495ae Iustin Pop
              return $ QueryNodes names fields locking
339 cdd495ae Iustin Pop
    ReqQueryGroups -> do
340 cdd495ae Iustin Pop
              (names, fields, locking) <- fromJVal args
341 cdd495ae Iustin Pop
              return $ QueryGroups names fields locking
342 5b11f8db Iustin Pop
    ReqQueryClusterInfo ->
343 cdd495ae Iustin Pop
              return QueryClusterInfo
344 cdd495ae Iustin Pop
    ReqQuery -> do
345 9a94c848 Iustin Pop
              (what, fields, qfilter) <- fromJVal args
346 9a94c848 Iustin Pop
              return $ Query what fields qfilter
347 72295708 Iustin Pop
    ReqQueryFields -> do
348 72295708 Iustin Pop
              (what, fields) <- fromJVal args
349 72295708 Iustin Pop
              fields' <- case fields of
350 72295708 Iustin Pop
                           JSNull -> return []
351 72295708 Iustin Pop
                           _ -> fromJVal fields
352 72295708 Iustin Pop
              return $ QueryFields what fields'
353 cdd495ae Iustin Pop
    ReqSubmitJob -> do
354 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
355 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
356 cdd495ae Iustin Pop
              return $ SubmitJob ops2
357 cdd495ae Iustin Pop
    ReqSubmitManyJobs -> do
358 cdd495ae Iustin Pop
              [ops1] <- fromJVal args
359 cdd495ae Iustin Pop
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
360 cdd495ae Iustin Pop
              return $ SubmitManyJobs ops2
361 cdd495ae Iustin Pop
    ReqWaitForJobChange -> do
362 cdd495ae Iustin Pop
              (jid, fields, pinfo, pidx, wtmout) <-
363 cdd495ae Iustin Pop
                -- No instance for 5-tuple, code copied from the
364 cdd495ae Iustin Pop
                -- json sources and adapted
365 cdd495ae Iustin Pop
                fromJResult "Parsing WaitForJobChange message" $
366 cdd495ae Iustin Pop
                case args of
367 cdd495ae Iustin Pop
                  JSArray [a, b, c, d, e] ->
368 cdd495ae Iustin Pop
                    (,,,,) `fmap`
369 cdd495ae Iustin Pop
                    J.readJSON a `ap`
370 cdd495ae Iustin Pop
                    J.readJSON b `ap`
371 cdd495ae Iustin Pop
                    J.readJSON c `ap`
372 cdd495ae Iustin Pop
                    J.readJSON d `ap`
373 cdd495ae Iustin Pop
                    J.readJSON e
374 cdd495ae Iustin Pop
                  _ -> J.Error "Not enough values"
375 c48711d5 Iustin Pop
              return $ WaitForJobChange jid fields pinfo pidx wtmout
376 cdd495ae Iustin Pop
    ReqArchiveJob -> do
377 cdd495ae Iustin Pop
              [jid] <- fromJVal args
378 c48711d5 Iustin Pop
              return $ ArchiveJob jid
379 cdd495ae Iustin Pop
    ReqAutoArchiveJobs -> do
380 cdd495ae Iustin Pop
              (age, tmout) <- fromJVal args
381 cdd495ae Iustin Pop
              return $ AutoArchiveJobs age tmout
382 cdd495ae Iustin Pop
    ReqQueryExports -> do
383 cdd495ae Iustin Pop
              (nodes, lock) <- fromJVal args
384 cdd495ae Iustin Pop
              return $ QueryExports nodes lock
385 cdd495ae Iustin Pop
    ReqQueryConfigValues -> do
386 cdd495ae Iustin Pop
              [fields] <- fromJVal args
387 cdd495ae Iustin Pop
              return $ QueryConfigValues fields
388 cdd495ae Iustin Pop
    ReqQueryTags -> do
389 cdd495ae Iustin Pop
              (kind, name) <- fromJVal args
390 d8e7c45e Iustin Pop
              item <- tagObjectFrom kind name
391 d8e7c45e Iustin Pop
              return $ QueryTags item
392 cdd495ae Iustin Pop
    ReqCancelJob -> do
393 c48711d5 Iustin Pop
              [jid] <- fromJVal args
394 c48711d5 Iustin Pop
              return $ CancelJob jid
395 f63ffb37 Michael Hanselmann
    ReqChangeJobPriority -> do
396 c48711d5 Iustin Pop
              (jid, priority) <- fromJVal args
397 c48711d5 Iustin Pop
              return $ ChangeJobPriority jid priority
398 cdd495ae Iustin Pop
    ReqSetDrainFlag -> do
399 cdd495ae Iustin Pop
              [flag] <- fromJVal args
400 cdd495ae Iustin Pop
              return $ SetDrainFlag flag
401 cdd495ae Iustin Pop
    ReqSetWatcherPause -> do
402 cdd495ae Iustin Pop
              [duration] <- fromJVal args
403 cdd495ae Iustin Pop
              return $ SetWatcherPause duration
404 cdd495ae Iustin Pop
405 6583e677 Iustin Pop
-- | Check that luxi responses contain the required keys and that the
406 6583e677 Iustin Pop
-- call was successful.
407 7adb7dff Iustin Pop
validateResult :: String -> ErrorResult JSValue
408 6583e677 Iustin Pop
validateResult s = do
409 e821050d Iustin Pop
  when (UTF8.replacement_char `elem` s) $
410 e821050d Iustin Pop
       fail "Failed to decode UTF-8, detected replacement char after decoding"
411 7adb7dff Iustin Pop
  oarr <- fromJResult "Parsing LUXI response" (decodeStrict s)
412 262f3e6c Iustin Pop
  let arr = J.fromJSObject oarr
413 7adb7dff Iustin Pop
  status <- fromObj arr (strOfKey Success)
414 7adb7dff Iustin Pop
  result <- fromObj arr (strOfKey Result)
415 3603605a Iustin Pop
  if status
416 7adb7dff Iustin Pop
    then return result
417 7adb7dff Iustin Pop
    else decodeError result
418 7adb7dff Iustin Pop
419 7adb7dff Iustin Pop
-- | Try to decode an error from the server response. This function
420 7adb7dff Iustin Pop
-- will always fail, since it's called only on the error path (when
421 7adb7dff Iustin Pop
-- status is False).
422 7adb7dff Iustin Pop
decodeError :: JSValue -> ErrorResult JSValue
423 7adb7dff Iustin Pop
decodeError val =
424 7adb7dff Iustin Pop
  case fromJVal val of
425 7adb7dff Iustin Pop
    Ok e -> Bad e
426 7adb7dff Iustin Pop
    Bad msg -> Bad $ GenericError msg
427 6583e677 Iustin Pop
428 6583e677 Iustin Pop
-- | Generic luxi method call.
429 7adb7dff Iustin Pop
callMethod :: LuxiOp -> Client -> IO (ErrorResult JSValue)
430 683b1ca7 Iustin Pop
callMethod method s = do
431 683b1ca7 Iustin Pop
  sendMsg s $ buildCall method
432 6583e677 Iustin Pop
  result <- recvMsg s
433 6583e677 Iustin Pop
  let rval = validateResult result
434 6583e677 Iustin Pop
  return rval
435 9a2ff880 Iustin Pop
436 619e89c8 Iustin Pop
-- | Parse job submission result.
437 7adb7dff Iustin Pop
parseSubmitJobResult :: JSValue -> ErrorResult JobId
438 7adb7dff Iustin Pop
parseSubmitJobResult (JSArray [JSBool True, v]) =
439 c48711d5 Iustin Pop
  case J.readJSON v of
440 c48711d5 Iustin Pop
    J.Error msg -> Bad $ LuxiError msg
441 c48711d5 Iustin Pop
    J.Ok v' -> Ok v'
442 619e89c8 Iustin Pop
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
443 7adb7dff Iustin Pop
  Bad . LuxiError $ fromJSString x
444 7adb7dff Iustin Pop
parseSubmitJobResult v =
445 7adb7dff Iustin Pop
  Bad . LuxiError $ "Unknown result from the master daemon: " ++
446 7adb7dff Iustin Pop
      show (pp_value v)
447 619e89c8 Iustin Pop
448 9a2ff880 Iustin Pop
-- | Specialized submitManyJobs call.
449 7e723913 Iustin Pop
submitManyJobs :: Client -> [[MetaOpCode]] -> IO (ErrorResult [JobId])
450 9a2ff880 Iustin Pop
submitManyJobs s jobs = do
451 683b1ca7 Iustin Pop
  rval <- callMethod (SubmitManyJobs jobs) s
452 9a2ff880 Iustin Pop
  -- map each result (status, payload) pair into a nice Result ADT
453 9a2ff880 Iustin Pop
  return $ case rval of
454 9a2ff880 Iustin Pop
             Bad x -> Bad x
455 619e89c8 Iustin Pop
             Ok (JSArray r) -> mapM parseSubmitJobResult r
456 7adb7dff Iustin Pop
             x -> Bad . LuxiError $
457 7adb7dff Iustin Pop
                  "Cannot parse response from Ganeti: " ++ show x
458 9a2ff880 Iustin Pop
459 9a2ff880 Iustin Pop
-- | Custom queryJobs call.
460 7adb7dff Iustin Pop
queryJobsStatus :: Client -> [JobId] -> IO (ErrorResult [JobStatus])
461 9a2ff880 Iustin Pop
queryJobsStatus s jids = do
462 76b62028 Iustin Pop
  rval <- callMethod (QueryJobs jids ["status"]) s
463 9a2ff880 Iustin Pop
  return $ case rval of
464 9a2ff880 Iustin Pop
             Bad x -> Bad x
465 9a2ff880 Iustin Pop
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
466 9a2ff880 Iustin Pop
                       J.Ok vals -> if any null vals
467 7adb7dff Iustin Pop
                                    then Bad $
468 7adb7dff Iustin Pop
                                         LuxiError "Missing job status field"
469 9a2ff880 Iustin Pop
                                    else Ok (map head vals)
470 7adb7dff Iustin Pop
                       J.Error x -> Bad $ LuxiError x