Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 8e527d04

History | View | Annotate | Download (22.4 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
  , rpcErrors
38
  , logRpcErrors
39

    
40
  , rpcCallName
41
  , rpcCallTimeout
42
  , rpcCallData
43
  , rpcCallAcceptOffline
44

    
45
  , rpcResultFill
46

    
47
  , RpcCallInstanceInfo(..)
48
  , InstanceState(..)
49
  , InstanceInfo(..)
50
  , RpcResultInstanceInfo(..)
51

    
52
  , RpcCallAllInstancesInfo(..)
53
  , RpcResultAllInstancesInfo(..)
54

    
55
  , InstanceConsoleInfoParams(..)
56
  , InstanceConsoleInfo(..)
57
  , RpcCallInstanceConsoleInfo(..)
58
  , RpcResultInstanceConsoleInfo(..)
59

    
60
  , RpcCallInstanceList(..)
61
  , RpcResultInstanceList(..)
62

    
63
  , HvInfo(..)
64
  , StorageInfo(..)
65
  , RpcCallNodeInfo(..)
66
  , RpcResultNodeInfo(..)
67

    
68
  , RpcCallVersion(..)
69
  , RpcResultVersion(..)
70

    
71
  , RpcCallStorageList(..)
72
  , RpcResultStorageList(..)
73

    
74
  , RpcCallTestDelay(..)
75
  , RpcResultTestDelay(..)
76

    
77
  , RpcCallExportList(..)
78
  , RpcResultExportList(..)
79

    
80
  , RpcCallJobqueueUpdate(..)
81
  , RpcCallJobqueueRename(..)
82
  , RpcCallSetWatcherPause(..)
83
  , RpcCallSetDrainFlag(..)
84
  ) where
85

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

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

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

    
110
-- * Base RPC functionality and types
111

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

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

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

    
141
type ERpcError = Either RpcError
142

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

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

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

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

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

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

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

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

    
213
-- | Scan the list of results produced by executeRpcCall and extract
214
-- all the RPC errors.
215
rpcErrors :: [(a, ERpcError b)] -> [(a, RpcError)]
216
rpcErrors =
217
  let rpcErr (node, Left err) = Just (node, err)
218
      rpcErr _                = Nothing
219
  in mapMaybe rpcErr
220

    
221
-- | Scan the list of results produced by executeRpcCall and log all the RPC
222
-- errors. Returns the list of errors for further processing.
223
logRpcErrors :: (MonadLog m, Show a) => [(a, ERpcError b)]
224
                                     -> m [(a, RpcError)]
225
logRpcErrors rs =
226
  let logOneRpcErr (node, err) =
227
        logError $ "Error in the RPC HTTP reply from '" ++
228
                   show node ++ "': " ++ show err
229
      errs = rpcErrors rs
230
  in mapM_ logOneRpcErr errs >> return errs
231

    
232
-- | Get options for RPC call
233
getOptionsForCall :: (Rpc a b) => FilePath -> FilePath -> a -> [CurlOption]
234
getOptionsForCall cert_path client_cert_path call =
235
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
236
  , CurlSSLCert client_cert_path
237
  , CurlSSLKey client_cert_path
238
  , CurlCAInfo cert_path
239
  ]
240

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

    
275
-- | Execute an RPC call for many nodes in parallel.
276
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
277
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
278

    
279
-- | Helper function that is used to read dictionaries of values.
280
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
281
sanitizeDictResults =
282
  foldr sanitize1 (Right [])
283
  where
284
    sanitize1 _ (Left e) = Left e
285
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
286
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
287

    
288
-- | Helper function to tranform JSON Result to Either RpcError b.
289
-- Note: For now we really only use it for b s.t. Rpc c b for some c
290
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
291
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
292
fromJResultToRes (J.Ok v) f = Right $ f v
293

    
294
-- | Helper function transforming JSValue to Rpc result type.
295
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
296
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
297

    
298
-- * RPC calls and results
299

    
300
-- ** Instance info
301

    
302
-- | Returns information about a single instance
303
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
304
  [ simpleField "instance" [t| String |]
305
  , simpleField "hname" [t| Hypervisor |]
306
  ])
307

    
308
$(declareILADT "InstanceState"
309
  [ ("InstanceStateRunning", 0)
310
  , ("InstanceStateShutdown", 1)
311
  ])
312

    
313
$(makeJSONInstance ''InstanceState)
314

    
315
instance PyValue InstanceState where
316
  showValue = show . instanceStateToRaw
317

    
318
$(buildObject "InstanceInfo" "instInfo"
319
  [ simpleField "memory" [t| Int|]
320
  , simpleField "state"  [t| InstanceState |]
321
  , simpleField "vcpus"  [t| Int |]
322
  , simpleField "time"   [t| Int |]
323
  ])
324

    
325
-- This is optional here because the result may be empty if instance is
326
-- not on a node - and this is not considered an error.
327
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
328
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
329

    
330
instance RpcCall RpcCallInstanceInfo where
331
  rpcCallName _          = "instance_info"
332
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
333
  rpcCallAcceptOffline _ = False
334

    
335
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
336
  rpcResultFill _ res =
337
    case res of
338
      J.JSObject res' ->
339
        case J.fromJSObject res' of
340
          [] -> Right $ RpcResultInstanceInfo Nothing
341
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
342
      _ -> Left $ JsonDecodeError
343
           ("Expected JSObject, got " ++ show (pp_value res))
344

    
345
-- ** AllInstancesInfo
346

    
347
-- | Returns information about all running instances on the given nodes
348
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
349
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
350

    
351
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
352
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
353

    
354
instance RpcCall RpcCallAllInstancesInfo where
355
  rpcCallName _          = "all_instances_info"
356
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
357
  rpcCallAcceptOffline _ = False
358
  rpcCallData _ call     = J.encode (
359
    map fst $ rpcCallAllInstInfoHypervisors call,
360
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
361

    
362
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
363
  -- FIXME: Is there a simpler way to do it?
364
  rpcResultFill _ res =
365
    case res of
366
      J.JSObject res' ->
367
        let res'' = map (second J.readJSON) (J.fromJSObject res')
368
                        :: [(String, J.Result InstanceInfo)] in
369
        case sanitizeDictResults res'' of
370
          Left err -> Left err
371
          Right insts -> Right $ RpcResultAllInstancesInfo insts
372
      _ -> Left $ JsonDecodeError
373
           ("Expected JSObject, got " ++ show (pp_value res))
374

    
375
-- ** InstanceConsoleInfo
376

    
377
-- | Returns information about how to access instances on the given node
378
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
379
  [ simpleField "instance"    [t| Instance |]
380
  , simpleField "node"        [t| Node |]
381
  , simpleField "group"       [t| NodeGroup |]
382
  , simpleField "hvParams"    [t| HvParams |]
383
  , simpleField "beParams"    [t| FilledBeParams |]
384
  ])
385

    
386
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
387
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
388

    
389
$(buildObject "InstanceConsoleInfo" "instConsInfo"
390
  [ simpleField "instance"    [t| String |]
391
  , simpleField "kind"        [t| String |]
392
  , optionalField $
393
    simpleField "message"     [t| String |]
394
  , optionalField $
395
    simpleField "host"        [t| String |]
396
  , optionalField $
397
    simpleField "port"        [t| Int |]
398
  , optionalField $
399
    simpleField "user"        [t| String |]
400
  , optionalField $
401
    simpleField "command"     [t| [String] |]
402
  , optionalField $
403
    simpleField "display"     [t| String |]
404
  ])
405

    
406
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
407
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
408

    
409
instance RpcCall RpcCallInstanceConsoleInfo where
410
  rpcCallName _          = "instance_console_info"
411
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
412
  rpcCallAcceptOffline _ = False
413
  rpcCallData _ call     = J.encode .
414
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
415

    
416
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
417
  rpcResultFill _ res =
418
    case res of
419
      J.JSObject res' ->
420
        let res'' = map (second J.readJSON) (J.fromJSObject res')
421
                        :: [(String, J.Result InstanceConsoleInfo)] in
422
        case sanitizeDictResults res'' of
423
          Left err -> Left err
424
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
425
      _ -> Left $ JsonDecodeError
426
           ("Expected JSObject, got " ++ show (pp_value res))
427

    
428
-- ** InstanceList
429

    
430
-- | Returns the list of running instances on the given nodes
431
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
432
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
433

    
434
$(buildObject "RpcResultInstanceList" "rpcResInstList"
435
  [ simpleField "instances" [t| [String] |] ])
436

    
437
instance RpcCall RpcCallInstanceList where
438
  rpcCallName _          = "instance_list"
439
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
440
  rpcCallAcceptOffline _ = False
441

    
442
instance Rpc RpcCallInstanceList RpcResultInstanceList where
443
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
444

    
445
-- ** NodeInfo
446

    
447
-- | Returns node information
448
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
449
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
450
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
451
  ])
452

    
453
$(buildObject "StorageInfo" "storageInfo"
454
  [ simpleField "name" [t| String |]
455
  , simpleField "type" [t| String |]
456
  , optionalField $ simpleField "storage_free" [t| Int |]
457
  , optionalField $ simpleField "storage_size" [t| Int |]
458
  ])
459

    
460
-- | We only provide common fields as described in hv_base.py.
461
$(buildObject "HvInfo" "hvInfo"
462
  [ simpleField "memory_total" [t| Int |]
463
  , simpleField "memory_free" [t| Int |]
464
  , simpleField "memory_dom0" [t| Int |]
465
  , simpleField "cpu_total" [t| Int |]
466
  , simpleField "cpu_nodes" [t| Int |]
467
  , simpleField "cpu_sockets" [t| Int |]
468
  , simpleField "cpu_dom0" [t| Int |]
469
  ])
470

    
471
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
472
  [ simpleField "boot_id" [t| String |]
473
  , simpleField "storage_info" [t| [StorageInfo] |]
474
  , simpleField "hv_info" [t| [HvInfo] |]
475
  ])
476

    
477
instance RpcCall RpcCallNodeInfo where
478
  rpcCallName _          = "node_info"
479
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
480
  rpcCallAcceptOffline _ = False
481
  rpcCallData n call     = J.encode
482
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
483
                         ++ nodeName n)
484
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
485
    , rpcCallNodeInfoHypervisors call
486
    )
487

    
488
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
489
  rpcResultFill _ res =
490
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
491

    
492
-- ** Version
493

    
494
-- | Query node version.
495
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
496

    
497
-- | Query node reply.
498
$(buildObject "RpcResultVersion" "rpcResultVersion"
499
  [ simpleField "version" [t| Int |]
500
  ])
501

    
502
instance RpcCall RpcCallVersion where
503
  rpcCallName _          = "version"
504
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
505
  rpcCallAcceptOffline _ = True
506
  rpcCallData _          = J.encode
507

    
508
instance Rpc RpcCallVersion RpcResultVersion where
509
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
510

    
511
-- ** StorageList
512

    
513
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
514
  [ simpleField "su_name" [t| StorageType |]
515
  , simpleField "su_args" [t| [String] |]
516
  , simpleField "name"    [t| String |]
517
  , simpleField "fields"  [t| [StorageField] |]
518
  ])
519

    
520
-- FIXME: The resulting JSValues should have types appropriate for their
521
-- StorageField value: Used -> Bool, Name -> String etc
522
$(buildObject "RpcResultStorageList" "rpcResStorageList"
523
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
524

    
525
instance RpcCall RpcCallStorageList where
526
  rpcCallName _          = "storage_list"
527
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
528
  rpcCallAcceptOffline _ = False
529

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

    
535
-- ** TestDelay
536

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

    
542
-- | Result definition for test delay.
543
data RpcResultTestDelay = RpcResultTestDelay
544
                          deriving Show
545

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

    
552
instance RpcCall RpcCallTestDelay where
553
  rpcCallName _          = "test_delay"
554
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
555
  rpcCallAcceptOffline _ = False
556

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

    
560
-- ** ExportList
561

    
562
-- | Call definition for export list.
563

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

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

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

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

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

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

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

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

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

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

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

    
618
instance RpcCall RpcCallJobqueueRename where
619
  rpcCallName _          = "jobqueue_rename"
620
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
621
  rpcCallAcceptOffline _ = False
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

    
648
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
649

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

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

    
665
instance RpcCall RpcCallSetDrainFlag where
666
  rpcCallName _          = "jobqueue_set_drain_flag"
667
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
668
  rpcCallAcceptOffline _ = False
669

    
670
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
671

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