Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 560ef132

History | View | Annotate | Download (22.2 kB)

1
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
2
  BangPatterns, TemplateHaskell #-}
3

    
4
{-| Implementation of the RPC client.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2012, 2013 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.Rpc
30
  ( RpcCall
31
  , Rpc
32
  , RpcError(..)
33
  , ERpcError
34
  , explainRpcError
35
  , executeRpcCall
36
  , executeRpcCalls
37
  , logRpcErrors
38

    
39
  , rpcCallName
40
  , rpcCallTimeout
41
  , rpcCallData
42
  , rpcCallAcceptOffline
43

    
44
  , rpcResultFill
45

    
46
  , RpcCallInstanceInfo(..)
47
  , InstanceState(..)
48
  , InstanceInfo(..)
49
  , RpcResultInstanceInfo(..)
50

    
51
  , RpcCallAllInstancesInfo(..)
52
  , RpcResultAllInstancesInfo(..)
53

    
54
  , InstanceConsoleInfoParams(..)
55
  , InstanceConsoleInfo(..)
56
  , RpcCallInstanceConsoleInfo(..)
57
  , RpcResultInstanceConsoleInfo(..)
58

    
59
  , RpcCallInstanceList(..)
60
  , RpcResultInstanceList(..)
61

    
62
  , HvInfo(..)
63
  , StorageInfo(..)
64
  , RpcCallNodeInfo(..)
65
  , RpcResultNodeInfo(..)
66

    
67
  , RpcCallVersion(..)
68
  , RpcResultVersion(..)
69

    
70
  , RpcCallStorageList(..)
71
  , RpcResultStorageList(..)
72

    
73
  , RpcCallTestDelay(..)
74
  , RpcResultTestDelay(..)
75

    
76
  , RpcCallExportList(..)
77
  , RpcResultExportList(..)
78

    
79
  , RpcCallJobqueueUpdate(..)
80
  , RpcCallJobqueueRename(..)
81
  , RpcCallSetWatcherPause(..)
82
  , RpcCallSetDrainFlag(..)
83
  ) where
84

    
85
import Control.Arrow (second)
86
import qualified Codec.Compression.Zlib as Zlib
87
import qualified Data.ByteString.Lazy.Char8 as BL
88
import qualified Data.Map as Map
89
import Data.Maybe (fromMaybe)
90
import qualified Text.JSON as J
91
import Text.JSON.Pretty (pp_value)
92
import qualified Data.ByteString.Base64.Lazy as Base64
93

    
94
import Network.Curl hiding (content)
95
import qualified Ganeti.Path as P
96

    
97
import Ganeti.BasicTypes
98
import qualified Ganeti.Constants as C
99
import Ganeti.JSON
100
import Ganeti.Logging
101
import Ganeti.Objects
102
import Ganeti.THH
103
import Ganeti.Types
104
import Ganeti.Curl.Multi
105
import Ganeti.Utils
106

    
107
-- * Base RPC functionality and types
108

    
109
-- | The curl options used for RPC.
110
curlOpts :: [CurlOption]
111
curlOpts = [ CurlFollowLocation False
112
           , CurlSSLVerifyHost 0
113
           , CurlSSLVerifyPeer True
114
           , CurlSSLCertType "PEM"
115
           , CurlSSLKeyType "PEM"
116
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
117
           ]
118

    
119
-- | Data type for RPC error reporting.
120
data RpcError
121
  = CurlLayerError String
122
  | JsonDecodeError String
123
  | RpcResultError String
124
  | OfflineNodeError
125
  deriving (Show, Eq)
126

    
127
-- | Provide explanation to RPC errors.
128
explainRpcError :: RpcError -> String
129
explainRpcError (CurlLayerError code) =
130
    "Curl error:" ++ code
131
explainRpcError (JsonDecodeError msg) =
132
    "Error while decoding JSON from HTTP response: " ++ msg
133
explainRpcError (RpcResultError msg) =
134
    "Error reponse received from RPC server: " ++ msg
135
explainRpcError OfflineNodeError =
136
    "Node is marked offline"
137

    
138
type ERpcError = Either RpcError
139

    
140
-- | A generic class for RPC calls.
141
class (J.JSON a) => RpcCall a where
142
  -- | Give the (Python) name of the procedure.
143
  rpcCallName :: a -> String
144
  -- | Calculate the timeout value for the call execution.
145
  rpcCallTimeout :: a -> Int
146
  -- | Prepare arguments of the call to be send as POST.
147
  rpcCallData :: Node -> a -> String
148
  -- | Whether we accept offline nodes when making a call.
149
  rpcCallAcceptOffline :: a -> Bool
150

    
151
-- | Generic class that ensures matching RPC call with its respective
152
-- result.
153
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
154
  -- | Create a result based on the received HTTP response.
155
  rpcResultFill :: a -> J.JSValue -> ERpcError b
156

    
157
-- | Http Request definition.
158
data HttpClientRequest = HttpClientRequest
159
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
160
  , requestData :: String       -- ^ The arguments for the call
161
  , requestOpts :: [CurlOption] -- ^ The various curl options
162
  }
