Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ 13f2321c

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