Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 64981f25

History | View | Annotate | Download (19.1 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
  ) where
81

    
82
import Control.Arrow (second)
83
import qualified Data.Map as Map
84
import Data.Maybe (fromMaybe)
85
import qualified Text.JSON as J
86
import Text.JSON.Pretty (pp_value)
87

    
88
import Network.Curl hiding (content)
89
import qualified Ganeti.Path as P
90

    
91
import Ganeti.BasicTypes
92
import qualified Ganeti.Constants as C
93
import Ganeti.JSON
94
import Ganeti.Logging
95
import Ganeti.Objects
96
import Ganeti.THH
97
import Ganeti.Types
98
import Ganeti.Curl.Multi
99
import Ganeti.Utils
100

    
101
-- * Base RPC functionality and types
102

    
103
-- | The curl options used for RPC.
104
curlOpts :: [CurlOption]
105
curlOpts = [ CurlFollowLocation False
106
           , CurlSSLVerifyHost 0
107
           , CurlSSLVerifyPeer True
108
           , CurlSSLCertType "PEM"
109
           , CurlSSLKeyType "PEM"
110
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
111
           ]
112

    
113
-- | Data type for RPC error reporting.
114
data RpcError
115
  = CurlLayerError String
116
  | JsonDecodeError String
117
  | RpcResultError String
118
  | OfflineNodeError
119
  deriving (Show, Eq)
120

    
121
-- | Provide explanation to RPC errors.
122
explainRpcError :: RpcError -> String
123
explainRpcError (CurlLayerError code) =
124
    "Curl error:" ++ code
125
explainRpcError (JsonDecodeError msg) =
126
    "Error while decoding JSON from HTTP response: " ++ msg
127
explainRpcError (RpcResultError msg) =
128
    "Error reponse received from RPC server: " ++ msg
129
explainRpcError OfflineNodeError =
130
    "Node is marked offline"
131

    
132
type ERpcError = Either RpcError
133

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

    
145
-- | Generic class that ensures matching RPC call with its respective
146
-- result.
147
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
148
  -- | Create a result based on the received HTTP response.
149
  rpcResultFill :: a -> J.JSValue -> ERpcError b
150

    
151
-- | Http Request definition.
152
data HttpClientRequest = HttpClientRequest
153
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
154
  , requestData :: String       -- ^ The arguments for the call
155
  , requestOpts :: [CurlOption] -- ^ The various curl options
156
  }
157

    
158
-- | Prepare url for the HTTP request.
159
prepareUrl :: (RpcCall a) => Node -> a -> String
160
prepareUrl node call =
161
  let node_ip = nodePrimaryIp node
162
      port = C.defaultNodedPort
163
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
164
  in path_prefix ++ "/" ++ rpcCallName call
165

    
166
-- | Create HTTP request for a given node provided it is online,
167
-- otherwise create empty response.
168
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
169
                   -> ERpcError HttpClientRequest
170
prepareHttpRequest opts node call
171
  | rpcCallAcceptOffline call || not (nodeOffline node) =
172
      Right HttpClientRequest { requestUrl  = prepareUrl node call
173
                              , requestData = rpcCallData node call
174
                              , requestOpts = opts ++ curlOpts
175
                              }
176
  | otherwise = Left OfflineNodeError
177

    
178
-- | Parse an HTTP reply.
179
parseHttpReply :: (Rpc a b) =>
180
                  a -> ERpcError (CurlCode, String) -> ERpcError b
181
parseHttpReply _ (Left e) = Left e
182
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
183
parseHttpReply _ (Right (code, err)) =
184
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
185

    
186
-- | Parse a result based on the received HTTP response.
187
parseHttpResponse :: (Rpc a b) => a -> String -> ERpcError b
188
parseHttpResponse call res =
189
  case J.decode res of
190
    J.Error val -> Left $ JsonDecodeError val
191
    J.Ok (True, res'') -> rpcResultFill call res''
192
    J.Ok (False, jerr) -> case jerr of
193
       J.JSString msg -> Left $ RpcResultError (J.fromJSString msg)
194
       _ -> Left . JsonDecodeError $ show (pp_value jerr)
195

    
196
-- | Scan the list of results produced by executeRpcCall and log all the RPC
197
-- errors.
198
logRpcErrors :: [(a, ERpcError b)] -> IO ()
199
logRpcErrors allElems =
200
  let logOneRpcErr (_, Right _) = return ()
201
      logOneRpcErr (_, Left err) =
