Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ b6e31235

History | View | Annotate | Download (15.7 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.Logging
85
import Ganeti.Objects
86
import Ganeti.THH
87
import Ganeti.Types
88
import Ganeti.Curl.Multi
89
import Ganeti.Utils
90

    
91
-- * Base RPC functionality and types
92

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

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

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

    
122
type ERpcError = Either RpcError
123

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

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

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

    
148
-- | Check if a string represented address is IPv6
149
isIpV6 :: String -> Bool
150
isIpV6 = (':' `elem`)
151

    
152
-- | Prepare url for the HTTP request.
153
prepareUrl :: (RpcCall a) => Node -> a -> String
154
prepareUrl node call =
155
  let node_ip = nodePrimaryIp node
156
      node_address = if isIpV6 node_ip
157
                     then "[" ++ node_ip ++ "]"
158
                     else node_ip
159
      port = C.defaultNodedPort
160
      path_prefix = "https://" ++ node_address ++ ":" ++ 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
-- | Execute RPC call for many nodes in parallel.
203
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
204
executeRpcCall nodes call = do
205
  cert_file <- P.nodedCertFile
206
  let opts = [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
207
             , CurlSSLCert cert_file
208
             , CurlSSLKey cert_file
209
             , CurlCAInfo cert_file
210
             ]
211
      opts_urls = map (\n ->
212
                         case prepareHttpRequest opts n call of
213
                           Left v -> Left v
214
                           Right request ->
215
                             Right (CurlPostFields [requestData request]:
216
                                    requestOpts request,
217
                                    requestUrl request)
218
                      ) nodes
219
  -- split the opts_urls list; we don't want to pass the
220
  -- failed-already nodes to Curl
221
  let (lefts, rights, trail) = splitEithers opts_urls
222
  results <- execMultiCall rights
223
  results' <- case recombineEithers lefts results trail of
224
                Bad msg -> error msg
225
                Ok r -> return r
226
  -- now parse the replies
227
  let results'' = map (parseHttpReply call) results'
228
      pairedList = zip nodes results''
229
  logRpcErrors pairedList
230
  return pairedList
231

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

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

    
247
-- | Helper function transforming JSValue to Rpc result type.
248
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
249
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
250

    
251
-- * RPC calls and results
252

    
253
-- ** Instance info
254

    
255
-- | InstanceInfo
256
--   Returns information about a single instance.
257

    
258
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
259
  [ simpleField "instance" [t| String |]
260
  , simpleField "hname" [t| Hypervisor |]
261
  ])
262

    
263
$(buildObject "InstanceInfo" "instInfo"
264
  [ simpleField "memory" [t| Int|]
265
  , simpleField "state"  [t| String |] -- It depends on hypervisor :(
266
  , simpleField "vcpus"  [t| Int |]
267
  , simpleField "time"   [t| Int |]
268
  ])
269

    
270
-- This is optional here because the result may be empty if instance is
271
-- not on a node - and this is not considered an error.
272
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
273
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
274

    
275
instance RpcCall RpcCallInstanceInfo where
276
  rpcCallName _          = "instance_info"
277
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
278
  rpcCallAcceptOffline _ = False
279
  rpcCallData _ call     = J.encode
280
    ( rpcCallInstInfoInstance call
281
    , rpcCallInstInfoHname call
282
    )
283

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

    
294
-- ** AllInstancesInfo
295

    
296
-- | AllInstancesInfo
297
--   Returns information about all running instances on the given nodes
298
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
299
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
300

    
301
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
302
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
303

    
304
instance RpcCall RpcCallAllInstancesInfo where
305
  rpcCallName _          = "all_instances_info"
306
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
307
  rpcCallAcceptOffline _ = False
308
  rpcCallData _ call     = J.encode [rpcCallAllInstInfoHypervisors call]
309

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

    
323
-- ** InstanceList
324

    
325
-- | InstanceList
326
-- Returns the list of running instances on the given nodes.
327
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
328
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
329

    
330
$(buildObject "RpcResultInstanceList" "rpcResInstList"
331
  [ simpleField "instances" [t| [String] |] ])
332

    
333
instance RpcCall RpcCallInstanceList where
334
  rpcCallName _          = "instance_list"
335
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
336
  rpcCallAcceptOffline _ = False
337
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
338

    
339
instance Rpc RpcCallInstanceList RpcResultInstanceList where
340
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
341

    
342
-- ** NodeInfo
343

    
344
-- | NodeInfo
345
-- Return node information.
346
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
347
  [ simpleField "storage_units" [t| Map.Map String [StorageUnit] |]
348
  , simpleField "hypervisors" [t| [ (Hypervisor, HvParams) ] |]
349
  ])