163

    
164
-- | Check if a string represented address is IPv6
165
isIpV6 :: String -> Bool
166
isIpV6 = (':' `elem`)
167

    
168
-- | Prepare url for the HTTP request.
169
prepareUrl :: (RpcCall a) => Node -> a -> String
170
prepareUrl node call =
171
  let node_ip = nodePrimaryIp node
172
      node_address = if isIpV6 node_ip
173
                     then "[" ++ node_ip ++ "]"
174
                     else node_ip
175
      port = C.defaultNodedPort
176
      path_prefix = "https://" ++ node_address ++ ":" ++ show port
177
  in path_prefix ++ "/" ++ rpcCallName call
178

    
179
-- | Create HTTP request for a given node provided it is online,
180
-- otherwise create empty response.
181
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
182
                   -> ERpcError HttpClientRequest
183
prepareHttpRequest opts node call
184
  | rpcCallAcceptOffline call || not (nodeOffline node) =
185
      Right HttpClientRequest { requestUrl  = prepareUrl node call
186
                              , requestData = rpcCallData node call
187
                              , requestOpts = opts ++ curlOpts
188
                              }
189
  | otherwise = Left OfflineNodeError
190

    
191
-- | Parse an HTTP reply.
192
parseHttpReply :: (Rpc a b) =>
193
                  a -> ERpcError (CurlCode, String) -> ERpcError b
194
parseHttpReply _ (Left e) = Left e
195
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
196
parseHttpReply _ (Right (code, err)) =
197
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
198

    
199
-- | Parse a result based on the received HTTP response.
200
parseHttpResponse :: (Rpc a b) => a -> String -> ERpcError b
201
parseHttpResponse call res =
202
  case J.decode res of
203
    J.Error val -> Left $ JsonDecodeError val
204
    J.Ok (True, res'') -> rpcResultFill call res''
205
    J.Ok (False, jerr) -> case jerr of
206
       J.JSString msg -> Left $ RpcResultError (J.fromJSString msg)
207
       _ -> Left . JsonDecodeError $ show (pp_value jerr)
208

    
209
-- | Scan the list of results produced by executeRpcCall and log all the RPC
210
-- errors.
211
logRpcErrors :: [(a, ERpcError b)] -> IO ()
212
logRpcErrors allElems =
213
  let logOneRpcErr (_, Right _) = return ()
214
      logOneRpcErr (_, Left err) =
215
        logError $ "Error in the RPC HTTP reply: " ++ show err
216
  in mapM_ logOneRpcErr allElems
217

    
218
-- | Get options for RPC call
219
getOptionsForCall :: (Rpc a b) => FilePath -> FilePath -> a -> [CurlOption]
220
getOptionsForCall cert_path client_cert_path call =
221
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
222
  , CurlSSLCert client_cert_path
223
  , CurlSSLKey client_cert_path
224
  , CurlCAInfo cert_path
225
  ]
