Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ c14ba680

History | View | Annotate | Download (15.6 kB)

1
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
2
  BangPatterns, TemplateHaskell #-}
3

    
4
{-| Implementation of the RPC client.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2012, 2013 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.Rpc
30
  ( RpcCall
31
  , Rpc
32
  , RpcError(..)
33
  , ERpcError
34
  , explainRpcError
35
  , executeRpcCall
36
  , logRpcErrors
37

    
38
  , rpcCallName
39
  , rpcCallTimeout
40
  , rpcCallData
41
  , rpcCallAcceptOffline
42

    
43
  , rpcResultFill
44

    
45
  , InstanceInfo(..)
46
  , RpcCallInstanceInfo(..)
47
  , RpcResultInstanceInfo(..)
48

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

    
52
  , RpcCallInstanceList(..)
53
  , RpcResultInstanceList(..)
54

    
55
  , HvInfo(..)
56
  , StorageInfo(..)
57
  , RpcCallNodeInfo(..)
58
  , RpcResultNodeInfo(..)
59

    
60
  , RpcCallVersion(..)
61
  , RpcResultVersion(..)
62

    
63
  , RpcCallStorageList(..)
64
  , RpcResultStorageList(..)
65

    
66
  , RpcCallTestDelay(..)
67
  , RpcResultTestDelay(..)
68

    
69
  , RpcCallExportList(..)
70
  , RpcResultExportList(..)
71
  ) where
72

    
73
import Control.Arrow (second)
74
import qualified Data.Map as Map
75
import Data.Maybe (fromMaybe)
76
import qualified Text.JSON as J
77
import Text.JSON.Pretty (pp_value)
78

    
79
import Network.Curl
80
import qualified Ganeti.Path as P
81

    
82
import Ganeti.BasicTypes
83
import qualified Ganeti.Constants as C
84
import Ganeti.JSON
85
import Ganeti.Logging
86
import Ganeti.Objects
87
import Ganeti.THH
88
import Ganeti.Types
89
import Ganeti.Curl.Multi
90
import Ganeti.Utils
91

    
92
-- * Base RPC functionality and types
93

    
94
-- | The curl options used for RPC.
95
curlOpts :: [CurlOption]
96
curlOpts = [ CurlFollowLocation False
97
           , CurlSSLVerifyHost 0
98
           , CurlSSLVerifyPeer True
99
           , CurlSSLCertType "PEM"
100
           , CurlSSLKeyType "PEM"
101
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
102
           ]
103

    
104
-- | Data type for RPC error reporting.
105
data RpcError
106
  = CurlLayerError String
107
  | JsonDecodeError String
108
  | RpcResultError String
109
  | OfflineNodeError
110
  deriving (Show, Eq)
111

    
112
-- | Provide explanation to RPC errors.
113
explainRpcError :: RpcError -> String
114
explainRpcError (CurlLayerError code) =
115
    "Curl error:" ++ code
116
explainRpcError (JsonDecodeError msg) =
117
    "Error while decoding JSON from HTTP response: " ++ msg
118
explainRpcError (RpcResultError msg) =
119
    "Error reponse received from RPC server: " ++ msg
120
explainRpcError OfflineNodeError =
121
    "Node is marked offline"
122

    
123
type ERpcError = Either RpcError
124

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

    
136
-- | Generic class that ensures matching RPC call with its respective
137
-- result.
138
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
139
  -- | Create a result based on the received HTTP response.
140
  rpcResultFill :: a -> J.JSValue -> ERpcError b
141

    
142
-- | Http Request definition.
143
data HttpClientRequest = HttpClientRequest
144
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
145
  , requestData :: String       -- ^ The arguments for the call
146
  , requestOpts :: [CurlOption] -- ^ The various curl options
147
  }
148

    
149
-- | Prepare url for the HTTP request.
150
prepareUrl :: (RpcCall a) => Node -> a -> String
151
prepareUrl node call =
152
  let node_ip = nodePrimaryIp node
153
      port = C.defaultNodedPort
154
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
155
  in path_prefix ++ "/" ++ rpcCallName call
156

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

    
169
-- | Parse an HTTP reply.
170
parseHttpReply :: (Rpc a b) =>
171
                  a -> ERpcError (CurlCode, String) -> ERpcError b
172
parseHttpReply _ (Left e) = Left e
173
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
174
parseHttpReply _ (Right (code, err)) =
175
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
176

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

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

    
196
-- | Execute RPC call for many nodes in parallel.
197
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
198
executeRpcCall nodes call = do
199
  cert_file <- P.nodedCertFile
200
  let opts = [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
201
             , CurlSSLCert cert_file
202
             , CurlSSLKey cert_file
203
             , CurlCAInfo cert_file
204
             ]