350

    
351
$(buildObject "StorageInfo" "storageInfo"
352
  [ simpleField "name" [t| String |]
353
  , simpleField "type" [t| String |]
354
  , optionalField $ simpleField "storage_free" [t| Int |]
355
  , optionalField $ simpleField "storage_size" [t| Int |]
356
  ])
357

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

    
369
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
370
  [ simpleField "boot_id" [t| String |]
371
  , simpleField "storage_info" [t| [StorageInfo] |]
372
  , simpleField "hv_info" [t| [HvInfo] |]
373
  ])
374

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

    
386
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
387
  rpcResultFill _ res =
388
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
389

    
390
-- ** Version
391

    
392
-- | Query node version.
393
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
394

    
395
-- | Query node reply.
396
$(buildObject "RpcResultVersion" "rpcResultVersion"
397
  [ simpleField "version" [t| Int |]
398
  ])
399

    
400
instance RpcCall RpcCallVersion where
401
  rpcCallName _          = "version"
402
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
403
  rpcCallAcceptOffline _ = True
404
  rpcCallData _          = J.encode
405

    
406
instance Rpc RpcCallVersion RpcResultVersion where
407
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
408

    
409
-- ** StorageList
410

    
411
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
412
  [ simpleField "su_name" [t| StorageType |]
413
  , simpleField "su_args" [t| [String] |]
414
  , simpleField "name"    [t| String |]
415
  , simpleField "fields"  [t| [StorageField] |]
416
  ])
417

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

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

    
434
instance Rpc RpcCallStorageList RpcResultStorageList where
435
  rpcResultFill call res =
436
    let sfields = rpcCallStorageListFields call in
437
    fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
438

    
439
-- ** TestDelay
440

    
441
-- | Call definition for test delay.
442
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
443
  [ simpleField "duration" [t| Double |]
444
  ])
445

    
446
-- | Result definition for test delay.
447
data RpcResultTestDelay = RpcResultTestDelay
448
                          deriving Show
449

    
450
-- | Custom JSON instance for null result.
451
instance J.JSON RpcResultTestDelay where
452
  showJSON _        = J.JSNull
453
  readJSON J.JSNull = return RpcResultTestDelay
454
  readJSON _        = fail "Unable to read RpcResultTestDelay"
455

    
456
instance RpcCall RpcCallTestDelay where
457
  rpcCallName _          = "test_delay"
458
  rpcCallTimeout         = ceiling . (+ 5) . rpcCallTestDelayDuration
459
  rpcCallAcceptOffline _ = False
460
  rpcCallData _ call     = J.encode [rpcCallTestDelayDuration call]
461

    
462
instance Rpc RpcCallTestDelay RpcResultTestDelay where
463
  rpcResultFill _ res = fromJSValueToRes res id
464

    
465
-- ** ExportList
466

    
467
-- | Call definition for export list.
468

    
469
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
470

    
471
-- | Result definition for export list.
472
$(buildObject "RpcResultExportList" "rpcResExportList"
473
  [ simpleField "exports" [t| [String] |]
474
  ])
475

    
476
instance RpcCall RpcCallExportList where
477
  rpcCallName _          = "export_list"
478
  rpcCallTimeout _       = rpcTimeoutToRaw Fast
479
  rpcCallAcceptOffline _ = False
480
  rpcCallData _          = J.encode
481

    
482
instance Rpc RpcCallExportList RpcResultExportList where
483
  rpcResultFill _ res = fromJSValueToRes res RpcResultExportList