226

    
227
-- | Execute multiple RPC calls in parallel
228
executeRpcCalls :: (Rpc a b) => [(Node, a)] -> IO [(Node, ERpcError b)]
229
executeRpcCalls nodeCalls = do
230
  cert_file <- P.nodedCertFile
231
  let (nodes, calls) = unzip nodeCalls
232
      opts = map (getOptionsForCall cert_file cert_file) calls
233
      opts_urls = zipWith3 (\n c o ->
234
                         case prepareHttpRequest o n c of
235
                           Left v -> Left v
236
                           Right request ->
237
                             Right (CurlPostFields [requestData request]:
238
                                    requestOpts request,
239
                                    requestUrl request)
240
                    ) nodes calls opts
241
  -- split the opts_urls list; we don't want to pass the
242
  -- failed-already nodes to Curl
243
  let (lefts, rights, trail) = splitEithers opts_urls
244
  results <- execMultiCall rights
245
  results' <- case recombineEithers lefts results trail of
246
                Bad msg -> error msg
247
                Ok r -> return r
248
  -- now parse the replies
249
  let results'' = zipWith parseHttpReply calls results'
250
      pairedList = zip nodes results''
251
  logRpcErrors pairedList
252
  return pairedList
253

    
254
-- | Execute an RPC call for many nodes in parallel.
255
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
256
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
257

    
258
-- | Helper function that is used to read dictionaries of values.
259
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
260
sanitizeDictResults =
261
  foldr sanitize1 (Right [])
262
  where
263
    sanitize1 _ (Left e) = Left e
264
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
265
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
266

    
267
-- | Helper function to tranform JSON Result to Either RpcError b.
268
-- Note: For now we really only use it for b s.t. Rpc c b for some c
269
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
270
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
271
fromJResultToRes (J.Ok v) f = Right $ f v
272

    
273
-- | Helper function transforming JSValue to Rpc result type.
274
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
275
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
276

    
277
-- * RPC calls and results
278

    
279
-- ** Instance info
280

    
281
-- | Returns information about a single instance
282
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
283
  [ simpleField "instance" [t| String |]
284
  , simpleField "hname" [t| Hypervisor |]
285
  ])
286

    
287
$(declareILADT "InstanceState"
288
  [ ("InstanceStateRunning", 0)
289
  , ("InstanceStateShutdown", 1)
290
  ])
291

    
292
$(makeJSONInstance ''InstanceState)
293

    
294
instance PyValue InstanceState where
295
  showValue = show . instanceStateToRaw
296

    
297
$(buildObject "InstanceInfo" "instInfo"
298
  [ simpleField "memory" [t| Int|]
299
  , simpleField "state"  [t| InstanceState |]
300
  , simpleField "vcpus"  [t| Int |]
301
  , simpleField "time"   [t| Int |]
302
  ])
303

    
304
-- This is optional here because the result may be empty if instance is
305
-- not on a node - and this is not considered an error.
306
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
307
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
308

    
309
instance RpcCall RpcCallInstanceInfo where
310
  rpcCallName _          = "instance_info"
311
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
312
  rpcCallAcceptOffline _ = False
313
  rpcCallData _ call     = J.encode
314
    ( rpcCallInstInfoInstance call
315
    , rpcCallInstInfoHname call
316
    )
317

    
318
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
319
  rpcResultFill _ res =
320
    case res of
321
      J.JSObject res' ->
322
        case J.fromJSObject res' of
323
          [] -> Right $ RpcResultInstanceInfo Nothing
324
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
325
      _ -> Left $ JsonDecodeError
326
           ("Expected JSObject, got " ++ show (pp_value res))
327

    
328
-- ** AllInstancesInfo
329

    
330
-- | Returns information about all running instances on the given nodes
331
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
332
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
333

    
334
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
335
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
336

    
337
instance RpcCall RpcCallAllInstancesInfo where
338
  rpcCallName _          = "all_instances_info"
339
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
340
  rpcCallAcceptOffline _ = False
