Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ ad56f735

History | View | Annotate | Download (18 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
  , InstanceInfo(..)
47
  , RpcCallInstanceInfo(..)
48
  , RpcResultInstanceInfo(..)
49

    
50
  , RpcCallAllInstancesInfo(..)
51
  , RpcResultAllInstancesInfo(..)
52

    
53
  , InstanceConsoleInfoParams(..)
54
  , InstanceConsoleInfo(..)
55
  , RpcCallInstanceConsoleInfo(..)
56
  , RpcResultInstanceConsoleInfo(..)
57

    
58
  , RpcCallInstanceList(..)
59
  , RpcResultInstanceList(..)
60

    
61
  , HvInfo(..)
62
  , StorageInfo(..)
63
  , RpcCallNodeInfo(..)
64
  , RpcResultNodeInfo(..)
65

    
66
  , RpcCallVersion(..)
67
  , RpcResultVersion(..)
68

    
69
  , RpcCallStorageList(..)
70
  , RpcResultStorageList(..)
71

    
72
  , RpcCallTestDelay(..)
73
  , RpcResultTestDelay(..)
74

    
75
  , RpcCallExportList(..)
76
  , RpcResultExportList(..)
77
  ) where
78

    
79
import Control.Arrow (second)
80
import qualified Data.Map as Map
81
import Data.Maybe (fromMaybe)
82
import qualified Text.JSON as J
83
import Text.JSON.Pretty (pp_value)
84

    
85
import Network.Curl
86
import qualified Ganeti.Path as P
87

    
88
import Ganeti.BasicTypes
89
import qualified Ganeti.Constants as C
90
import Ganeti.JSON
91
import Ganeti.Logging
92
import Ganeti.Objects
93
import Ganeti.THH
94
import Ganeti.Types
95
import Ganeti.Curl.Multi
96
import Ganeti.Utils
97

    
98
-- * Base RPC functionality and types
99

    
100
-- | The curl options used for RPC.
101
curlOpts :: [CurlOption]
102
curlOpts = [ CurlFollowLocation False
103
           , CurlSSLVerifyHost 0
104
           , CurlSSLVerifyPeer True
105
           , CurlSSLCertType "PEM"
106
           , CurlSSLKeyType "PEM"
107
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
108
           ]
109

    
110
-- | Data type for RPC error reporting.
111
data RpcError
112
  = CurlLayerError String
113
  | JsonDecodeError String
114
  | RpcResultError String
115
  | OfflineNodeError
116
  deriving (Show, Eq)
117

    
118
-- | Provide explanation to RPC errors.
119
explainRpcError :: RpcError -> String
120
explainRpcError (CurlLayerError code) =
121
    "Curl error:" ++ code
122
explainRpcError (JsonDecodeError msg) =
123
    "Error while decoding JSON from HTTP response: " ++ msg
124
explainRpcError (RpcResultError msg) =
125
    "Error reponse received from RPC server: " ++ msg
126
explainRpcError OfflineNodeError =
127
    "Node is marked offline"
128

    
129
type ERpcError = Either RpcError
130

    
131
-- | A generic class for RPC calls.
132
class (J.JSON a) => RpcCall a where
133
  -- | Give the (Python) name of the procedure.
134
  rpcCallName :: a -> String
135
  -- | Calculate the timeout value for the call execution.
136
  rpcCallTimeout :: a -> Int
137
  -- | Prepare arguments of the call to be send as POST.
138
  rpcCallData :: Node -> a -> String
139
  -- | Whether we accept offline nodes when making a call.
140
  rpcCallAcceptOffline :: a -> Bool
141

    
142
-- | Generic class that ensures matching RPC call with its respective
143
-- result.
144
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
145
  -- | Create a result based on the received HTTP response.
146
  rpcResultFill :: a -> J.JSValue -> ERpcError b
147

    
148
-- | Http Request definition.
149
data HttpClientRequest = HttpClientRequest
150
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
151
  , requestData :: String       -- ^ The arguments for the call
152
  , requestOpts :: [CurlOption] -- ^ The various curl options
153
  }
154

    
155
-- | Prepare url for the HTTP request.
156
prepareUrl :: (RpcCall a) => Node -> a -> String
157
prepareUrl node call =
158
  let node_ip = nodePrimaryIp node
159
      port = C.defaultNodedPort
160
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
161
  in path_prefix ++ "/" ++ rpcCallName call
162

    
163
-- | Create HTTP request for a given node provided it is online,
164
-- otherwise create empty response.
165
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
166
                   -> ERpcError HttpClientRequest
167
prepareHttpRequest opts node call
168
  | rpcCallAcceptOffline call || not (nodeOffline node) =
169
      Right HttpClientRequest { requestUrl  = prepareUrl node call
170
                              , requestData = rpcCallData node call
171
                              , requestOpts = opts ++ curlOpts
172
                              }
173
  | otherwise = Left OfflineNodeError
174

    
175
-- | Parse an HTTP reply.
176
parseHttpReply :: (Rpc a b) =>
177
                  a -> ERpcError (CurlCode, String) -> ERpcError b
178
parseHttpReply _ (Left e) = Left e
179
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
180
parseHttpReply _ (Right (code, err)) =
181
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
182

    
183
-- | Parse a result based on the received HTTP response.
184
parseHttpResponse :: (Rpc a b) => a -> String -> ERpcError b
185
parseHttpResponse call res =
186
  case J.decode res of
187
    J.Error val -> Left $ JsonDecodeError val
188
    J.Ok (True, res'') -> rpcResultFill call res''
189
    J.Ok (False, jerr) -> case jerr of
190
       J.JSString msg -> Left $ RpcResultError (J.fromJSString msg)
191
       _ -> Left . JsonDecodeError $ show (pp_value jerr)
192

    
193
-- | Scan the list of results produced by executeRpcCall and log all the RPC
194
-- errors.
195
logRpcErrors :: [(a, ERpcError b)] -> IO ()
196
logRpcErrors allElems =
197
  let logOneRpcErr (_, Right _) = return ()
198
      logOneRpcErr (_, Left err) =
199
        logError $ "Error in the RPC HTTP reply: " ++ show err
200
  in mapM_ logOneRpcErr allElems
201

    
202
-- | Get options for RPC call
203
getOptionsForCall :: (Rpc a b) => FilePath -> a -> [CurlOption]
204
getOptionsForCall certPath call =
205
  [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
206
  , CurlSSLCert certPath
207
  , CurlSSLKey certPath
208
  , CurlCAInfo certPath
209
  ]
210

    
211
-- | Execute multiple RPC calls in parallel
212
executeRpcCalls :: (Rpc a b) => [(Node, a)] -> IO [(Node, ERpcError b)]
213
executeRpcCalls nodeCalls = do
214
  cert_file <- P.nodedCertFile
215
  let (nodes, calls) = unzip nodeCalls
216
      opts = map (getOptionsForCall cert_file) calls
217
      opts_urls = zipWith3 (\n c o ->
218
                         case prepareHttpRequest o n c of
219
                           Left v -> Left v
220
                           Right request ->
221
                             Right (CurlPostFields [requestData request]:
222
                                    requestOpts request,
223
                                    requestUrl request)
224
                    ) nodes calls opts
225
  -- split the opts_urls list; we don't want to pass the
226
  -- failed-already nodes to Curl
227
  let (lefts, rights, trail) = splitEithers opts_urls
228
  results <- execMultiCall rights
229
  results' <- case recombineEithers lefts results trail of
230
                Bad msg -> error msg
231
                Ok r -> return r
232
  -- now parse the replies
233
  let results'' = zipWith parseHttpReply calls results'
234
      pairedList = zip nodes results''
235
  logRpcErrors pairedList
236
  return pairedList
237

    
238
-- | Execute an RPC call for many nodes in parallel.
239
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
240
executeRpcCall nodes call = executeRpcCalls . zip nodes $ repeat call
241

    
242
-- | Helper function that is used to read dictionaries of values.
243
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
244
sanitizeDictResults =
245
  foldr sanitize1 (Right [])
246
  where
247
    sanitize1 _ (Left e) = Left e
248
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
249
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
250

    
251
-- | Helper function to tranform JSON Result to Either RpcError b.
252
-- Note: For now we really only use it for b s.t. Rpc c b for some c
253
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
254
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
255
fromJResultToRes (J.Ok v) f = Right $ f v
256

    
257
-- | Helper function transforming JSValue to Rpc result type.
258
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
259
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
260

    
261
-- * RPC calls and results
262

    
263
-- ** Instance info
264

    
265
-- | Returns information about a single instance
266
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
267
  [ simpleField "instance" [t| String |]
268
  , simpleField "hname" [t| Hypervisor |]
269
  ])
270

    
271
$(buildObject "InstanceInfo" "instInfo"
272
  [ simpleField "memory" [t| Int|]
273
  , simpleField "state"  [t| String |] -- It depends on hypervisor :(
274
  , simpleField "vcpus"  [t| Int |]
275
  , simpleField "time"   [t| Int |]
276
  ])
277

    
278
-- This is optional here because the result may be empty if instance is
279
-- not on a node - and this is not considered an error.
280
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
281
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
282

    
283
instance RpcCall RpcCallInstanceInfo where
284
  rpcCallName _          = "instance_info"
285
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
286
  rpcCallAcceptOffline _ = False
287
  rpcCallData _ call     = J.encode
288
    ( rpcCallInstInfoInstance call
289
    , rpcCallInstInfoHname call
290
    )
291

    
292
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
293
  rpcResultFill _ res =
294
    case res of
295
      J.JSObject res' ->
296
        case J.fromJSObject res' of
297
          [] -> Right $ RpcResultInstanceInfo Nothing
298
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
299
      _ -> Left $ JsonDecodeError
300
           ("Expected JSObject, got " ++ show (pp_value res))
301

    
302
-- ** AllInstancesInfo
303

    
304
-- | Returns information about all running instances on the given nodes
305
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
306
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
307

    
308
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
309
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
310

    
311
instance RpcCall RpcCallAllInstancesInfo where
312
  rpcCallName _          = "all_instances_info"
313
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
314
  rpcCallAcceptOffline _ = False
315
  rpcCallData _ call     = J.encode (
316
    map fst $ rpcCallAllInstInfoHypervisors call,
317
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
318

    
319
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
320
  -- FIXME: Is there a simpler way to do it?
321
  rpcResultFill _ res =
322
    case res of
323
      J.JSObject res' ->
324
        let res'' = map (second J.readJSON) (J.fromJSObject res')
325
                        :: [(String, J.Result InstanceInfo)] in
326
        case sanitizeDictResults res'' of
327
          Left err -> Left err
328
          Right insts -> Right $ RpcResultAllInstancesInfo insts
329
      _ -> Left $ JsonDecodeError
330
           ("Expected JSObject, got " ++ show (pp_value res))
331

    
332
-- ** InstanceConsoleInfo
333

    
334
-- | Returns information about how to access instances on the given node
335
$(buildObject "InstanceConsoleInfoParams" "instConsInfoParams"
336
  [ simpleField "instance"    [t| Instance |]
337
  , simpleField "node"        [t| Node |]
338
  , simpleField "hvParams"    [t| HvParams |]
339
  , simpleField "beParams"    [t| FilledBeParams |]
340
  ])
341

    
342
$(buildObject "RpcCallInstanceConsoleInfo" "rpcCallInstConsInfo"
343
  [ simpleField "instanceInfo" [t| [(String, InstanceConsoleInfoParams)] |] ])
344

    
345
$(buildObject "InstanceConsoleInfo" "instConsInfo"
346
  [ simpleField "instance"    [t| String |]
347
  , simpleField "kind"        [t| String |]
348
  , optionalField $
349
    simpleField "message"     [t| String |]
350
  , optionalField $
351
    simpleField "host"        [t| String |]
352
  , optionalField $
353
    simpleField "port"        [t| Int |]
354
  , optionalField $
355
    simpleField "user"        [t| String |]
356
  , optionalField $
357
    simpleField "command"     [t| [String] |]
358
  , optionalField $
359
    simpleField "display"     [t| String |]
360
  ])
361

    
362
$(buildObject "RpcResultInstanceConsoleInfo" "rpcResInstConsInfo"
363
  [ simpleField "instancesInfo" [t| [(String, InstanceConsoleInfo)] |] ])
364

    
365
instance RpcCall RpcCallInstanceConsoleInfo where
366
  rpcCallName _          = "instance_console_info"
367
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
368
  rpcCallAcceptOffline _ = False
369
  rpcCallData _ call     = J.encode .
370
    GenericContainer $ Map.fromList (rpcCallInstConsInfoInstanceInfo call)
371

    
372
instance Rpc RpcCallInstanceConsoleInfo RpcResultInstanceConsoleInfo where
373
  rpcResultFill _ res =
374
    case res of
375
      J.JSObject res' ->
376
        let res'' = map (second J.readJSON) (J.fromJSObject res')
377
                        :: [(String, J.Result InstanceConsoleInfo)] in
378
        case sanitizeDictResults res'' of
379
          Left err -> Left err
380
          Right instInfos -> Right $ RpcResultInstanceConsoleInfo instInfos
381
      _ -> Left $ JsonDecodeError
382
           ("Expected JSObject, got " ++ show (pp_value res))
383

    
384
-- ** InstanceList
385

    
386
-- | Returns the list of running instances on the given nodes
387
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
388
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
389

    
390
$(buildObject "RpcResultInstanceList" "rpcResInstList"
391
  [ simpleField "instances" [t| [String] |] ])
392

    
393
instance RpcCall RpcCallInstanceList where
394
  rpcCallName _          = "instance_list"
395
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
396
  rpcCallAcceptOffline _ = False
397
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
398

    
399
instance Rpc RpcCallInstanceList RpcResultInstanceList where
400
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
401

    
402
-- ** NodeInfo
403

    
404
-- | Returns node information
405
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
406
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
407
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
408
  ])
409

    
410
$(buildObject "StorageInfo" "storageInfo"
411
  [ simpleField "name" [t| String |]
412
  , simpleField "type" [t| String |]
413
  , optionalField $ simpleField "storage_free" [t| Int |]
414
  , optionalField $ simpleField "storage_size" [t| Int |]
415
  ])
416

    
417
-- | We only provide common fields as described in hv_base.py.
418
$(buildObject "HvInfo" "hvInfo"
419
  [ simpleField "memory_total" [t| Int |]
420
  , simpleField "memory_free" [t| Int |]
421
  , simpleField "memory_dom0" [t| Int |]
422
  , simpleField "cpu_total" [t| Int |]
423
  , simpleField "cpu_nodes" [t| Int |]
424
  , simpleField "cpu_sockets" [t| Int |]
425
  , simpleField "cpu_dom0" [t| Int |]
426
  ])
427

    
428
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
429
  [ simpleField "boot_id" [t| String |]
430
  , simpleField "storage_info" [t| [StorageInfo] |]
431
  , simpleField "hv_info" [t| [HvInfo] |]
432
  ])
433

    
434
instance RpcCall RpcCallNodeInfo where
435
  rpcCallName _          = "node_info"
436
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
437
  rpcCallAcceptOffline _ = False
438
  rpcCallData n call     = J.encode
439
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
440
                         ++ nodeName n)
