Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ d6f05205

History | View | Annotate | Download (23.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
  , Compressed
48
  , packCompressed
49
  , toCompressed
50
  , getCompressed
51

    
52
  , RpcCallInstanceInfo(..)
53
  , InstanceState(..)
54
  , InstanceInfo(..)
55
  , RpcResultInstanceInfo(..)
56

    
57
  , RpcCallAllInstancesInfo(..)
58
  , RpcResultAllInstancesInfo(..)
59

    
60
  , InstanceConsoleInfoParams(..)
61
  , InstanceConsoleInfo(..)
62
  , RpcCallInstanceConsoleInfo(..)
63
  , RpcResultInstanceConsoleInfo(..)
64

    
65
  , RpcCallInstanceList(..)
66
  , RpcResultInstanceList(..)
67

    
68
  , HvInfo(..)
69
  , StorageInfo(..)
70
  , RpcCallNodeInfo(..)
71
  , RpcResultNodeInfo(..)
72

    
73
  , RpcCallVersion(..)
74
  , RpcResultVersion(..)
75

    
76
  , RpcCallStorageList(..)
77
  , RpcResultStorageList(..)
78

    
79
  , RpcCallTestDelay(..)
80
  , RpcResultTestDelay(..)
81

    
82
  , RpcCallExportList(..)
83
  , RpcResultExportList(..)
84

    
85
  , RpcCallJobqueueUpdate(..)
86
  , RpcCallJobqueueRename(..)
87
  , RpcCallSetWatcherPause(..)
88
  , RpcCallSetDrainFlag(..)
89
  ) where
90

    
91
import Control.Arrow (second)
92
import Control.Monad
93
import qualified Data.ByteString.Lazy.Char8 as BL
94
import qualified Data.Map as Map
95
import Data.Maybe (fromMaybe, mapMaybe)
96
import qualified Text.JSON as J
97
import Text.JSON.Pretty (pp_value)
98
import qualified Data.ByteString.Base64.Lazy as Base64
99
import System.Directory
100

    
101
import Network.Curl hiding (content)
102
import qualified Ganeti.Path as P
103

    
104
import Ganeti.BasicTypes
105
import qualified Ganeti.Constants as C
106
import Ganeti.Codec
107
import Ganeti.Curl.Multi
108
import Ganeti.JSON
109
import Ganeti.Logging
110
import Ganeti.Objects
111
import Ganeti.THH
112
import Ganeti.THH.Field
113
import Ganeti.Types
114
import Ganeti.Utils
115

    
116
-- * Base RPC functionality and types
117

    
118
-- | The curl options used for RPC.
119
curlOpts :: [CurlOption]
120
curlOpts = [ CurlFollowLocation False
121
           , CurlSSLVerifyHost 0
122
           , CurlSSLVerifyPeer True
123
           , CurlSSLCertType "PEM"
124
           , CurlSSLKeyType "PEM"
125
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
126
           ]
127

    
128
-- | Data type for RPC error reporting.
129
data RpcError
130
  = CurlLayerError String
131
  | JsonDecodeError String
132
  | RpcResultError String
133
  | OfflineNodeError
134
  deriving (Show, Eq)
135

    
136
-- | Provide explanation to RPC errors.
137
explainRpcError :: RpcError -> String
138
explainRpcError (CurlLayerError code) =
139
    "Curl error:" ++ code
140
explainRpcError (JsonDecodeError msg) =
141
    "Error while decoding JSON from HTTP response: " ++ msg
142
explainRpcError (RpcResultError msg) =
143
    "Error reponse received from RPC server: " ++ msg
144
explainRpcError OfflineNodeError =
145
    "Node is marked offline"
146

    
147
type ERpcError = Either RpcError
148

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

    
161
-- | Generic class that ensures matching RPC call with its respective
162
-- result.
163
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
164
  -- | Create a result based on the received HTTP response.
165
  rpcResultFill :: a -> J.JSValue -> ERpcError b
166

    
167
-- | Http Request definition.
168
data HttpClientRequest = HttpClientRequest
169
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
170
  , requestData :: String       -- ^ The arguments for the call
171
  , requestOpts :: [CurlOption] -- ^ The various curl options
172
  }
173

    
174
-- | Check if a string represented address is IPv6
175
isIpV6 :: String -> Bool
176
isIpV6 = (':' `elem`)
177

    
178
-- | Prepare url for the HTTP request.
179
prepareUrl :: (RpcCall a) => Node -> a -> String
180
prepareUrl node call =
181
  let node_ip = nodePrimaryIp node
182
      node_address = if isIpV6 node_ip
183
                     then "[" ++ node_ip ++ "]"
184
                     else node_ip
185
      port = C.defaultNodedPort
186
      path_prefix = "https://" ++ node_address ++ ":" ++ show port
187
  in path_prefix ++ "/" ++ rpcCallName call
188

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

    
201
-- | Parse an HTTP reply.
202
parseHttpReply :: (Rpc a b) =>
203
                  a -> ERpcError (CurlCode, String) -> ERpcError b
204
parseHttpReply _ (Left e) = Left e
205
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
206
parseHttpReply _ (Right (code, err)) =
207
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
208

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

    
219
-- | Scan the list of results produced by executeRpcCall and extract
220
-- all the RPC errors.
221
rpcErrors :: [(a, ERpcError b)] -> [(a, RpcError)]
222
rpcErrors =
223
  let rpcErr (node, Left err) = Just (node, err)
224
      rpcErr _                = Nothing
225
  in mapMaybe rpcErr
226

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

    
238
-- | Get options for RPC call
239
getOptionsForCall :: (Rpc a b) => FilePath -> FilePath -> a -> [CurlOption]
240
getOptionsForCall cert_path client_cert_path call =
241
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
242
  , CurlSSLCert client_cert_path
243
  , CurlSSLKey client_cert_path
244
  , CurlCAInfo cert_path
245
  ]
246

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

    
281
-- | Execute an RPC call for many nodes in parallel.
282
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
283
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
284

    
285
-- | Helper function that is used to read dictionaries of values.
286
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
287
sanitizeDictResults =
288
  foldr sanitize1 (Right [])
289
  where
290
    sanitize1 _ (Left e) = Left e
291
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
292
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
293

    
294
-- | Helper function to tranform JSON Result to Either RpcError b.
295
-- Note: For now we really only use it for b s.t. Rpc c b for some c
296
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
297
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
298
fromJResultToRes (J.Ok v) f = Right $ f v
299

    
300
-- | Helper function transforming JSValue to Rpc result type.
301
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
302
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
303

    
304
-- | An opaque data type for representing data that should be compressed
305
-- over the wire.
306
--
307
-- On Python side it is decompressed by @backend._Decompress@.
308
newtype Compressed = Compressed { getCompressed :: BL.ByteString }
309
  deriving (Eq, Ord, Show)
310

    
311
-- TODO Add a unit test for all octets
312
instance J.JSON Compressed where
313
  showJSON = J.showJSON
314
             . (,) C.rpcEncodingZlibBase64
315
             . Base64.encode . compressZlib . getCompressed
316
  readJSON = J.readJSON >=> decompress
317
    where
318
      decompress (enc, cont)
319
        | enc == C.rpcEncodingNone =
320
            return $ Compressed cont
321
        | enc == C.rpcEncodingZlibBase64 =
322
            liftM Compressed
323
            . either fail return . decompressZlib
324
            <=< either (fail . ("Base64: " ++)) return . Base64.decode
325
            $ cont
326
        | otherwise =
327
            fail $ "Unknown RPC encoding type: " ++ show enc
328

    
329
packCompressed :: BL.ByteString -> Compressed
330
packCompressed = Compressed
331

    
332
toCompressed :: String -> Compressed
333
toCompressed = packCompressed . BL.pack
334

    
335
-- * RPC calls and results
336

    
337
-- ** Instance info
338

    
339
-- | Returns information about a single instance
340
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
341
  [ simpleField "instance" [t| String |]
342
  , simpleField "hname" [t| Hypervisor |]
343
  ])
344

    
345
$(declareILADT "InstanceState"
346
  [ ("InstanceStateRunning", 0)
347
  , ("InstanceStateShutdown", 1)
348
  ])
349

    
350
$(makeJSONInstance ''InstanceState)
351

    
352
instance PyValue InstanceState where
353
  showValue = show . instanceStateToRaw
354

    
355
$(buildObject "InstanceInfo" "instInfo"
356
  [ simpleField "memory" [t| Int|]
357
  , simpleField "state"  [t| InstanceState |]
358
  , simpleField "vcpus"  [t| Int |]
359
  , simpleField "time"   [t| Int |]
360
  ])
361

    
362
-- This is optional here because the result may be empty if instance is
363
-- not on a node - and this is not considered an error.
364
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
365
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
366

    
367
instance RpcCall RpcCallInstanceInfo where
368
  rpcCallName _          = "instance_info"
369
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
370
  rpcCallAcceptOffline _ = False
371

    
372
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
373
  rpcResultFill _ res =
374
    case res of
375
      J.JSObject res' ->
376
        case J.fromJSObject res' of
377
          [] -> Right $ RpcResultInstanceInfo Nothing
378
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
379
      _ -> Left $ JsonDecodeError
380
           ("Expected JSObject, got " ++ show (pp_value res))
381

    
382
-- ** AllInstancesInfo
383

    
384
-- | Returns information about all running instances on the given nodes
385
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
386
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
387

    
388
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
389
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
390

    
391
instance RpcCall RpcCallAllInstancesInfo where
392
  rpcCallName _          = "all_instances_info"
393
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
394
  rpcCallAcceptOffline _ = False
395
  rpcCallData _ call     = J.encode (
396
    map fst $ rpcCallAllInstInfoHypervisors call,
397
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
398

    
399
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
400
  -- FIXME: Is there a simpler way to do it?
401
  rpcResultFill _ res =
402
    case res of
403
      J.JSObject res' ->
404
        let res'' = map (second J.readJSON) (J.fromJSObject res')
405
                        :: [(String, J.Result InstanceInfo)] in
406
        case sanitizeDictResults res'' of
407
          Left err -> Left err
408
          Right insts -> Right $ RpcResultAllInstancesInfo insts
409
      _ -> Left $ JsonDecodeError
410
           ("Expected JSObject, got " ++ show (pp_value res))
411

    
412
-- ** InstanceConsoleInfo
413

    
414
-- | Returns information about how to access instances on the given node
415
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
416
  [ simpleField "instance"    [t| Instance |]
417
  , simpleField "node"        [t| Node |]
418
  , simpleField "group"       [t| NodeGroup |]
419
  , simpleField "hvParams"    [t| HvParams |]
420
  , simpleField "beParams"    [t| FilledBeParams |]
421
  ])
422

    
423
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
424
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
425

    
426
$(buildObject "InstanceConsoleInfo" "instConsInfo"
427
  [ simpleField "instance"    [t| String |]
428
  , simpleField "kind"        [t| String |]
429
  , optionalField $
430
    simpleField "message"     [t| String |]
431
  , optionalField $
432
    simpleField "host"        [t| String |]
433
  , optionalField $
434
    simpleField "port"        [t| Int |]
435
  , optionalField $
436
    simpleField "user"        [t| String |]
437
  , optionalField $
438
    simpleField "command"     [t| [String] |]
439
  , optionalField $
440
    simpleField "display"     [t| String |]
441
  ])
442

    
443
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
444
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
445

    
446
instance RpcCall RpcCallInstanceConsoleInfo where
447
  rpcCallName _          = "instance_console_info"
448
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
449
  rpcCallAcceptOffline _ = False
450
  rpcCallData _ call     = J.encode .
451
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
452

    
453
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
454
  rpcResultFill _ res =
455
    case res of
456
      J.JSObject res' ->
457
        let res'' = map (second J.readJSON) (J.fromJSObject res')
458
                        :: [(String, J.Result InstanceConsoleInfo)] in
459
        case sanitizeDictResults res'' of
460
          Left err -> Left err
461
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
462
      _ -> Left $ JsonDecodeError
463
           ("Expected JSObject, got " ++ show (pp_value res))
464

    
465
-- ** InstanceList
466

    
467
-- | Returns the list of running instances on the given nodes
468
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
469
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
470

    
471
$(buildObject "RpcResultInstanceList" "rpcResInstList"
472
  [ simpleField "instances" [t| [String] |] ])
473

    
474
instance RpcCall RpcCallInstanceList where
475
  rpcCallName _          = "instance_list"
476
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
477
  rpcCallAcceptOffline _ = False
478

    
479
instance Rpc RpcCallInstanceList RpcResultInstanceList where
480
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
481

    
482
-- ** NodeInfo
483

    
484
-- | Returns node information
485
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
486
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
487
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
488
  ])
489

    
490
$(buildObject "StorageInfo" "storageInfo"
491
  [ simpleField "name" [t| String |]
492
  , simpleField "type" [t| String |]
493
  , optionalField $ simpleField "storage_free" [t| Int |]
494
  , optionalField $ simpleField "storage_size" [t| Int |]
495
  ])
496

    
497
-- | We only provide common fields as described in hv_base.py.
498
$(buildObject "HvInfo" "hvInfo"
499
  [ simpleField "memory_total" [t| Int |]
500
  , simpleField "memory_free" [t| Int |]
501
  , simpleField "memory_dom0" [t| Int |]
502
  , simpleField "cpu_total" [t| Int |]
503
  , simpleField "cpu_nodes" [t| Int |]
504
  , simpleField "cpu_sockets" [t| Int |]
505
  , simpleField "cpu_dom0" [t| Int |]
506
  ])
507

    
508
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
509
  [ simpleField "boot_id" [t| String |]
510
  , simpleField "storage_info" [t| [StorageInfo] |]
511
  , simpleField "hv_info" [t| [HvInfo] |]
512
  ])
513

    
514
instance RpcCall RpcCallNodeInfo where
515
  rpcCallName _          = "node_info"
516
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
517
  rpcCallAcceptOffline _ = False
518
  rpcCallData n call     = J.encode
519
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
520
                         ++ nodeName n)
521
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
522
    , rpcCallNodeInfoHypervisors call
523
    )
524

    
525
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
526
  rpcResultFill _ res =
527
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
528

    
529
-- ** Version
530

    
531
-- | Query node version.
532
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
533

    
534
-- | Query node reply.
535
$(buildObject "RpcResultVersion" "rpcResultVersion"
536
  [ simpleField "version" [t| Int |]
537
  ])
538

    
539
instance RpcCall RpcCallVersion where
540
  rpcCallName _          = "version"
541
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
542
  rpcCallAcceptOffline _ = True
543
  rpcCallData _          = J.encode
544

    
545
instance Rpc RpcCallVersion RpcResultVersion where
546
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
547

    
548
-- ** StorageList
549

    
550
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
551
  [ simpleField "su_name" [t| StorageType |]
552
  , simpleField "su_args" [t| [String] |]
553
  , simpleField "name"    [t| String |]
554
  , simpleField "fields"  [t| [StorageField] |]
555
  ])
556

    
557
-- FIXME: The resulting JSValues should have types appropriate for their
558
-- StorageField value: Used -> Bool, Name -> String etc
559
$(buildObject "RpcResultStorageList" "rpcResStorageList"
560
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
561

    
562
instance RpcCall RpcCallStorageList where
563
  rpcCallName _          = "storage_list"
564
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
565
  rpcCallAcceptOffline _ = False
566

    
567
instance Rpc RpcCallStorageList RpcResultStorageList where
568
  rpcResultFill call res =
569
    let sfields = rpcCallStorageListFields call in
570
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
571

    
572
-- ** TestDelay
573

    
574
-- | Call definition for test delay.
575
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
576
  [ simpleField "duration" [t| Double |]
577
  ])
578

    
579
-- | Result definition for test delay.
580
data RpcResultTestDelay = RpcResultTestDelay
581
                          deriving Show
582

    
583
-- | Custom JSON instance for null result.
584
instance J.JSON RpcResultTestDelay where
585
  showJSON _        = J.JSNull
586
  readJSON J.JSNull = return RpcResultTestDelay
587
  readJSON _        = fail "Unable to read RpcResultTestDelay"
588

    
589
instance RpcCall RpcCallTestDelay where
590
  rpcCallName _          = "test_delay"
591
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
592
  rpcCallAcceptOffline _ = False
593

    
594
instance Rpc RpcCallTestDelay RpcResultTestDelay where
595
  rpcResultFill _ res = fromJSValueToRes res id
596

    
597
-- ** ExportList
598

    
599
-- | Call definition for export list.
600

    
601
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
602

    
603
-- | Result definition for export list.
604
$(buildObject "RpcResultExportList" "rpcResExportList"
605
  [ simpleField "exports" [t| [String] |]
606
  ])
607

    
608
instance RpcCall RpcCallExportList where
609
  rpcCallName _          = "export_list"
610
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
611
  rpcCallAcceptOffline _ = False
612
  rpcCallData _          = J.encode
613

    
614
instance Rpc RpcCallExportList RpcResultExportList where
615
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
616

    
617
-- ** Job Queue Replication
618
  
619
-- | Update a job queue file
620
  
621
$(buildObject "RpcCallJobqueueUpdate" "rpcCallJobqueueUpdate"
622
  [ simpleField "file_name" [t| String |]
623
  , simpleField "content" [t| String |]
624
  ])
625

    
626
$(buildObject "RpcResultJobQueueUpdate" "rpcResultJobQueueUpdate" [])
627

    
628
instance RpcCall RpcCallJobqueueUpdate where
629
  rpcCallName _          = "jobqueue_update"
630
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
631
  rpcCallAcceptOffline _ = False
632
  rpcCallData _ call     = J.encode
633
    ( rpcCallJobqueueUpdateFileName call
634
    , toCompressed $ rpcCallJobqueueUpdateContent call
635
    )
636

    
637
instance Rpc RpcCallJobqueueUpdate RpcResultJobQueueUpdate where
638
  rpcResultFill _ res =
639
    case res of
640
      J.JSNull ->  Right RpcResultJobQueueUpdate
641
      _ -> Left $ JsonDecodeError
642
           ("Expected JSNull, got " ++ show (pp_value res))
643

    
644
-- | Rename a file in the job queue
645

    
646
$(buildObject "RpcCallJobqueueRename" "rpcCallJobqueueRename"
647
  [ simpleField "rename" [t| [(String, String)] |]
648
  ])
649

    
650
$(buildObject "RpcResultJobqueueRename" "rpcResultJobqueueRename" [])
651

    
652
instance RpcCall RpcCallJobqueueRename where
653
  rpcCallName _          = "jobqueue_rename"
654
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
655
  rpcCallAcceptOffline _ = False
656

    
657
instance Rpc RpcCallJobqueueRename RpcResultJobqueueRename where
658
  rpcResultFill call res =
659
    -- Upon success, the RPC returns the list of return values of
660
    -- the rename operations, which is always None, serialized to
661
    -- null in JSON.
662
    let expected = J.showJSON . map (const J.JSNull)
663
                     $ rpcCallJobqueueRenameRename call
664
    in if res == expected
665
      then Right RpcResultJobqueueRename
666
      else Left
667
             $ JsonDecodeError ("Expected JSNull, got " ++ show (pp_value res))
668

    
669
-- ** Watcher Status Update
670
      
671
-- | Set the watcher status
672
      
673
$(buildObject "RpcCallSetWatcherPause" "rpcCallSetWatcherPause"
674
  [ optionalField $ timeAsDoubleField "time"
675
  ])
676

    
677
instance RpcCall RpcCallSetWatcherPause where
678
  rpcCallName _          = "set_watcher_pause"
679
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
680
  rpcCallAcceptOffline _ = False
681

    
682
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
683

    
684
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
685
  rpcResultFill _ res =
686
    case res of
687
      J.JSNull ->  Right RpcResultSetWatcherPause
688
      _ -> Left $ JsonDecodeError
689
           ("Expected JSNull, got " ++ show (pp_value res))
690

    
691
-- ** Queue drain status
692
      
693
-- | Set the queu drain flag
694
      
695
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
696
  [ simpleField "value" [t| Bool |]
697
  ])
698

    
699
instance RpcCall RpcCallSetDrainFlag where
700
  rpcCallName _          = "jobqueue_set_drain_flag"
701
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
702
  rpcCallAcceptOffline _ = False
703

    
704
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
705

    
706
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
707
  rpcResultFill _ res =
708
    case res of
709
      J.JSNull ->  Right RpcResultSetDrainFlag
710
      _ -> Left $ JsonDecodeError
711
           ("Expected JSNull, got " ++ show (pp_value res))
712