341
  rpcCallData _ call     = J.encode (
342
    map fst $ rpcCallAllInstInfoHypervisors call,
343
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
344

    
345
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
346
  -- FIXME: Is there a simpler way to do it?
347
  rpcResultFill _ res =
348
    case res of
349
      J.JSObject res' ->
350
        let res'' = map (second J.readJSON) (J.fromJSObject res')
351
                        :: [(String, J.Result InstanceInfo)] in
352
        case sanitizeDictResults res'' of
353
          Left err -> Left err
354
          Right insts -> Right $ RpcResultAllInstancesInfo insts
355
      _ -> Left $ JsonDecodeError
356
           ("Expected JSObject, got " ++ show (pp_value res))
357

    
358
-- ** InstanceConsoleInfo
359

    
360
-- | Returns information about how to access instances on the given node
361
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
362
  [ simpleField "instance"    [t| Instance |]
363
  , simpleField "node"        [t| Node |]
364
  , simpleField "group"       [t| NodeGroup |]
365
  , simpleField "hvParams"    [t| HvParams |]
366
  , simpleField "beParams"    [t| FilledBeParams |]
367
  ])
368

    
369
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
370
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
371

    
372
$(buildObject "InstanceConsoleInfo" "instConsInfo"
373
  [ simpleField "instance"    [t| String |]
374
  , simpleField "kind"        [t| String |]
375
  , optionalField $
376
    simpleField "message"     [t| String |]
377
  , optionalField $
378
    simpleField "host"        [t| String |]
379
  , optionalField $
380
    simpleField "port"        [t| Int |]
381
  , optionalField $
382
    simpleField "user"        [t| String |]
383
  , optionalField $
384
    simpleField "command"     [t| [String] |]
385
  , optionalField $
386
    simpleField "display"     [t| String |]
387
  ])
388

    
389
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
390
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
391

    
392
instance RpcCall RpcCallInstanceConsoleInfo where
393
  rpcCallName _          = "instance_console_info"
394
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
395
  rpcCallAcceptOffline _ = False
396
  rpcCallData _ call     = J.encode .
397
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
398

    
399
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
400
  rpcResultFill _ res =
401
    case res of
402
      J.JSObject res' ->
403
        let res'' = map (second J.readJSON) (J.fromJSObject res')
404
                        :: [(String, J.Result InstanceConsoleInfo)] in
405
        case sanitizeDictResults res'' of
406
          Left err -> Left err
407
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
408
      _ -> Left $ JsonDecodeError
409
           ("Expected JSObject, got " ++ show (pp_value res))
410

    
411
-- ** InstanceList
412

    
413
-- | Returns the list of running instances on the given nodes
414
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
415
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
416

    
417
$(buildObject "RpcResultInstanceList" "rpcResInstList"
418
  [ simpleField "instances" [t| [String] |] ])
419

    
420
instance RpcCall RpcCallInstanceList where
421
  rpcCallName _          = "instance_list"
422
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
423
  rpcCallAcceptOffline _ = False
424
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
425

    
426
instance Rpc RpcCallInstanceList RpcResultInstanceList where
427
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
428

    
429
-- ** NodeInfo
430

    
431
-- | Returns node information
432
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
433
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
434
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
435
  ])
436

    
437
$(buildObject "StorageInfo" "storageInfo"
438
  [ simpleField "name" [t| String |]
439
  , simpleField "type" [t| String |]
440
  , optionalField $ simpleField "storage_free" [t| Int |]
441
  , optionalField $ simpleField "storage_size" [t| Int |]
442
  ])
443

    
444
-- | We only provide common fields as described in hv_base.py.
445
$(buildObject "HvInfo" "hvInfo"
446
  [ simpleField "memory_total" [t| Int |]
447
  , simpleField "memory_free" [t| Int |]
448
  , simpleField "memory_dom0" [t| Int |]
449
  , simpleField "cpu_total" [t| Int |]
450
  , simpleField "cpu_nodes" [t| Int |]
451
  , simpleField "cpu_sockets" [t| Int |]
452
  , simpleField "cpu_dom0" [t| Int |]
453
  ])
454

    
455
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
456
  [ simpleField "boot_id" [t| String |]
457
  , simpleField "storage_info" [t| [StorageInfo] |]
458
  , simpleField "hv_info" [t| [HvInfo] |]
459
  ])
460

    
461
instance RpcCall RpcCallNodeInfo where
462
  rpcCallName _          = "node_info"
463
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
464
  rpcCallAcceptOffline _ = False
465
  rpcCallData n call     = J.encode
466
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
467
                         ++ nodeName n)
468
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
469
    , rpcCallNodeInfoHypervisors call
470
    )
471

    
472
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
473
  rpcResultFill _ res =
474
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
475

    
476
-- ** Version
477

    
478
-- | Query node version.
479
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
480

    
481
-- | Query node reply.
482
$(buildObject "RpcResultVersion" "rpcResultVersion"
483
  [ simpleField "version" [t| Int |]
484
  ])
485

    
486
instance RpcCall RpcCallVersion where
487
  rpcCallName _          = "version"
488
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
489
  rpcCallAcceptOffline _ = True
490
  rpcCallData _          = J.encode
491

    
492
instance Rpc RpcCallVersion RpcResultVersion where
493
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
494

    
495
-- ** StorageList
496

    
497
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
498
  [ simpleField "su_name" [t| StorageType |]
499
  , simpleField "su_args" [t| [String] |]
500
  , simpleField "name"    [t| String |]
501
  , simpleField "fields"  [t| [StorageField] |]
502
  ])
503

    
504
-- FIXME: The resulting JSValues should have types appropriate for their
505
-- StorageField value: Used -> Bool, Name -> String etc
506
$(buildObject "RpcResultStorageList" "rpcResStorageList"
507
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
508

    
509
instance RpcCall RpcCallStorageList where
510
  rpcCallName _          = "storage_list"
511
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
512
  rpcCallAcceptOffline _ = False
513
  rpcCallData _ call     = J.encode
514
    ( rpcCallStorageListSuName call
515
    , rpcCallStorageListSuArgs call
516
    , rpcCallStorageListName call
517
    , rpcCallStorageListFields call
518
    )
519

    
520
instance Rpc RpcCallStorageList RpcResultStorageList where
521
  rpcResultFill call res =
522
    let sfields = rpcCallStorageListFields call in
523
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
524

    
525
-- ** TestDelay
526

    
527
-- | Call definition for test delay.
528
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
529
  [ simpleField "duration" [t| Double |]
530
  ])
531

    
532
-- | Result definition for test delay.
533
data RpcResultTestDelay = RpcResultTestDelay
534
                          deriving Show
535

    
536
-- | Custom JSON instance for null result.
537
instance J.JSON RpcResultTestDelay where
538
  showJSON _        = J.JSNull
539
  readJSON J.JSNull = return RpcResultTestDelay
540
  readJSON _        = fail "Unable to read RpcResultTestDelay"
541

    
542
instance RpcCall RpcCallTestDelay where
543
  rpcCallName _          = "test_delay"
544
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
545
  rpcCallAcceptOffline _ = False
546
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
547

    
548
instance Rpc RpcCallTestDelay RpcResultTestDelay where
549
  rpcResultFill _ res = fromJSValueToRes res id
550

    
551
-- ** ExportList
552

    
553
-- | Call definition for export list.
554

    
555
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
556

    
557
-- | Result definition for export list.
558
$(buildObject "RpcResultExportList" "rpcResExportList"
559
  [ simpleField "exports" [t| [String] |]
560
  ])
561

    
562
instance RpcCall RpcCallExportList where
563
  rpcCallName _          = "export_list"
564
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
565
  rpcCallAcceptOffline _ = False
566
  rpcCallData _          = J.encode
567

    
568
instance Rpc RpcCallExportList RpcResultExportList where
569
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
570

    
571
-- ** Job Queue Replication
572
  
573
-- | Update a job queue file
574
  