205
      opts_urls = map (\n ->
206
                         case prepareHttpRequest opts n call of
207
                           Left v -> Left v
208
                           Right request ->
209
                             Right (CurlPostFields [requestData request]:
210
                                    requestOpts request,
211
                                    requestUrl request)
212
                      ) nodes
213
  -- split the opts_urls list; we don't want to pass the
214
  -- failed-already nodes to Curl
215
  let (lefts, rights, trail) = splitEithers opts_urls
216
  results <- execMultiCall rights
217
  results' <- case recombineEithers lefts results trail of
218
                Bad msg -> error msg
219
                Ok r -> return r
220
  -- now parse the replies
221
  let results'' = map (parseHttpReply call) results'
222
      pairedList = zip nodes results''
223
  logRpcErrors pairedList
224
  return pairedList
225

    
226
-- | Helper function that is used to read dictionaries of values.
227
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
228
sanitizeDictResults =
229
  foldr sanitize1 (Right [])
230
  where
231
    sanitize1 _ (Left e) = Left e
232
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
233
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
234

    
235
-- | Helper function to tranform JSON Result to Either RpcError b.
236
-- Note: For now we really only use it for b s.t. Rpc c b for some c
237
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
238
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
239
fromJResultToRes (J.Ok v) f = Right $ f v
240

    
241
-- | Helper function transforming JSValue to Rpc result type.
242
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
243
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
244

    
245
-- * RPC calls and results
246

    
247
-- ** Instance info
248

    
249
-- | InstanceInfo
250
--   Returns information about a single instance.
251

    
252
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
253
  [ simpleField "instance" [t| String |]
254
  , simpleField "hname" [t| Hypervisor |]
255
  ])
256

    
257
$(buildObject "InstanceInfo" "instInfo"
258
  [ simpleField "memory" [t| Int|]
259
  , simpleField "state"  [t| String |] -- It depends on hypervisor :(
260
  , simpleField "vcpus"  [t| Int |]
261
  , simpleField "time"   [t| Int |]
262
  ])
263

    
264
-- This is optional here because the result may be empty if instance is
265
-- not on a node - and this is not considered an error.
266
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
267
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
268

    
269
instance RpcCall RpcCallInstanceInfo where
270
  rpcCallName _          = "instance_info"
271
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
272
  rpcCallAcceptOffline _ = False
273
  rpcCallData _ call     = J.encode
274
    ( rpcCallInstInfoInstance call
275
    , rpcCallInstInfoHname call
276
    )
277

    
278
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
279
  rpcResultFill _ res =
280
    case res of
281
      J.JSObject res' ->
282
        case J.fromJSObject res' of
283
          [] -> Right $ RpcResultInstanceInfo Nothing
284
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
285
      _ -> Left $ JsonDecodeError
286
           ("Expected JSObject, got " ++ show (pp_value res))
287

    
288
-- ** AllInstancesInfo
289

    
290
-- | AllInstancesInfo
291
--   Returns information about all running instances on the given nodes
292
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
293
  [ simpleField "hypervisors" [t| [(Hypervisor, HvParams)] |] ])
294

    
295
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
296
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
297

    
298
instance RpcCall RpcCallAllInstancesInfo where
299
  rpcCallName _          = "all_instances_info"
300
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
301
  rpcCallAcceptOffline _ = False
302
  rpcCallData _ call     = J.encode (
303
    map fst $ rpcCallAllInstInfoHypervisors call,
304
    GenericContainer . Map.fromList $ rpcCallAllInstInfoHypervisors call)
305

    
306
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
307
  -- FIXME: Is there a simpler way to do it?
308
  rpcResultFill _ res =
309
    case res of
310
      J.JSObject res' ->
311
        let res'' = map (second J.readJSON) (J.fromJSObject res')
312
                        :: [(String, J.Result InstanceInfo)] in
313
        case sanitizeDictResults res'' of
314
          Left err -> Left err
315
          Right insts -> Right $ RpcResultAllInstancesInfo insts
316
      _ -> Left $ JsonDecodeError
317
           ("Expected JSObject, got " ++ show (pp_value res))
318

    
319
-- ** InstanceList
320

    
321
-- | InstanceList
322
-- Returns the list of running instances on the given nodes.
323
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
324
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
325

    
326
$(buildObject "RpcResultInstanceList" "rpcResInstList"
327
  [ simpleField "instances" [t| [String] |] ])
328

    
329
instance RpcCall RpcCallInstanceList where
330
  rpcCallName _          = "instance_list"
331
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
332
  rpcCallAcceptOffline _ = False
333
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
334

    
335
instance Rpc RpcCallInstanceList RpcResultInstanceList where
336
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
337

    
338
-- ** NodeInfo
339

    
340
-- | NodeInfo
341
-- Return node information.
342
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
343
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
344
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
345
  ])
