Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ 289e7fcc

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