Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ 6d558717

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