Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 83a451f5

History | View | Annotate | Download (21.5 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
  , RpcCallSetDrainFlag(..)
82
  ) where
83

    
84
import Control.Arrow (second)
85
import qualified Codec.Compression.Zlib as Zlib
86
import qualified Data.ByteString.Lazy.Char8 as BL
87
import qualified Data.Map as Map
88
import Data.Maybe (fromMaybe)
89
import qualified Text.JSON as J
90
import Text.JSON.Pretty (pp_value)
91
import qualified Data.ByteString.Base64.Lazy as Base64
92
import System.Directory
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
  client_cert_file_name <- P.nodedClientCertFile
232
  client_file_exists <- doesFileExist client_cert_file_name
233
  -- FIXME: This is needed to ensure upgradability to 2.11
234
  -- Remove in 2.12.
235
  let client_cert_file = if client_file_exists
236
                         then client_cert_file_name
237
                         else cert_file
238
      (nodes, calls) = unzip nodeCalls
239
      opts = map (getOptionsForCall cert_file client_cert_file) calls
240
      opts_urls = zipWith3 (\n c o ->
241
                         case prepareHttpRequest o n c of
242
                           Left v -> Left v
243
                           Right request ->
244
                             Right (CurlPostFields [requestData request]:
245
                                    requestOpts request,
246
                                    requestUrl request)
247
                    ) nodes calls opts
248
  -- split the opts_urls list; we don't want to pass the
249
  -- failed-already nodes to Curl
250
  let (lefts, rights, trail) = splitEithers opts_urls
251
  results <- execMultiCall rights
252
  results' <- case recombineEithers lefts results trail of
253
                Bad msg -> error msg
254
                Ok r -> return r
255
  -- now parse the replies
256
  let results'' = zipWith parseHttpReply calls results'
257
      pairedList = zip nodes results''
258
  logRpcErrors pairedList
259
  return pairedList
260

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

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

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

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

    
284
-- * RPC calls and results
285

    
286
-- ** Instance info
287

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

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

    
299
$(makeJSONInstance ''InstanceState)
300

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

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

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

    
316
instance RpcCall RpcCallInstanceInfo where
317
  rpcCallName _          = "instance_info"
318
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
319
  rpcCallAcceptOffline _ = False
320
  rpcCallData _ call     = J.encode
321
    ( rpcCallInstInfoInstance call
322
    , rpcCallInstInfoHname call
323
    )
324

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

    
335
-- ** AllInstancesInfo
336

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

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

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

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

    
365
-- ** InstanceConsoleInfo
366

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

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

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

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

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

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

    
418
-- ** InstanceList
419

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

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

    
427
instance RpcCall RpcCallInstanceList where
428
  rpcCallName _          = "instance_list"
429
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
430
  rpcCallAcceptOffline _ = False
431
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
432

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

    
436
-- ** NodeInfo
437

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

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

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

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

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

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

    
483
-- ** Version
484

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

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

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

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

    
502
-- ** StorageList
503

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

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

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

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

    
532
-- ** TestDelay
533

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

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

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

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

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

    
558
-- ** ExportList
559

    
560
-- | Call definition for export list.
561

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

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

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

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

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

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

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

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

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

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

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

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

    
632
-- ** Queue drain status
633
      
634
-- | Set the queu drain flag
635
      
636
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
637
  [ simpleField "value" [t| Bool |]
638
  ])
639

    
640
instance RpcCall RpcCallSetDrainFlag where
641
  rpcCallName _          = "jobqueue_set_drain_flag"
642
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
643
  rpcCallAcceptOffline _ = False
644
  rpcCallData _ call     = J.encode [ rpcCallSetDrainFlagValue call ]
645

    
646
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
647

    
648
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
649
  rpcResultFill _ res =
650
    case res of
651
      J.JSNull ->  Right RpcResultSetDrainFlag
652
      _ -> Left $ JsonDecodeError
653
           ("Expected JSNull, got " ++ show (pp_value res))
654