Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 3b170ad4

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

    
72
  , rpcTimeoutFromRaw -- FIXME: Not used anywhere
73
  ) where
74

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

    
81
import Network.Curl
82
import qualified Ganeti.Path as P
83

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

    
93
-- * Base RPC functionality and types
94

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

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

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

    
124
type ERpcError = Either RpcError
125

    
126
-- | Basic timeouts for RPC calls.
127
$(declareIADT "RpcTimeout"
128
  [ ( "Urgent",    'C.rpcTmoUrgent )
129
  , ( "Fast",      'C.rpcTmoFast )
130
  , ( "Normal",    'C.rpcTmoNormal )
131
  , ( "Slow",      'C.rpcTmoSlow )
132
  , ( "FourHours", 'C.rpcTmo4hrs )
133
  , ( "OneDay",    'C.rpcTmo1day )
134
  ])
135

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

    
147
-- | Generic class that ensures matching RPC call with its respective
148
-- result.
149
class (RpcCall a, J.JSON b) => Rpc a b  | a -> b, b -> a where
150
  -- | Create a result based on the received HTTP response.
151
  rpcResultFill :: a -> J.JSValue -> ERpcError b
152

    
153
-- | Http Request definition.
154
data HttpClientRequest = HttpClientRequest
155
  { requestUrl  :: String       -- ^ The actual URL for the node endpoint
156
  , requestData :: String       -- ^ The arguments for the call
157
  , requestOpts :: [CurlOption] -- ^ The various curl options
158
  }
159

    
160
-- | Prepare url for the HTTP request.
161
prepareUrl :: (RpcCall a) => Node -> a -> String
162
prepareUrl node call =
163
  let node_ip = nodePrimaryIp node
164
      port = C.defaultNodedPort
165
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
166
  in path_prefix ++ "/" ++ rpcCallName call
167

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

    
180
-- | Parse an HTTP reply.
181
parseHttpReply :: (Rpc a b) =>
182
                  a -> ERpcError (CurlCode, String) -> ERpcError b
183
parseHttpReply _ (Left e) = Left e
184
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
185
parseHttpReply _ (Right (code, err)) =
186
  Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
187

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

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

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

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

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

    
252
-- | Helper function transforming JSValue to Rpc result type.
253
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
254
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
255

    
256
-- * RPC calls and results
257

    
258
-- ** Instance info
259

    
260
-- | InstanceInfo
261
--   Returns information about a single instance.
262

    
263
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
264
  [ simpleField "instance" [t| String |]
265
  , simpleField "hname" [t| Hypervisor |]
266
  ])
267

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

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

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

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

    
299
-- ** AllInstancesInfo
300

    
301
-- | AllInstancesInfo
302
--   Returns information about all running instances on the given nodes
303
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
304
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
305

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

    
309
instance RpcCall RpcCallAllInstancesInfo where
310
  rpcCallName _          = "all_instances_info"
311
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
312
  rpcCallAcceptOffline _ = False
313
  rpcCallData _ call     = J.encode [rpcCallAllInstInfoHypervisors call]
314

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

    
328
-- ** InstanceList
329

    
330
-- | InstanceList
331
-- Returns the list of running instances on the given nodes.
332
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
333
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
334

    
335
$(buildObject "RpcResultInstanceList" "rpcResInstList"
336
  [ simpleField "instances" [t| [String] |] ])
337

    
338
instance RpcCall RpcCallInstanceList where
339
  rpcCallName _          = "instance_list"
340
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
341
  rpcCallAcceptOffline _ = False
342
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
343

    
344
instance Rpc RpcCallInstanceList RpcResultInstanceList where
345
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
346

    
347
-- ** NodeInfo
348

    
349
-- | NodeInfo
350
-- Return node information.
351
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
352
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
353
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
354
  ])
355

    
356
$(buildObject "StorageInfo" "storageInfo"
357
  [ simpleField "name" [t| String |]
358
  , simpleField "type" [t| String |]
359
  , optionalField $ simpleField "storage_free" [t| Int |]
360
  , optionalField $ simpleField "storage_size" [t| Int |]
361
  ])
362

    
363
-- | We only provide common fields as described in hv_base.py.
364
$(buildObject "HvInfo" "hvInfo"
365
  [ simpleField "memory_total" [t| Int |]
366
  , simpleField "memory_free" [t| Int |]
367
  , simpleField "memory_dom0" [t| Int |]
368
  , simpleField "cpu_total" [t| Int |]
369
  , simpleField "cpu_nodes" [t| Int |]
370
  , simpleField "cpu_sockets" [t| Int |]
371
  , simpleField "cpu_dom0" [t| Int |]
372
  ])
373

    
374
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
375
  [ simpleField "boot_id" [t| String |]
376
  , simpleField "storage_info" [t| [StorageInfo] |]
377
  , simpleField "hv_info" [t| [HvInfo] |]
378
  ])
379

    
380
instance RpcCall RpcCallNodeInfo where
381
  rpcCallName _          = "node_info"
382
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
383
  rpcCallAcceptOffline _ = False
384
  rpcCallData n call     = J.encode
385
    ( fromMaybe (error $ "Programmer error: missing parameter for node named "
386
                         ++ nodeName n)
387
          $ Map.lookup (nodeUuid n) (rpcCallNodeInfoStorageUnits call)
388
    , rpcCallNodeInfoHypervisors call
389
    )
390

    
391
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
392
  rpcResultFill _ res =
393
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
394

    
395
-- ** Version
396

    
397
-- | Query node version.
398
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
399

    
400
-- | Query node reply.
401
$(buildObject "RpcResultVersion" "rpcResultVersion"
402
  [ simpleField "version" [t| Int |]
403
  ])
404

    
405
instance RpcCall RpcCallVersion where
406
  rpcCallName _          = "version"
407
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
408
  rpcCallAcceptOffline _ = True
409
  rpcCallData _          = J.encode
410

    
411
instance Rpc RpcCallVersion RpcResultVersion where
412
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
413

    
414
-- ** StorageList
415

    
416
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
417
  [ simpleField "su_name" [t| StorageType |]
418
  , simpleField "su_args" [t| [String] |]
419
  , simpleField "name"    [t| String |]
420
  , simpleField "fields"  [t| [StorageField] |]
421
  ])
422

    
423
-- FIXME: The resulting JSValues should have types appropriate for their
424
-- StorageField value: Used -> Bool, Name -> String etc
425
$(buildObject "RpcResultStorageList" "rpcResStorageList"
426
  [ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
427

    
428
instance RpcCall RpcCallStorageList where
429
  rpcCallName _          = "storage_list"
430
  rpcCallTimeout _       = rpcTimeoutToRaw Normal
431
  rpcCallAcceptOffline _ = False
432
  rpcCallData _ call     = J.encode
433
    ( rpcCallStorageListSuName call
434
    , rpcCallStorageListSuArgs call
435
    , rpcCallStorageListName call
436
    , rpcCallStorageListFields call
437
    )
438

    
439
instance Rpc RpcCallStorageList RpcResultStorageList where
440
  rpcResultFill call res =
441
    let sfields = rpcCallStorageListFields call in
442
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
443

    
444
-- ** TestDelay
445

    
446
-- | Call definition for test delay.
447
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
448
  [ simpleField "duration" [t| Double |]
449
  ])
450

    
451
-- | Result definition for test delay.
452
data RpcResultTestDelay = RpcResultTestDelay
453
                          deriving Show
454

    
455
-- | Custom JSON instance for null result.
456
instance J.JSON RpcResultTestDelay where
457
  showJSON _        = J.JSNull
458
  readJSON J.JSNull = return RpcResultTestDelay
459
  readJSON _        = fail "Unable to read RpcResultTestDelay"
460

    
461
instance RpcCall RpcCallTestDelay where
462
  rpcCallName _          = "test_delay"
463
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
464
  rpcCallAcceptOffline _ = False
465
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
466

    
467
instance Rpc RpcCallTestDelay RpcResultTestDelay where
468
  rpcResultFill _ res = fromJSValueToRes res id
469

    
470
-- ** ExportList
471

    
472
-- | Call definition for export list.
473

    
474
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
475

    
476
-- | Result definition for export list.
477
$(buildObject "RpcResultExportList" "rpcResExportList"
478
  [ simpleField "exports" [t| [String] |]
479
  ])
480

    
481
instance RpcCall RpcCallExportList where
482
  rpcCallName _          = "export_list"
483
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
484
  rpcCallAcceptOffline _ = False
485
  rpcCallData _          = J.encode
486

    
487
instance Rpc RpcCallExportList RpcResultExportList where
488
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList