Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 9a8952e0

History | View | Annotate | Download (26.1 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

    
90
  , RpcCallUploadFile(..)
91
  , prepareRpcCallUploadFile
92
  , RpcCallWriteSsconfFiles(..)
93
  ) where
94

    
95
import Control.Arrow (second)
96
import Control.Monad
97
import qualified Data.ByteString.Lazy.Char8 as BL
98
import qualified Data.Map as Map
99
import Data.Maybe (fromMaybe, mapMaybe)
100
import qualified Text.JSON as J
101
import Text.JSON.Pretty (pp_value)
102
import qualified Data.ByteString.Base64.Lazy as Base64
103
import System.Directory
104
import System.Posix.Files ( modificationTime, accessTime, fileOwner
105
                          , fileGroup, fileMode, getFileStatus)
106

    
107
import Network.Curl hiding (content)
108
import qualified Ganeti.Path as P
109

    
110
import Ganeti.BasicTypes
111
import qualified Ganeti.Constants as C
112
import Ganeti.Codec
113
import Ganeti.Curl.Multi
114
import Ganeti.Errors
115
import Ganeti.JSON
116
import Ganeti.Logging
117
import Ganeti.Objects
118
import Ganeti.Runtime
119
import Ganeti.Ssconf
120
import Ganeti.THH
121
import Ganeti.THH.Field
122
import Ganeti.Types
123
import Ganeti.Utils
124
import Ganeti.VCluster
125

    
126
-- * Base RPC functionality and types
127

    
128
-- | The curl options used for RPC.
129
curlOpts :: [CurlOption]
130
curlOpts = [ CurlFollowLocation False
131
           , CurlSSLVerifyHost 0
132
           , CurlSSLVerifyPeer True
133
           , CurlSSLCertType "PEM"
134
           , CurlSSLKeyType "PEM"
135
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
136
           ]
137

    
138
-- | Data type for RPC error reporting.
139
data RpcError
140
  = CurlLayerError String
141
  | JsonDecodeError String
142
  | RpcResultError String
143
  | OfflineNodeError
144
  deriving (Show, Eq)
145

    
146
-- | Provide explanation to RPC errors.
147
explainRpcError :: RpcError -> String
148
explainRpcError (CurlLayerError code) =
149
    "Curl error:" ++ code
150
explainRpcError (JsonDecodeError msg) =
151
    "Error while decoding JSON from HTTP response: " ++ msg
152
explainRpcError (RpcResultError msg) =
153
    "Error reponse received from RPC server: " ++ msg
154
explainRpcError OfflineNodeError =
155
    "Node is marked offline"
156

    
157
type ERpcError = Either RpcError
158

    
159
-- | A generic class for RPC calls.
160
class (ArrayObject a) => RpcCall a where
161
  -- | Give the (Python) name of the procedure.
162
  rpcCallName :: a -> String
163
  -- | Calculate the timeout value for the call execution.
164
  rpcCallTimeout :: a -> Int
165
  -- | Prepare arguments of the call to be send as POST.
166
  rpcCallData :: Node -> a -> String
167
  rpcCallData _ = J.encode . J.JSArray . toJSArray
168
  -- | Whether we accept offline nodes when making a call.
169
  rpcCallAcceptOffline :: a -> Bool
170

    
171
-- | Generic class that ensures matching RPC call with its respective
172
-- result.
173
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
174
  -- | Create a result based on the received HTTP response.
175
  rpcResultFill :: a -> J.JSValue -> ERpcError b
176

    
177
-- | Http Request definition.
178
data HttpClientRequest = HttpClientRequest
179
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
180
  , requestData :: String       -- ^ The arguments for the call
181
  , requestOpts :: [CurlOption] -- ^ The various curl options
182
  }
183

    
184
-- | Check if a string represented address is IPv6
185
isIpV6 :: String -> Bool
186
isIpV6 = (':' `elem`)
187

    
188
-- | Prepare url for the HTTP request.
189
prepareUrl :: (RpcCall a) => Node -> a -> String
190
prepareUrl node call =
191
  let node_ip = nodePrimaryIp node
192
      node_address = if isIpV6 node_ip
193
                     then "[" ++ node_ip ++ "]"
194
                     else node_ip
195
      port = C.defaultNodedPort
196
      path_prefix = "https://" ++ node_address ++ ":" ++ show port
197
  in path_prefix ++ "/" ++ rpcCallName call
198

    
199
-- | Create HTTP request for a given node provided it is online,
200
-- otherwise create empty response.
201
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
202
                   -> ERpcError HttpClientRequest
203
prepareHttpRequest opts node call
204
  | rpcCallAcceptOffline call || not (nodeOffline node) =
205
      Right HttpClientRequest { requestUrl  = prepareUrl node call
206
                              , requestData = rpcCallData node call
207
                              , requestOpts = opts ++ curlOpts
208
                              }
209
  | otherwise = Left OfflineNodeError
210

    
211
-- | Parse an HTTP reply.
212
parseHttpReply :: (Rpc a b) =>
213
                  a -> ERpcError (CurlCode, String) -> ERpcError b
214
parseHttpReply _ (Left e) = Left e
215
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
216
parseHttpReply _ (Right (code, err)) =
217
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
218

    
219
-- | Parse a result based on the received HTTP response.
220
parseHttpResponse :: (Rpc a b) => a -> String -> ERpcError b
221
parseHttpResponse call res =
222
  case J.decode res of
223
    J.Error val -> Left $ JsonDecodeError val
224
    J.Ok (True, res'') -> rpcResultFill call res''
225
    J.Ok (False, jerr) -> case jerr of
226
       J.JSString msg -> Left $ RpcResultError (J.fromJSString msg)
227
       _ -> Left . JsonDecodeError $ show (pp_value jerr)
228

    
229
-- | Scan the list of results produced by executeRpcCall and extract
230
-- all the RPC errors.
231
rpcErrors :: [(a, ERpcError b)] -> [(a, RpcError)]
232
rpcErrors =
233
  let rpcErr (node, Left err) = Just (node, err)
234
      rpcErr _                = Nothing
235
  in mapMaybe rpcErr
236

    
237
-- | Scan the list of results produced by executeRpcCall and log all the RPC
238
-- errors. Returns the list of errors for further processing.
239
logRpcErrors :: (MonadLog m, Show a) => [(a, ERpcError b)]
240
                                     -> m [(a, RpcError)]
241
logRpcErrors rs =
242
  let logOneRpcErr (node, err) =
243
        logError $ "Error in the RPC HTTP reply from '" ++
244
                   show node ++ "': " ++ show err
245
      errs = rpcErrors rs
246
  in mapM_ logOneRpcErr errs >> return errs
247

    
248
-- | Get options for RPC call
249
getOptionsForCall :: (Rpc a b) => FilePath -> FilePath -> a -> [CurlOption]
250
getOptionsForCall cert_path client_cert_path call =
251
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
252
  , CurlSSLCert client_cert_path
253
  , CurlSSLKey client_cert_path
254
  , CurlCAInfo cert_path
255
  ]
256

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

    
291
-- | Execute an RPC call for many nodes in parallel.
292
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
293
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
294

    
295
-- | Helper function that is used to read dictionaries of values.
296
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
297
sanitizeDictResults =
298
  foldr sanitize1 (Right [])
299
  where
300
    sanitize1 _ (Left e) = Left e
301
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
302
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
303

    
304
-- | Helper function to tranform JSON Result to Either RpcError b.
305
-- Note: For now we really only use it for b s.t. Rpc c b for some c
306
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
307
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
308
fromJResultToRes (J.Ok v) f = Right $ f v
309

    
310
-- | Helper function transforming JSValue to Rpc result type.
311
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
312
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
313

    
314
-- | An opaque data type for representing data that should be compressed
315
-- over the wire.
316
--
317
-- On Python side it is decompressed by @backend._Decompress@.
318
newtype Compressed = Compressed { getCompressed :: BL.ByteString }
319
  deriving (Eq, Ord, Show)
320

    
321
-- TODO Add a unit test for all octets
322
instance J.JSON Compressed where
323
  showJSON = J.showJSON
324
             . (,) C.rpcEncodingZlibBase64
325
             . Base64.encode . compressZlib . getCompressed
326
  readJSON = J.readJSON >=> decompress
327
    where
328
      decompress (enc, cont)
329
        | enc == C.rpcEncodingNone =
330
            return $ Compressed cont
