Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 72375ff8

History | View | Annotate | Download (22 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
import System.Directory
94

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

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

    
109
-- * Base RPC functionality and types
110

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

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

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

    
140
type ERpcError = Either RpcError
141

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

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

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

    
167
-- | Check if a string represented address is IPv6
168
isIpV6 :: String -> Bool
169
isIpV6 = (':' `elem`)
170

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

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

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

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

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

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

    
230
-- | Execute multiple RPC calls in parallel
231
executeRpcCalls :: (Rpc a b) => [(Node, a)] -> IO [(Node, ERpcError b)]
232
executeRpcCalls nodeCalls = do
233
  cert_file <- P.nodedCertFile
234
  client_cert_file_name <- P.nodedClientCertFile
235
  client_file_exists <- doesFileExist client_cert_file_name
236
  -- FIXME: This is needed to ensure upgradability to 2.11
237
  -- Remove in 2.12.
238
  let client_cert_file = if client_file_exists
239
                         then client_cert_file_name
240
                         else cert_file
241
      (nodes, calls) = unzip nodeCalls
242
      opts = map (getOptionsForCall cert_file client_cert_file) calls
243
      opts_urls = zipWith3 (\n c o ->
244
                         case prepareHttpRequest o n c of
245
                           Left v -> Left v
246
                           Right request ->
247
                             Right (CurlPostFields [requestData request]:
248
                                    requestOpts request,
249
                                    requestUrl request)
250
                    ) nodes calls opts
251
  -- split the opts_urls list; we don't want to pass the
252
  -- failed-already nodes to Curl
253
  let (lefts, rights, trail) = splitEithers opts_urls
254
  results <- execMultiCall rights
255
  results' <- case recombineEithers lefts results trail of
256
                Bad msg -> error msg
257
                Ok r -> return r
258
  -- now parse the replies
259
  let results'' = zipWith parseHttpReply calls results'
260
      pairedList = zip nodes results''
261
  logRpcErrors pairedList
262
  return pairedList
263

    
264
-- | Execute an RPC call for many nodes in parallel.
265
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
266
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
267

    
268
-- | Helper function that is used to read dictionaries of values.
269
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
270
sanitizeDictResults =
271
  foldr sanitize1 (Right [])
272
  where
273
    sanitize1 _ (Left e) = Left e
274
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
275
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
276

    
277
-- | Helper function to tranform JSON Result to Either RpcError b.
278
-- Note: For now we really only use it for b s.t. Rpc c b for some c
279
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
280
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
281
fromJResultToRes (J.Ok v) f = Right $ f v
282

    
283
-- | Helper function transforming JSValue to Rpc result type.
284
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
285
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
286

    
287
-- * RPC calls and results
288

    
289
-- ** Instance info
290

    
291
-- | Returns information about a single instance
292
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
293
  [ simpleField "instance" [t| String |]
294
  , simpleField "hname" [t| Hypervisor |]
295
  ])
296

    
297
$(declareILADT "InstanceState"
298
  [ ("InstanceStateRunning", 0)
299
  , ("InstanceStateShutdown", 1)
300
  ])
301

    
302
$(makeJSONInstance ''InstanceState)
303

    
304
instance PyValue InstanceState where
305
  showValue = show . instanceStateToRaw
306

    
307
$(buildObject "InstanceInfo" "instInfo"
308
  [ simpleField "memory" [t| Int|]
309
  , simpleField "state"  [t| InstanceState |]
310
  , simpleField "vcpus"  [t| Int |]
311
  , simpleField "time"   [t| Int |]
312
  ])
313

    
314
-- This is optional here because the result may be empty if instance is
315
-- not on a node - and this is not considered an error.
316
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
317
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
318

    
319
instance RpcCall RpcCallInstanceInfo where
320
  rpcCallName _          = "instance_info"
321
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
322
  rpcCallAcceptOffline _ = False
323

    
324
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
325
  rpcResultFill _ res =
326
    case res of
327
      J.JSObject res' ->
328
        case J.fromJSObject res' of
329
          [] -> Right $ RpcResultInstanceInfo Nothing
330
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
331
      _ -> Left $ JsonDecodeError
332
           ("Expected JSObject, got " ++ show (pp_value res))
333

    
334
-- ** AllInstancesInfo
335

    
336
-- | Returns information about all running instances on the given nodes
337
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
338
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
339

    
340
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
341
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
342

    
343
instance RpcCall RpcCallAllInstancesInfo where
344
  rpcCallName _          = "all_instances_info"
345
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
346
  rpcCallAcceptOffline _ = False
347
  rpcCallData _ call     = J.encode (
348
    map fst $ rpcCallAllInstInfoHypervisors call,
349
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
350

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

    
364
-- ** InstanceConsoleInfo
365

    
366
-- | Returns information about how to access instances on the given node
367
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
368
  [ simpleField "instance"    [t| Instance |]
369
  , simpleField "node"        [t| Node |]
370
  , simpleField "group"       [t| NodeGroup |]
371
  , simpleField "hvParams"    [t| HvParams |]
372
  , simpleField "beParams"    [t| FilledBeParams |]
373
  ])
374

    
375
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
376
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
377

    
378
$(buildObject "InstanceConsoleInfo" "instConsInfo"
379
  [ simpleField "instance"    [t| String |]
380
  , simpleField "kind"        [t| String |]
381
  , optionalField $
382
    simpleField "message"     [t| String |]
383
  , optionalField $
384
    simpleField "host"        [t| String |]
385
  , optionalField $
386
    simpleField "port"        [t| Int |]
387
  , optionalField $
388
    simpleField "user"        [t| String |]
389
  , optionalField $
390
    simpleField "command"     [t| [String] |]
391
  , optionalField $
392
    simpleField "display"     [t| String |]
393
  ])
394

    
395
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
396
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
397

    
398
instance RpcCall RpcCallInstanceConsoleInfo where
399
  rpcCallName _          = "instance_console_info"
400
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
401
  rpcCallAcceptOffline _ = False
402
  rpcCallData _ call     = J.encode .
403
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
404

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

    
417
-- ** InstanceList
418

    
419
-- | Returns the list of running instances on the given nodes
420
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
421
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
422

    
423
$(buildObject "RpcResultInstanceList" "rpcResInstList"
424
  [ simpleField "instances" [t| [String] |] ])
425

    
426
instance RpcCall RpcCallInstanceList where
427
  rpcCallName _          = "instance_list"
428
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
429
  rpcCallAcceptOffline _ = False
430

    
431
instance Rpc RpcCallInstanceList RpcResultInstanceList where
432
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
433

    
434
-- ** NodeInfo
435

    
436
-- | Returns node information
437
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
438
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
439
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
440
  ])
441

    
442
$(buildObject "StorageInfo" "storageInfo"
443
  [ simpleField "name" [t| String |]
444
  , simpleField "type" [t| String |]
445
  , optionalField $ simpleField "storage_free" [t| Int |]
446
  , optionalField $ simpleField "storage_size" [t| Int |]
447
  ])
448

    
449
-- | We only provide common fields as described in hv_base.py.
450
$(buildObject "HvInfo" "hvInfo"
451
  [ simpleField "memory_total" [t| Int |]
452
  , simpleField "memory_free" [t| Int |]
453
  , simpleField "memory_dom0" [t| Int |]
454
  , simpleField "cpu_total" [t| Int |]
455
  , simpleField "cpu_nodes" [t| Int |]
456
  , simpleField "cpu_sockets" [t| Int |]
457
  , simpleField "cpu_dom0" [t| Int |]
458
  ])
459

    
460
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
461
  [ simpleField "boot_id" [t| String |]
462
  , simpleField "storage_info" [t| [StorageInfo] |]
463
  , simpleField "hv_info" [t| [HvInfo] |]
464
  ])
465

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

    
477
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
478
  rpcResultFill _ res =
479
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
480

    
481
-- ** Version
482

    
483
-- | Query node version.
484
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
485

    
486
-- | Query node reply.
487
$(buildObject "RpcResultVersion" "rpcResultVersion"
488
  [ simpleField "version" [t| Int |]
489
  ])
490

    
491
instance RpcCall RpcCallVersion where
492
  rpcCallName _          = "version"
493
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
494
  rpcCallAcceptOffline _ = True
495
  rpcCallData _          = J.encode
496

    
497
instance Rpc RpcCallVersion RpcResultVersion where
498
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
499

    
500
-- ** StorageList
501

    
502
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
503
  [ simpleField "su_name" [t| StorageType |]
504
  , simpleField "su_args" [t| [String] |]
505
  , simpleField "name"    [t| String |]
506
  , simpleField "fields"  [t| [StorageField] |]
507
  ])
508

    
509
-- FIXME: The resulting JSValues should have types appropriate for their
510
-- StorageField value: Used -> Bool, Name -> String etc
511
$(buildObject "RpcResultStorageList" "rpcResStorageList"
512
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
513

    
514
instance RpcCall RpcCallStorageList where
515
  rpcCallName _          = "storage_list"
516
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
517
  rpcCallAcceptOffline _ = False
518

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

    
524
-- ** TestDelay
525

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

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

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

    
541
instance RpcCall RpcCallTestDelay where
542
  rpcCallName _          = "test_delay"
543
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
544
  rpcCallAcceptOffline _ = False
545

    
546
instance Rpc RpcCallTestDelay RpcResultTestDelay where
547
  rpcResultFill _ res = fromJSValueToRes res id
548

    
549
-- ** ExportList
550

    
551
-- | Call definition for export list.
552

    
553
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
554

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

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

    
566
instance Rpc RpcCallExportList RpcResultExportList where
567
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
568

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

    
578
$(buildObject "RpcResultJobQueueUpdate" "rpcResultJobQueueUpdate" [])
579

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

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

    
599
-- | Rename a file in the job queue
600

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

    
605
$(buildObject "RpcResultJobqueueRename" "rpcResultJobqueueRename" [])
606

    
607
instance RpcCall RpcCallJobqueueRename where
608
  rpcCallName _          = "jobqueue_rename"
609
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
610
  rpcCallAcceptOffline _ = False
611

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

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

    
632
instance RpcCall RpcCallSetWatcherPause where
633
  rpcCallName _          = "set_watcher_pause"
634
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
635
  rpcCallAcceptOffline _ = False
636

    
637
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
638

    
639
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
640
  rpcResultFill _ res =
641
    case res of
642
      J.JSNull ->  Right RpcResultSetWatcherPause
643
      _ -> Left $ JsonDecodeError
644
           ("Expected JSNull, got " ++ show (pp_value res))
645

    
646
-- ** Queue drain status
647
      
648
-- | Set the queu drain flag
649
      
650
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
651
  [ simpleField "value" [t| Bool |]
652
  ])
653

    
654
instance RpcCall RpcCallSetDrainFlag where
655
  rpcCallName _          = "jobqueue_set_drain_flag"
656
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
657
  rpcCallAcceptOffline _ = False
658

    
659
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
660

    
661
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
662
  rpcResultFill _ res =
663
    case res of
664
      J.JSNull ->  Right RpcResultSetDrainFlag
665
      _ -> Left $ JsonDecodeError
666
           ("Expected JSNull, got " ++ show (pp_value res))
667