202
        logError $ "Error in the RPC HTTP reply: " ++ show err
203
  in mapM_ logOneRpcErr allElems
204

    
205
-- | Get options for RPC call
206
getOptionsForCall :: (Rpc a b) => FilePath -> a -> [CurlOption]
207
getOptionsForCall certPath call =
208
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
209
  , CurlSSLCert certPath
210
  , CurlSSLKey certPath
211
  , CurlCAInfo certPath
212
  ]
213

    
214
-- | Execute multiple RPC calls in parallel
215
executeRpcCalls :: (Rpc a b) => [(Node, a)] -> IO [(Node, ERpcError b)]
216
executeRpcCalls nodeCalls = do
217
  cert_file <- P.nodedCertFile
218
  let (nodes, calls) = unzip nodeCalls
219
      opts = map (getOptionsForCall cert_file) calls
220
      opts_urls = zipWith3 (\n c o ->
221
                         case prepareHttpRequest o n c of
222
                           Left v -> Left v
223
                           Right request ->
224
                             Right (CurlPostFields [requestData request]:
225
                                    requestOpts request,
226
                                    requestUrl request)
227
                    ) nodes calls opts
228
  -- split the opts_urls list; we don't want to pass the
229
  -- failed-already nodes to Curl
230
  let (lefts, rights, trail) = splitEithers opts_urls
231
  results <- execMultiCall rights
232
  results' <- case recombineEithers lefts results trail of
233
                Bad msg -> error msg
234
                Ok r -> return r
235
  -- now parse the replies
236
  let results'' = zipWith parseHttpReply calls results'
237
      pairedList = zip nodes results''
238
  logRpcErrors pairedList
239
  return pairedList
240

    
241
-- | Execute an RPC call for many nodes in parallel.
242
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
243
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
244

    
245
-- | Helper function that is used to read dictionaries of values.
246
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
247
sanitizeDictResults =
248
  foldr sanitize1 (Right [])
249
  where
250
    sanitize1 _ (Left e) = Left e
251
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
252
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
253

    
254
-- | Helper function to tranform JSON Result to Either RpcError b.
255
-- Note: For now we really only use it for b s.t. Rpc c b for some c
256
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
257
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
258
fromJResultToRes (J.Ok v) f = Right $ f v
259

    
260
-- | Helper function transforming JSValue to Rpc result type.
261
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
262
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
263

    
264
-- * RPC calls and results
265

    
266
-- ** Instance info
267

    
268
-- | Returns information about a single instance
269
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
270
  [ simpleField "instance" [t| String |]
271
  , simpleField "hname" [t| Hypervisor |]
272
  ])
273

    
274
$(declareILADT "InstanceState"
275
  [ ("InstanceStateRunning", 0)
276
  , ("InstanceStateShutdown", 1)
277
  ])
278

    
279
$(makeJSONInstance ''InstanceState)
280

    
281
instance PyValue InstanceState where
282
  showValue = show . instanceStateToRaw
283

    
284
$(buildObject "InstanceInfo" "instInfo"
285
  [ simpleField "memory" [t| Int|]
286
  , simpleField "state"  [t| InstanceState |]
287
  , simpleField "vcpus"  [t| Int |]
288
  , simpleField "time"   [t| Int |]
289
  ])
290

    
291
-- This is optional here because the result may be empty if instance is
292
-- not on a node - and this is not considered an error.
293
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
294
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
295

    
296
instance RpcCall RpcCallInstanceInfo where
297
  rpcCallName _          = "instance_info"
298
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
299
  rpcCallAcceptOffline _ = False
300
  rpcCallData _ call     = J.encode
301
    ( rpcCallInstInfoInstance call
302
    , rpcCallInstInfoHname call
303
    )
304

    
305
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
306
  rpcResultFill _ res =
307
    case res of
308
      J.JSObject res' ->
309
        case J.fromJSObject res' of
310
          [] -> Right $ RpcResultInstanceInfo Nothing
311
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
312
      _ -> Left $ JsonDecodeError
313
           ("Expected JSObject, got " ++ show (pp_value res))
314

    
315
-- ** AllInstancesInfo
316

    
317
-- | Returns information about all running instances on the given nodes
318
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
319
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
320

    
321
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
322
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
323

    
324
instance RpcCall RpcCallAllInstancesInfo where
325
  rpcCallName _          = "all_instances_info"
326
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
327
  rpcCallAcceptOffline _ = False