441
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
442
    , rpcCallNodeInfoHypervisors call
443
    )
444

    
445
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
446
  rpcResultFill _ res =
447
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
448

    
449
-- ** Version
450

    
451
-- | Query node version.
452
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
453

    
454
-- | Query node reply.
455
$(buildObject "RpcResultVersion" "rpcResultVersion"
456
  [ simpleField "version" [t| Int |]
457
  ])
458

    
459
instance RpcCall RpcCallVersion where
460
  rpcCallName _          = "version"
461
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
462
  rpcCallAcceptOffline _ = True
463
  rpcCallData _          = J.encode
464

    
465
instance Rpc RpcCallVersion RpcResultVersion where
466
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
467

    
468
-- ** StorageList
469

    
470
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
471
  [ simpleField "su_name" [t| StorageType |]
472
  , simpleField "su_args" [t| [String] |]
473
  , simpleField "name"    [t| String |]
474
  , simpleField "fields"  [t| [StorageField] |]
475
  ])
476

    
477
-- FIXME: The resulting JSValues should have types appropriate for their
478
-- StorageField value: Used -> Bool, Name -> String etc
479
$(buildObject "RpcResultStorageList" "rpcResStorageList"
480
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
481

    
482
instance RpcCall RpcCallStorageList where
483
  rpcCallName _          = "storage_list"
484
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
485
  rpcCallAcceptOffline _ = False
486
  rpcCallData _ call     = J.encode
487
    ( rpcCallStorageListSuName call
488
    , rpcCallStorageListSuArgs call
489
    , rpcCallStorageListName call
490
    , rpcCallStorageListFields call
491
    )
492

    
493
instance Rpc RpcCallStorageList RpcResultStorageList where
494
  rpcResultFill call res =
495
    let sfields = rpcCallStorageListFields call in
496
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
497

    
498
-- ** TestDelay
499

    
500
-- | Call definition for test delay.
501
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
502
  [ simpleField "duration" [t| Double |]
503
  ])
504

    
505
-- | Result definition for test delay.
506
data RpcResultTestDelay = RpcResultTestDelay
507
                          deriving Show
508

    
509
-- | Custom JSON instance for null result.
510
instance J.JSON RpcResultTestDelay where
511
  showJSON _        = J.JSNull
512
  readJSON J.JSNull = return RpcResultTestDelay
513
  readJSON _        = fail "Unable to read RpcResultTestDelay"
514

    
515
instance RpcCall RpcCallTestDelay where
516
  rpcCallName _          = "test_delay"
517
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
518
  rpcCallAcceptOffline _ = False
519
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
520

    
521
instance Rpc RpcCallTestDelay RpcResultTestDelay where
522
  rpcResultFill _ res = fromJSValueToRes res id
523

    
524
-- ** ExportList
525

    
526
-- | Call definition for export list.
527

    
528
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
529

    
530
-- | Result definition for export list.
531
$(buildObject "RpcResultExportList" "rpcResExportList"
532
  [ simpleField "exports" [t| [String] |]
533
  ])
534

    
535
instance RpcCall RpcCallExportList where
536
  rpcCallName _          = "export_list"
537
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
538
  rpcCallAcceptOffline _ = False
539
  rpcCallData _          = J.encode
540

    
541
instance Rpc RpcCallExportList RpcResultExportList where
542
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList