Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ b3cc1646

History | View | Annotate | Download (20.8 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
  , RpcCallSetWatcherPause(..)
81
  ) where
82

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

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

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

    
106
-- * Base RPC functionality and types
107

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

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

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

    
137
type ERpcError = Either RpcError
138

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

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

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

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

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

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

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

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

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

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

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

    
260
-- | Execute an RPC call for many nodes in parallel.
261
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
262
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
263

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

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

    
279
-- | Helper function transforming JSValue to Rpc result type.
280
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
281
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
282

    
283
-- * RPC calls and results
284

    
285
-- ** Instance info
286

    
287
-- | Returns information about a single instance
288
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
289
  [ simpleField "instance" [t| String |]
290
  , simpleField "hname" [t| Hypervisor |]
291
  ])
292

    
293
$(declareILADT "InstanceState"
294
  [ ("InstanceStateRunning", 0)
295
  , ("InstanceStateShutdown", 1)
296
  ])
297

    
298
$(makeJSONInstance ''InstanceState)
299

    
300
instance PyValue InstanceState where
301
  showValue = show . instanceStateToRaw
302

    
303
$(buildObject "InstanceInfo" "instInfo"
304
  [ simpleField "memory" [t| Int|]
305
  , simpleField "state"  [t| InstanceState |]
306
  , simpleField "vcpus"  [t| Int |]
307
  , simpleField "time"   [t| Int |]
308
  ])
309

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

    
315
instance RpcCall RpcCallInstanceInfo where
316
  rpcCallName _          = "instance_info"
317
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
318
  rpcCallAcceptOffline _ = False
319
  rpcCallData _ call     = J.encode
320
    ( rpcCallInstInfoInstance call
321
    , rpcCallInstInfoHname call
322
    )
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
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
431

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

    
435
-- ** NodeInfo
436

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

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

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

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

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

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

    
482
-- ** Version
483

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

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

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

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

    
501
-- ** StorageList
502

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

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

    
515
instance RpcCall RpcCallStorageList where
516
  rpcCallName _          = "storage_list"
517
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
518
  rpcCallAcceptOffline _ = False
519
  rpcCallData _ call     = J.encode
520
    ( rpcCallStorageListSuName call
521
    , rpcCallStorageListSuArgs call
522
    , rpcCallStorageListName call
523
    , rpcCallStorageListFields call
524
    )
525

    
526
instance Rpc RpcCallStorageList RpcResultStorageList where
527
  rpcResultFill call res =
528
    let sfields = rpcCallStorageListFields call in
529
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
530

    
531
-- ** TestDelay
532

    
533
-- | Call definition for test delay.
534
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
535
  [ simpleField "duration" [t| Double |]
536
  ])
537

    
538
-- | Result definition for test delay.
539
data RpcResultTestDelay = RpcResultTestDelay
540
                          deriving Show
541

    
542
-- | Custom JSON instance for null result.
543
instance J.JSON RpcResultTestDelay where
544
  showJSON _        = J.JSNull
545
  readJSON J.JSNull = return RpcResultTestDelay
546
  readJSON _        = fail "Unable to read RpcResultTestDelay"
547

    
548
instance RpcCall RpcCallTestDelay where
549
  rpcCallName _          = "test_delay"
550
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
551
  rpcCallAcceptOffline _ = False
552
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
553

    
554
instance Rpc RpcCallTestDelay RpcResultTestDelay where
555
  rpcResultFill _ res = fromJSValueToRes res id
556

    
557
-- ** ExportList
558

    
559
-- | Call definition for export list.
560

    
561
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
562

    
563
-- | Result definition for export list.
564
$(buildObject "RpcResultExportList" "rpcResExportList"
565
  [ simpleField "exports" [t| [String] |]
566
  ])
567

    
568
instance RpcCall RpcCallExportList where
569
  rpcCallName _          = "export_list"
570
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
571
  rpcCallAcceptOffline _ = False
572
  rpcCallData _          = J.encode
573

    
574
instance Rpc RpcCallExportList RpcResultExportList where
575
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
576

    
577
-- ** Job Queue Replication
578
  
579
-- | Update a job queue file
580
  
581
$(buildObject "RpcCallJobqueueUpdate" "rpcCallJobqueueUpdate"
582
  [ simpleField "file_name" [t| String |]
583
  , simpleField "content" [t| String |]
584
  ])
585

    
586
$(buildObject "RpcResultJobQueueUpdate" "rpcResultJobQueueUpdate" [])
587

    
588
instance RpcCall RpcCallJobqueueUpdate where
589
  rpcCallName _          = "jobqueue_update"
590
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
591
  rpcCallAcceptOffline _ = False
592
  rpcCallData _ call     = J.encode
593
    ( rpcCallJobqueueUpdateFileName call
594
    , ( C.rpcEncodingZlibBase64
595
      , BL.unpack . Base64.encode . Zlib.compress . BL.pack
596
          $ rpcCallJobqueueUpdateContent call
597
      )
598
    )
599

    
600
instance Rpc RpcCallJobqueueUpdate RpcResultJobQueueUpdate where
601
  rpcResultFill _ res =
602
    case res of
603
      J.JSNull ->  Right RpcResultJobQueueUpdate
604
      _ -> Left $ JsonDecodeError
605
           ("Expected JSNull, got " ++ show (pp_value res))
606

    
607
-- ** Watcher Status Update
608
      
609
-- | Set the watcher status
610
      
611
$(buildObject "RpcCallSetWatcherPause" "rpcCallSetWatcherPause"
612
  [ simpleField "time" [t| Maybe Double |]
613
  ])
614

    
615
instance RpcCall RpcCallSetWatcherPause where
616
  rpcCallName _          = "set_watcher_pause"
617
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
618
  rpcCallAcceptOffline _ = False
619
  rpcCallData _ call     = J.encode
620
    [ maybe J.JSNull J.showJSON $ rpcCallSetWatcherPauseTime call ]
621

    
622
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
623

    
624
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
625
  rpcResultFill _ res =
626
    case res of
627
      J.JSNull ->  Right RpcResultSetWatcherPause
628
      _ -> Left $ JsonDecodeError
629
           ("Expected JSNull, got " ++ show (pp_value res))
630