328
  rpcCallData _ call     = J.encode (
329
    map fst $ rpcCallAllInstInfoHypervisors call,
330
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
331

    
332
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
333
  -- FIXME: Is there a simpler way to do it?
334
  rpcResultFill _ res =
335
    case res of
336
      J.JSObject res' ->
337
        let res'' = map (second J.readJSON) (J.fromJSObject res')
338
                        :: [(String, J.Result InstanceInfo)] in
339
        case sanitizeDictResults res'' of
340
          Left err -> Left err
341
          Right insts -> Right $ RpcResultAllInstancesInfo insts
342
      _ -> Left $ JsonDecodeError
343
           ("Expected JSObject, got " ++ show (pp_value res))
344

    
345
-- ** InstanceConsoleInfo
346

    
347
-- | Returns information about how to access instances on the given node
348
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
349
  [ simpleField "instance"    [t| Instance |]
350
  , simpleField "node"        [t| Node |]
351
  , simpleField "group"       [t| NodeGroup |]
352
  , simpleField "hvParams"    [t| HvParams |]
353
  , simpleField "beParams"    [t| FilledBeParams |]
354
  ])
355

    
356
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
357
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
358

    
359
$(buildObject "InstanceConsoleInfo" "instConsInfo"
360
  [ simpleField "instance"    [t| String |]
361
  , simpleField "kind"        [t| String |]
362
  , optionalField $
363
    simpleField "message"     [t| String |]
364
  , optionalField $
365
    simpleField "host"        [t| String |]
366
  , optionalField $
367
    simpleField "port"        [t| Int |]
368
  , optionalField $
369
    simpleField "user"        [t| String |]
370
  , optionalField $
371
    simpleField "command"     [t| [String] |]
372
  , optionalField $
373
    simpleField "display"     [t| String |]
374
  ])
375

    
376
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
377
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
378

    
379
instance RpcCall RpcCallInstanceConsoleInfo where
380
  rpcCallName _          = "instance_console_info"
381
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
382
  rpcCallAcceptOffline _ = False
383
  rpcCallData _ call     = J.encode .
384
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
385

    
386
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
387
  rpcResultFill _ res =
388
    case res of
389
      J.JSObject res' ->
390
        let res'' = map (second J.readJSON) (J.fromJSObject res')
391
                        :: [(String, J.Result InstanceConsoleInfo)] in
392
        case sanitizeDictResults res'' of
393
          Left err -> Left err
394
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
395
      _ -> Left $ JsonDecodeError
396
           ("Expected JSObject, got " ++ show (pp_value res))
397

    
398
-- ** InstanceList
399

    
400
-- | Returns the list of running instances on the given nodes
401
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
402
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
403

    
404
$(buildObject "RpcResultInstanceList" "rpcResInstList"
405
  [ simpleField "instances" [t| [String] |] ])
406

    
407
instance RpcCall RpcCallInstanceList where
408
  rpcCallName _          = "instance_list"
409
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
410
  rpcCallAcceptOffline _ = False
411
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
412

    
413
instance Rpc RpcCallInstanceList RpcResultInstanceList where
414
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
415

    
416
-- ** NodeInfo
417

    
418
-- | Returns node information
419
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
420
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
421
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
422
  ])
423

    
424
$(buildObject "StorageInfo" "storageInfo"
425
  [ simpleField "name" [t| String |]
426
  , simpleField "type" [t| String |]
427
  , optionalField $ simpleField "storage_free" [t| Int |]
428
  , optionalField $ simpleField "storage_size" [t| Int |]
429
  ])
430

    
431
-- | We only provide common fields as described in hv_base.py.
432
$(buildObject "HvInfo" "hvInfo"
433
  [ simpleField "memory_total" [t| Int |]
434
  , simpleField "memory_free" [t| Int |]
435
  , simpleField "memory_dom0" [t| Int |]
436
  , simpleField "cpu_total" [t| Int |]
437
  , simpleField "cpu_nodes" [t| Int |]
438
  , simpleField "cpu_sockets" [t| Int |]
439
  , simpleField "cpu_dom0" [t| Int |]
440
  ])
441

    
442
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
443
  [ simpleField "boot_id" [t| String |]
444
  , simpleField "storage_info" [t| [StorageInfo] |]
445
  , simpleField "hv_info" [t| [HvInfo] |]
446
  ])
447

    
448
instance RpcCall RpcCallNodeInfo where
449
  rpcCallName _          = "node_info"
450
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
451
  rpcCallAcceptOffline _ = False
452
  rpcCallData n call     = J.encode
453
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
454
                         ++ nodeName n)
455
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
456
    , rpcCallNodeInfoHypervisors call
457
    )
458

    
459
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
460
  rpcResultFill _ res =
461
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
462

    
463
-- ** Version
464

    
465
-- | Query node version.
466
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
467

    
468
-- | Query node reply.
469
$(buildObject "RpcResultVersion" "rpcResultVersion"
470
  [ simpleField "version" [t| Int |]
471
  ])
472

    
473
instance RpcCall RpcCallVersion where
474
  rpcCallName _          = "version"
475
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
476
  rpcCallAcceptOffline _ = True
477
  rpcCallData _          = J.encode
478

    
479
instance Rpc RpcCallVersion RpcResultVersion where
480
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
481

    
482
-- ** StorageList
483

    
484
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
485
  [ simpleField "su_name" [t| StorageType |]
486
  , simpleField "su_args" [t| [String] |]
487
  , simpleField "name"    [t| String |]
488
  , simpleField "fields"  [t| [StorageField] |]
489
  ])
490

    
491
-- FIXME: The resulting JSValues should have types appropriate for their
492
-- StorageField value: Used -> Bool, Name -> String etc
493
$(buildObject "RpcResultStorageList" "rpcResStorageList"
494
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
495

    
496
instance RpcCall RpcCallStorageList where
497
  rpcCallName _          = "storage_list"
498
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
499
  rpcCallAcceptOffline _ = False
500
  rpcCallData _ call     = J.encode
501
    ( rpcCallStorageListSuName call
502
    , rpcCallStorageListSuArgs call
503
    , rpcCallStorageListName call
504
    , rpcCallStorageListFields call
505
    )
506

    
507
instance Rpc RpcCallStorageList RpcResultStorageList where
508
  rpcResultFill call res =
509
    let sfields = rpcCallStorageListFields call in
510
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
511

    
512
-- ** TestDelay
513

    
514
-- | Call definition for test delay.
515
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
516
  [ simpleField "duration" [t| Double |]
517
  ])
518

    
519
-- | Result definition for test delay.
520
data RpcResultTestDelay = RpcResultTestDelay
521
                          deriving Show
522

    
523
-- | Custom JSON instance for null result.
524
instance J.JSON RpcResultTestDelay where
525
  showJSON _        = J.JSNull
526
  readJSON J.JSNull = return RpcResultTestDelay
527
  readJSON _        = fail "Unable to read RpcResultTestDelay"
528

    
529
instance RpcCall RpcCallTestDelay where
530
  rpcCallName _          = "test_delay"
531
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
532
  rpcCallAcceptOffline _ = False
533
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
534

    
535
instance Rpc RpcCallTestDelay RpcResultTestDelay where
536
  rpcResultFill _ res = fromJSValueToRes res id
537

    
538
-- ** ExportList
539

    
540
-- | Call definition for export list.
541

    
542
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
543

    
544
-- | Result definition for export list.
545
$(buildObject "RpcResultExportList" "rpcResExportList"
546
  [ simpleField "exports" [t| [String] |]
547
  ])
548

    
549
instance RpcCall RpcCallExportList where
550
  rpcCallName _          = "export_list"
551
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
552
  rpcCallAcceptOffline _ = False
553
  rpcCallData _          = J.encode
554

    
555
instance Rpc RpcCallExportList RpcResultExportList where
556
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
557

    
558
-- ** Job Queue Replication
559
  
560
-- | Update a job queue file
561
  
562
$(buildObject "RpcCallJobqueueUpdate" "rpcCallJobqueueUpdate"
563
  [ simpleField "file_name" [t| String |]
564
  , simpleField "content" [t| String |]
565
  ])
566

    
567
instance RpcCall RpcCallJobqueueUpdate where
568
  rpcCallName _          = "jobqueue_update"
569
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
570
  rpcCallAcceptOffline _ = False
571
  rpcCallData _ call     = J.encode
572
    ( rpcCallJobqueueUpdateFileName call
573
    , ( C.rpcEncodingNone
574
      , rpcCallJobqueueUpdateContent call
575
      )
576
    )
577

    
578
instance Rpc RpcCallJobqueueUpdate () where
579
  rpcResultFill _ res =
580
    case res of
581
      J.JSNull ->  Right ()
582
      _ -> Left $ JsonDecodeError
583
           ("Expected JSNull, got " ++ show (pp_value res))
584