575
$(buildObject "RpcCallJobqueueUpdate" "rpcCallJobqueueUpdate"
576
  [ simpleField "file_name" [t| String |]
577
  , simpleField "content" [t| String |]
578
  ])
579

    
580
$(buildObject "RpcResultJobQueueUpdate" "rpcResultJobQueueUpdate" [])
581

    
582
instance RpcCall RpcCallJobqueueUpdate where
583
  rpcCallName _          = "jobqueue_update"
584
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
585
  rpcCallAcceptOffline _ = False
586
  rpcCallData _ call     = J.encode
587
    ( rpcCallJobqueueUpdateFileName call
588
    , ( C.rpcEncodingZlibBase64
589
      , BL.unpack . Base64.encode . Zlib.compress . BL.pack
590
          $ rpcCallJobqueueUpdateContent call
591
      )
592
    )
593

    
594
instance Rpc RpcCallJobqueueUpdate RpcResultJobQueueUpdate where
595
  rpcResultFill _ res =
596
    case res of
597
      J.JSNull ->  Right RpcResultJobQueueUpdate
598
      _ -> Left $ JsonDecodeError
599
           ("Expected JSNull, got " ++ show (pp_value res))
600

    
601
-- | Rename a file in the job queue
602

    
603
$(buildObject "RpcCallJobqueueRename" "rpcCallJobqueueRename"
604
  [ simpleField "rename" [t| [(String, String)] |]
605
  ])
606

    
607
$(buildObject "RpcResultJobqueueRename" "rpcResultJobqueueRename" [])
608

    
609
instance RpcCall RpcCallJobqueueRename where
610
  rpcCallName _          = "jobqueue_rename"
611
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
612
  rpcCallAcceptOffline _ = False
613
  rpcCallData _ call     = J.encode [ rpcCallJobqueueRenameRename call ]
614

    
615
instance Rpc RpcCallJobqueueRename RpcResultJobqueueRename where
616
  rpcResultFill call res =
617
    -- Upon success, the RPC returns the list of return values of
618
    -- the rename operations, which is always None, serialized to
619
    -- null in JSON.
620
    let expected = J.showJSON . map (const J.JSNull)
621
                     $ rpcCallJobqueueRenameRename call
622
    in if res == expected
623
      then Right RpcResultJobqueueRename
624
      else Left
625
             $ JsonDecodeError ("Expected JSNull, got " ++ show (pp_value res))
626

    
627
-- ** Watcher Status Update
628
      
629
-- | Set the watcher status
630
      
631
$(buildObject "RpcCallSetWatcherPause" "rpcCallSetWatcherPause"
632
  [ optionalField $ timeAsDoubleField "time"
633
  ])
634

    
635
instance RpcCall RpcCallSetWatcherPause where
636
  rpcCallName _          = "set_watcher_pause"
637
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
638
  rpcCallAcceptOffline _ = False
639
  rpcCallData _ call     = J.encode
640
    [ maybe J.JSNull (J.showJSON . TimeAsDoubleJSON) $
641
            rpcCallSetWatcherPauseTime call ]
642

    
643
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
644

    
645
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
646
  rpcResultFill _ res =
647
    case res of
648
      J.JSNull ->  Right RpcResultSetWatcherPause
649
      _ -> Left $ JsonDecodeError
650
           ("Expected JSNull, got " ++ show (pp_value res))
651

    
652
-- ** Queue drain status
653
      
654
-- | Set the queu drain flag
655
      
656
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
657
  [ simpleField "value" [t| Bool |]
658
  ])
659

    
660
instance RpcCall RpcCallSetDrainFlag where
661
  rpcCallName _          = "jobqueue_set_drain_flag"
662
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
663
  rpcCallAcceptOffline _ = False
664
  rpcCallData _ call     = J.encode [ rpcCallSetDrainFlagValue call ]
665

    
666
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
667

    
668
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
669
  rpcResultFill _ res =
670
    case res of
671
      J.JSNull ->  Right RpcResultSetDrainFlag
672
      _ -> Left $ JsonDecodeError
673
           ("Expected JSNull, got " ++ show (pp_value res))
674