Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ 229da00f

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