Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 13d26b66

History | View | Annotate | Download (22.6 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.Types
105
import Ganeti.Curl.Multi
106
import Ganeti.Utils
107

    
108
-- * Base RPC functionality and types
109

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

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

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

    
139
type ERpcError = Either RpcError
140

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
285
-- * RPC calls and results
286

    
287
-- ** Instance info
288

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

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

    
300
$(makeJSONInstance ''InstanceState)
301

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

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

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

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

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

    
336
-- ** AllInstancesInfo
337

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

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

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

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

    
366
-- ** InstanceConsoleInfo
367

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

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

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

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

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

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

    
419
-- ** InstanceList
420

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

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

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

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

    
437
-- ** NodeInfo
438

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

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

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

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

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

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

    
484
-- ** Version
485

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

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

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

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

    
503
-- ** StorageList
504

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

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

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

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

    
533
-- ** TestDelay
534

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

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

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

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

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

    
559
-- ** ExportList
560

    
561
-- | Call definition for export list.
562

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

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

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

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

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

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

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

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

    
609
-- | Rename a file in the job queue
610

    
611
$(buildObject "RpcCallJobqueueRename" "rpcCallJobqueueRename"
612
  [ simpleField "rename" [t| [(String, String)] |]
613
  ])
614

    
615
$(buildObject "RpcResultJobqueueRename" "rpcResultJobqueueRename" [])
616

    
617
instance RpcCall RpcCallJobqueueRename where
618
  rpcCallName _          = "jobqueue_rename"
619
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
620
  rpcCallAcceptOffline _ = False
621
  rpcCallData _ call     = J.encode [ rpcCallJobqueueRenameRename call ]
622

    
623
instance Rpc RpcCallJobqueueRename RpcResultJobqueueRename where
624
  rpcResultFill call res =
625
    -- Upon success, the RPC returns the list of return values of
626
    -- the rename operations, which is always None, serialized to
627
    -- null in JSON.
628
    let expected = J.showJSON . map (const J.JSNull)
629
                     $ rpcCallJobqueueRenameRename call
630
    in if res == expected
631
      then Right RpcResultJobqueueRename
632
      else Left
633
             $ JsonDecodeError ("Expected JSNull, got " ++ show (pp_value res))
634

    
635
-- ** Watcher Status Update
636
      
637
-- | Set the watcher status
638
      
639
$(buildObject "RpcCallSetWatcherPause" "rpcCallSetWatcherPause"
640
  [ optionalField $ timeAsDoubleField "time"
641
  ])
642

    
643
instance RpcCall RpcCallSetWatcherPause where
644
  rpcCallName _          = "set_watcher_pause"
645
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
646
  rpcCallAcceptOffline _ = False
647
  rpcCallData _ call     = J.encode
648
    [ maybe J.JSNull (J.showJSON . TimeAsDoubleJSON) $
649
            rpcCallSetWatcherPauseTime call ]
650

    
651
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
652

    
653
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
654
  rpcResultFill _ res =
655
    case res of
656
      J.JSNull ->  Right RpcResultSetWatcherPause
657
      _ -> Left $ JsonDecodeError
658
           ("Expected JSNull, got " ++ show (pp_value res))
659

    
660
-- ** Queue drain status
661
      
662
-- | Set the queu drain flag
663
      
664
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
665
  [ simpleField "value" [t| Bool |]
666
  ])
667

    
668
instance RpcCall RpcCallSetDrainFlag where
669
  rpcCallName _          = "jobqueue_set_drain_flag"
670
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
671
  rpcCallAcceptOffline _ = False
672
  rpcCallData _ call     = J.encode [ rpcCallSetDrainFlagValue call ]
673

    
674
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
675

    
676
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
677
  rpcResultFill _ res =
678
    case res of
679
      J.JSNull ->  Right RpcResultSetDrainFlag
680
      _ -> Left $ JsonDecodeError
681
           ("Expected JSNull, got " ++ show (pp_value res))
682