Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ 8a9ee1e9

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