331
        | enc == C.rpcEncodingZlibBase64 =
332
            liftM Compressed
333
            . either fail return . decompressZlib
334
            <=< either (fail . ("Base64: " ++)) return . Base64.decode
335
            $ cont
336
        | otherwise =
337
            fail $ "Unknown RPC encoding type: " ++ show enc
338

    
339
packCompressed :: BL.ByteString -> Compressed
340
packCompressed = Compressed
341

    
342
toCompressed :: String -> Compressed
343
toCompressed = packCompressed . BL.pack
344

    
345
-- * RPC calls and results
346

    
347
-- ** Instance info
348

    
349
-- | Returns information about a single instance
350
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
351
  [ simpleField "instance" [t| String |]
352
  , simpleField "hname" [t| Hypervisor |]
353
  ])
354

    
355
$(declareILADT "InstanceState"
356
  [ ("InstanceStateRunning", 0)
357
  , ("InstanceStateShutdown", 1)
358
  ])
359

    
360
$(makeJSONInstance ''InstanceState)
361

    
362
instance PyValue InstanceState where
363
  showValue = show . instanceStateToRaw
364

    
365
$(buildObject "InstanceInfo" "instInfo"
366
  [ simpleField "memory" [t| Int|]
367
  , simpleField "state"  [t| InstanceState |]
368
  , simpleField "vcpus"  [t| Int |]
369
  , simpleField "time"   [t| Int |]
370
  ])
371

    
372
-- This is optional here because the result may be empty if instance is
373
-- not on a node - and this is not considered an error.
374
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
375
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
376

    
377
instance RpcCall RpcCallInstanceInfo where
378
  rpcCallName _          = "instance_info"
379
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
380
  rpcCallAcceptOffline _ = False
381

    
382
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
383
  rpcResultFill _ res =
384
    case res of
385
      J.JSObject res' ->
386
        case J.fromJSObject res' of
387
          [] -> Right $ RpcResultInstanceInfo Nothing
388
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
389
      _ -> Left $ JsonDecodeError
390
           ("Expected JSObject, got " ++ show (pp_value res))
391

    
392
-- ** AllInstancesInfo
393

    
394
-- | Returns information about all running instances on the given nodes
395
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
396
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
397

    
398
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
399
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
400

    
401
instance RpcCall RpcCallAllInstancesInfo where
402
  rpcCallName _          = "all_instances_info"
403
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
404
  rpcCallAcceptOffline _ = False
405
  rpcCallData _ call     = J.encode (
406
    map fst $ rpcCallAllInstInfoHypervisors call,
407
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
408

    
409
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
410
  -- FIXME: Is there a simpler way to do it?
411
  rpcResultFill _ res =
412
    case res of
413
      J.JSObject res' ->
414
        let res'' = map (second J.readJSON) (J.fromJSObject res')
415
                        :: [(String, J.Result InstanceInfo)] in
416
        case sanitizeDictResults res'' of
417
          Left err -> Left err
418
          Right insts -> Right $ RpcResultAllInstancesInfo insts
419
      _ -> Left $ JsonDecodeError
420
           ("Expected JSObject, got " ++ show (pp_value res))
421

    
422
-- ** InstanceConsoleInfo
423

    
424
-- | Returns information about how to access instances on the given node
425
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
426
  [ simpleField "instance"    [t| Instance |]
427
  , simpleField "node"        [t| Node |]
428
  , simpleField "group"       [t| NodeGroup |]
429
  , simpleField "hvParams"    [t| HvParams |]
430
  , simpleField "beParams"    [t| FilledBeParams |]
431
  ])
432

    
433
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
434
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
435

    
436
$(buildObject "InstanceConsoleInfo" "instConsInfo"
437
  [ simpleField "instance"    [t| String |]
438
  , simpleField "kind"        [t| String |]
439
  , optionalField $
440
    simpleField "message"     [t| String |]
441
  , optionalField $
442
    simpleField "host"        [t| String |]
443
  , optionalField $
444
    simpleField "port"        [t| Int |]
445
  , optionalField $
446
    simpleField "user"        [t| String |]
447
  , optionalField $
448
    simpleField "command"     [t| [String] |]
449
  , optionalField $
450
    simpleField "display"     [t| String |]
451
  ])
452

    
453
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
454
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
455

    
456
instance RpcCall RpcCallInstanceConsoleInfo where
457
  rpcCallName _          = "instance_console_info"
458
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
459
  rpcCallAcceptOffline _ = False
460
  rpcCallData _ call     = J.encode .
461
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
462

    
463
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
464
  rpcResultFill _ res =
465
    case res of
466
      J.JSObject res' ->
467
        let res'' = map (second J.readJSON) (J.fromJSObject res')
468
                        :: [(String, J.Result InstanceConsoleInfo)] in
469
        case sanitizeDictResults res'' of
470
          Left err -> Left err
471
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
472
      _ -> Left $ JsonDecodeError
473
           ("Expected JSObject, got " ++ show (pp_value res))
474

    
475
-- ** InstanceList
476

    
477
-- | Returns the list of running instances on the given nodes
478
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
479
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
480

    
481
$(buildObject "RpcResultInstanceList" "rpcResInstList"
482
  [ simpleField "instances" [t| [String] |] ])
483

    
484
instance RpcCall RpcCallInstanceList where
485
  rpcCallName _          = "instance_list"
486
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
487
  rpcCallAcceptOffline _ = False
488

    
489
instance Rpc RpcCallInstanceList RpcResultInstanceList where
490
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
491

    
492
-- ** NodeInfo
493

    
494
-- | Returns node information
495
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
496
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
497
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
498
  ])
499

    
500
$(buildObject "StorageInfo" "storageInfo"
501
  [ simpleField "name" [t| String |]
502
  , simpleField "type" [t| String |]
503
  , optionalField $ simpleField "storage_free" [t| Int |]
504
  , optionalField $ simpleField "storage_size" [t| Int |]
505
  ])
506

    
507
-- | We only provide common fields as described in hv_base.py.
508
$(buildObject "HvInfo" "hvInfo"
509
  [ simpleField "memory_total" [t| Int |]
510
  , simpleField "memory_free" [t| Int |]
511
  , simpleField "memory_dom0" [t| Int |]
512
  , simpleField "cpu_total" [t| Int |]
513
  , simpleField "cpu_nodes" [t| Int |]
514
  , simpleField "cpu_sockets" [t| Int |]
515
  , simpleField "cpu_dom0" [t| Int |]
516
  ])
517

    
518
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
519
  [ simpleField "boot_id" [t| String |]
520
  , simpleField "storage_info" [t| [StorageInfo] |]
521
  , simpleField "hv_info" [t| [HvInfo] |]
522
  ])
523

    
524
instance RpcCall RpcCallNodeInfo where
525
  rpcCallName _          = "node_info"
526
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
527
  rpcCallAcceptOffline _ = False
528
  rpcCallData n call     = J.encode
529
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
530
                         ++ nodeName n)
531
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
532
    , rpcCallNodeInfoHypervisors call
533
    )
534

    
535
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
536
  rpcResultFill _ res =
537
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
538

    
539
-- ** Version
540

    
541
-- | Query node version.
542
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
543

    
544
-- | Query node reply.
545
$(buildObject "RpcResultVersion" "rpcResultVersion"
546
  [ simpleField "version" [t| Int |]
547
  ])
548

    
549
instance RpcCall RpcCallVersion where
550
  rpcCallName _          = "version"
551
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
552
  rpcCallAcceptOffline _ = True
553
  rpcCallData _          = J.encode
554

    
555
instance Rpc RpcCallVersion RpcResultVersion where
556
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
557

    
558
-- ** StorageList
559

    
560
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
561
  [ simpleField "su_name" [t| StorageType |]
562
  , simpleField "su_args" [t| [String] |]
563
  , simpleField "name"    [t| String |]
564
  , simpleField "fields"  [t| [StorageField] |]
565
  ])
566

    
567
-- FIXME: The resulting JSValues should have types appropriate for their
568
-- StorageField value: Used -> Bool, Name -> String etc
569
$(buildObject "RpcResultStorageList" "rpcResStorageList"
570
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
571

    
572
instance RpcCall RpcCallStorageList where
573
  rpcCallName _          = "storage_list"
574
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
575
  rpcCallAcceptOffline _ = False
576

    
577
instance Rpc RpcCallStorageList RpcResultStorageList where
578
  rpcResultFill call res =
579
    let sfields = rpcCallStorageListFields call in
580
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
581

    
582
-- ** TestDelay
583

    
584
-- | Call definition for test delay.
585
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
586
  [ simpleField "duration" [t| Double |]
587
  ])
588

    
589
-- | Result definition for test delay.
590
data RpcResultTestDelay = RpcResultTestDelay
591
                          deriving Show
592

    
593
-- | Custom JSON instance for null result.
594
instance J.JSON RpcResultTestDelay where
595
  showJSON _        = J.JSNull
596
  readJSON J.JSNull = return RpcResultTestDelay
597
  readJSON _        = fail "Unable to read RpcResultTestDelay"
598

    
599
instance RpcCall RpcCallTestDelay where
600
  rpcCallName _          = "test_delay"
601
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
602
  rpcCallAcceptOffline _ = False
603

    
604
instance Rpc RpcCallTestDelay RpcResultTestDelay where
605
  rpcResultFill _ res = fromJSValueToRes res id
606

    
607
-- ** ExportList
608

    
609
-- | Call definition for export list.
610

    
611
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
612

    
613
-- | Result definition for export list.
614
$(buildObject "RpcResultExportList" "rpcResExportList"
615
  [ simpleField "exports" [t| [String] |]
616
  ])
617

    
618
instance RpcCall RpcCallExportList where
619
  rpcCallName _          = "export_list"
620
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
621
  rpcCallAcceptOffline _ = False
622
  rpcCallData _          = J.encode
623

    
624
instance Rpc RpcCallExportList RpcResultExportList where
625
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList
626

    
627
-- ** Job Queue Replication
628
  
629
-- | Update a job queue file
630
  
631
$(buildObject "RpcCallJobqueueUpdate" "rpcCallJobqueueUpdate"
632
  [ simpleField "file_name" [t| String |]
633
  , simpleField "content" [t| String |]
634
  ])
635

    
636
$(buildObject "RpcResultJobQueueUpdate" "rpcResultJobQueueUpdate" [])
637

    
638
instance RpcCall RpcCallJobqueueUpdate where
639
  rpcCallName _          = "jobqueue_update"
640
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
641
  rpcCallAcceptOffline _ = False
642
  rpcCallData _ call     = J.encode
643
    ( rpcCallJobqueueUpdateFileName call
644
    , toCompressed $ rpcCallJobqueueUpdateContent call
645
    )
646

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

    
654
-- | Rename a file in the job queue
655

    
656
$(buildObject "RpcCallJobqueueRename" "rpcCallJobqueueRename"
657
  [ simpleField "rename" [t| [(String, String)] |]
658
  ])
659

    
660
$(buildObject "RpcResultJobqueueRename" "rpcResultJobqueueRename" [])
661

    
662
instance RpcCall RpcCallJobqueueRename where
663
  rpcCallName _          = "jobqueue_rename"
664
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
665
  rpcCallAcceptOffline _ = False
666

    
667
instance Rpc RpcCallJobqueueRename RpcResultJobqueueRename where
668
  rpcResultFill call res =
669
    -- Upon success, the RPC returns the list of return values of
670
    -- the rename operations, which is always None, serialized to
671
    -- null in JSON.
672
    let expected = J.showJSON . map (const J.JSNull)
673
                     $ rpcCallJobqueueRenameRename call
674
    in if res == expected
675
      then Right RpcResultJobqueueRename
676
      else Left
677
             $ JsonDecodeError ("Expected JSNull, got " ++ show (pp_value res))
678

    
679
-- ** Watcher Status Update
680
      
681
-- | Set the watcher status
682
      
683
$(buildObject "RpcCallSetWatcherPause" "rpcCallSetWatcherPause"
684
  [ optionalField $ timeAsDoubleField "time"
685
  ])
686

    
687
instance RpcCall RpcCallSetWatcherPause where
688
  rpcCallName _          = "set_watcher_pause"
689
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
690
  rpcCallAcceptOffline _ = False
691

    
692
$(buildObject "RpcResultSetWatcherPause" "rpcResultSetWatcherPause" [])
693

    
694
instance Rpc RpcCallSetWatcherPause RpcResultSetWatcherPause where
695
  rpcResultFill _ res =
696
    case res of
697
      J.JSNull ->  Right RpcResultSetWatcherPause
698
      _ -> Left $ JsonDecodeError
699
           ("Expected JSNull, got " ++ show (pp_value res))
700

    
701
-- ** Queue drain status
702
      
703
-- | Set the queu drain flag
704
      
705
$(buildObject "RpcCallSetDrainFlag" "rpcCallSetDrainFlag"
706
  [ simpleField "value" [t| Bool |]
707
  ])
708

    
709
instance RpcCall RpcCallSetDrainFlag where
710
  rpcCallName _          = "jobqueue_set_drain_flag"
711
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
712
  rpcCallAcceptOffline _ = False
713

    
714
$(buildObject "RpcResultSetDrainFlag" "rpcResultSetDrainFalg" [])
715

    
716
instance Rpc RpcCallSetDrainFlag RpcResultSetDrainFlag where
717
  rpcResultFill _ res =
718
    case res of
719
      J.JSNull ->  Right RpcResultSetDrainFlag
720
      _ -> Left $ JsonDecodeError
721
           ("Expected JSNull, got " ++ show (pp_value res))
722

    
723
-- ** Configuration files upload to nodes
724

    
725
-- | Upload a configuration file to nodes
726

    
727
$(buildObject "RpcCallUploadFile" "rpcCallUploadFile"
728
  [ simpleField "file_name" [t| FilePath |]
729
  , simpleField "content" [t| Compressed |]
730
  , optionalField $ fileModeAsIntField "mode"
731
  , simpleField "uid" [t| String |]
732
  , simpleField "gid" [t| String |]
733
  , timeAsDoubleField "atime"
734
  , timeAsDoubleField "mtime"
735
  ])
736

    
737
instance RpcCall RpcCallUploadFile where
738
  rpcCallName _          = "upload_file_single"
739
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
740
  rpcCallAcceptOffline _ = False
741

    
742
$(buildObject "RpcResultUploadFile" "rpcResultUploadFile" [])
743

    
744
instance Rpc RpcCallUploadFile RpcResultUploadFile where
745
  rpcResultFill _ res =
746
    case res of
747
      J.JSNull -> Right RpcResultUploadFile
748
      _ -> Left $ JsonDecodeError
749
           ("Expected JSNull, got " ++ show (pp_value res))
750

    
751
-- | Reads a file and constructs the corresponding 'RpcCallUploadFile' value.
752
prepareRpcCallUploadFile :: RuntimeEnts -> FilePath
753
                         -> ResultG RpcCallUploadFile
754
prepareRpcCallUploadFile re path = do
755
  status <- liftIO $ getFileStatus path
756
  content <- liftIO $ BL.readFile path
757
  let lookupM x m = maybe (failError $ "Uid/gid " ++ show x ++
758
                                       " not found, probably file " ++
759
                                       show path ++ " isn't a Ganeti file")
760
                          return
761
                          (Map.lookup x m)
762
  uid <- lookupM (fileOwner status) (reUidToUser re)
763
  gid <- lookupM (fileGroup status) (reGidToGroup re)
764
  vpath <- liftIO $ makeVirtualPath path
765
  return $ RpcCallUploadFile
766
    vpath
767
    (packCompressed content)
768
    (Just $ fileMode status)
769
    uid
770
    gid
771
    (cTimeToClockTime $ accessTime status)
772
    (cTimeToClockTime $ modificationTime status)
773

    
774
-- | Upload ssconf files to nodes
775

    
776
$(buildObject "RpcCallWriteSsconfFiles" "rpcCallWriteSsconfFiles"
777
  [ simpleField "values" [t| SSConf |]
778
  ])
779

    
780
instance RpcCall RpcCallWriteSsconfFiles where
781
  rpcCallName _          = "write_ssconf_files"
782
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
783
  rpcCallAcceptOffline _ = False
784

    
785
$(buildObject "RpcResultWriteSsconfFiles" "rpcResultWriteSsconfFiles" [])
786

    
787
instance Rpc RpcCallWriteSsconfFiles RpcResultWriteSsconfFiles where
788
  rpcResultFill _ res =
789
    case res of
790
      J.JSNull -> Right RpcResultWriteSsconfFiles
791
      _ -> Left $ JsonDecodeError
792
           ("Expected JSNull, got " ++ show (pp_value res))