346

    
347
$(buildObject "StorageInfo" "storageInfo"
348
  [ simpleField "name" [t| String |]
349
  , simpleField "type" [t| String |]
350
  , optionalField $ simpleField "storage_free" [t| Int |]
351
  , optionalField $ simpleField "storage_size" [t| Int |]
352
  ])
353

    
354
-- | We only provide common fields as described in hv_base.py.
355
$(buildObject "HvInfo" "hvInfo"
356
  [ simpleField "memory_total" [t| Int |]
357
  , simpleField "memory_free" [t| Int |]
358
  , simpleField "memory_dom0" [t| Int |]
359
  , simpleField "cpu_total" [t| Int |]
360
  , simpleField "cpu_nodes" [t| Int |]
361
  , simpleField "cpu_sockets" [t| Int |]
362
  , simpleField "cpu_dom0" [t| Int |]
363
  ])
364

    
365
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
366
  [ simpleField "boot_id" [t| String |]
367
  , simpleField "storage_info" [t| [StorageInfo] |]
368
  , simpleField "hv_info" [t| [HvInfo] |]
369
  ])
370

    
371
instance RpcCall RpcCallNodeInfo where
372
  rpcCallName _          = "node_info"
373
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
374
  rpcCallAcceptOffline _ = False
375
  rpcCallData n call     = J.encode
376
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
377
                         ++ nodeName n)
378
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
379
    , rpcCallNodeInfoHypervisors call
380
    )
381

    
382
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
383
  rpcResultFill _ res =
384
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
385

    
386
-- ** Version
387

    
388
-- | Query node version.
389
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
390

    
391
-- | Query node reply.
392
$(buildObject "RpcResultVersion" "rpcResultVersion"
393
  [ simpleField "version" [t| Int |]
394
  ])
395

    
396
instance RpcCall RpcCallVersion where
397
  rpcCallName _          = "version"
398
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
399
  rpcCallAcceptOffline _ = True
400
  rpcCallData _          = J.encode
401

    
402
instance Rpc RpcCallVersion RpcResultVersion where
403
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
404

    
405
-- ** StorageList
406

    
407
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
408
  [ simpleField "su_name" [t| StorageType |]
409
  , simpleField "su_args" [t| [String] |]
410
  , simpleField "name"    [t| String |]
411
  , simpleField "fields"  [t| [StorageField] |]
412
  ])
413

    
414
-- FIXME: The resulting JSValues should have types appropriate for their
415
-- StorageField value: Used -> Bool, Name -> String etc
416
$(buildObject "RpcResultStorageList" "rpcResStorageList"
417
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
418

    
419
instance RpcCall RpcCallStorageList where
420
  rpcCallName _          = "storage_list"
421
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
422
  rpcCallAcceptOffline _ = False
423
  rpcCallData _ call     = J.encode
424
    ( rpcCallStorageListSuName call
425
    , rpcCallStorageListSuArgs call
426
    , rpcCallStorageListName call
427
    , rpcCallStorageListFields call
428
    )
429

    
430
instance Rpc RpcCallStorageList RpcResultStorageList where
431
  rpcResultFill call res =
432
    let sfields = rpcCallStorageListFields call in
433
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
434

    
435
-- ** TestDelay
436

    
437
-- | Call definition for test delay.
438
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
439
  [ simpleField "duration" [t| Double |]
440
  ])
441

    
442
-- | Result definition for test delay.
443
data RpcResultTestDelay = RpcResultTestDelay
444
                          deriving Show
445

    
446
-- | Custom JSON instance for null result.
447
instance J.JSON RpcResultTestDelay where
448
  showJSON _        = J.JSNull
449
  readJSON J.JSNull = return RpcResultTestDelay
450
  readJSON _        = fail "Unable to read RpcResultTestDelay"
451

    
452
instance RpcCall RpcCallTestDelay where
453
  rpcCallName _          = "test_delay"
454
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
455
  rpcCallAcceptOffline _ = False
456
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
457

    
458
instance Rpc RpcCallTestDelay RpcResultTestDelay where
459
  rpcResultFill _ res = fromJSValueToRes res id
460

    
461
-- ** ExportList
462

    
463
-- | Call definition for export list.
464

    
465
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
466

    
467
-- | Result definition for export list.
468
$(buildObject "RpcResultExportList" "rpcResExportList"
469
  [ simpleField "exports" [t| [String] |]
470
  ])
471

    
472
instance RpcCall RpcCallExportList where
473
  rpcCallName _          = "export_list"
474
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
475
  rpcCallAcceptOffline _ = False
476
  rpcCallData _          = J.encode
477

    
478
instance Rpc RpcCallExportList RpcResultExportList where
479
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList