Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 85f6a869

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

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

    
42
  , rpcResultFill
43

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

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

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

    
54
  , HvInfo(..)
55
  , VgInfo(..)
56
  , RpcCallNodeInfo(..)
57
  , RpcResultNodeInfo(..)
58

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

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

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

    
69
  , rpcTimeoutFromRaw -- FIXME: Not used anywhere
70
  ) where
71

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

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

    
81
import qualified Ganeti.Constants as C
82
import Ganeti.Objects
83
import Ganeti.THH
84
import Ganeti.Types
85
import Ganeti.Compat
86

    
87
-- * Base RPC functionality and types
88

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

    
99
-- | Data type for RPC error reporting.
100
data RpcError
101
  = CurlLayerError Node String
102
  | JsonDecodeError String
103
  | RpcResultError String
104
  | OfflineNodeError Node
105
  deriving (Show, Eq)
106

    
107
-- | Provide explanation to RPC errors.
108
explainRpcError :: RpcError -> String
109
explainRpcError (CurlLayerError node code) =
110
    "Curl error for " ++ nodeName node ++ ", " ++ code
111
explainRpcError (JsonDecodeError msg) =
112
    "Error while decoding JSON from HTTP response: " ++ msg
113
explainRpcError (RpcResultError msg) =
114
    "Error reponse received from RPC server: " ++ msg
115
explainRpcError (OfflineNodeError node) =
116
    "Node " ++ nodeName node ++ " is marked as offline"
117

    
118
type ERpcError = Either RpcError
119

    
120
-- | Basic timeouts for RPC calls.
121
$(declareIADT "RpcTimeout"
122
  [ ( "Urgent",    'C.rpcTmoUrgent )
123
  , ( "Fast",      'C.rpcTmoFast )
124
  , ( "Normal",    'C.rpcTmoNormal )
125
  , ( "Slow",      'C.rpcTmoSlow )
126
  , ( "FourHours", 'C.rpcTmo4hrs )
127
  , ( "OneDay",    'C.rpcTmo1day )
128
  ])
129

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

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

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

    
154
-- | Execute the request and return the result as a plain String. When
155
-- curl reports an error, we propagate it.
156
executeHttpRequest :: Node -> ERpcError HttpClientRequest
157
                   -> IO (ERpcError String)
158
executeHttpRequest _ (Left rpc_err) = return $ Left rpc_err
159
executeHttpRequest node (Right request) = do
160
  let reqOpts = CurlPostFields [requestData request]:requestOpts request
161
      url = requestUrl request
162
  -- FIXME: This is very similar to getUrl in Htools/Rapi.hs
163
  (code, !body) <- curlGetString url $ curlOpts ++ reqOpts
164
  return $ case code of
165
             CurlOK -> Right body
166
             _ -> Left $ CurlLayerError node (show code)
167

    
168
-- | Prepare url for the HTTP request.
169
prepareUrl :: (RpcCall a) => Node -> a -> String
170
prepareUrl node call =
171
  let node_ip = nodePrimaryIp node
172
      port = snd C.daemonsPortsGanetiNoded
173
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
174
  in path_prefix ++ "/" ++ rpcCallName call
175

    
176
-- | Create HTTP request for a given node provided it is online,
177
-- otherwise create empty response.
178
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
179
                   -> ERpcError HttpClientRequest
180
prepareHttpRequest opts node call
181
  | rpcCallAcceptOffline call || not (nodeOffline node) =
182
      Right HttpClientRequest { requestUrl  = prepareUrl node call
183
                              , requestData = rpcCallData node call
184
                              , requestOpts = opts ++ curlOpts
185
                              }
186
  | otherwise = Left $ OfflineNodeError node
187

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

    
199
-- | Execute RPC call for a sigle node.
200
executeSingleRpcCall :: (Rpc a b) =>
201
                        [CurlOption] -> Node -> a -> IO (Node, ERpcError b)
202
executeSingleRpcCall opts node call = do
203
  let request = prepareHttpRequest opts node call
204
  response <- executeHttpRequest node request
205
  let result = parseHttpResponse call response
206
  return (node, result)
207

    
208
-- | Execute RPC call for many nodes in parallel.
209
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
210
executeRpcCall nodes call = do
211
  cert_file <- P.nodedCertFile
212
  let opts = [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
213
             , CurlSSLCert cert_file
214
             , CurlSSLKey cert_file
215
             , CurlCAInfo cert_file
216
             ]
217
  sequence $ parMap rwhnf (\n -> executeSingleRpcCall opts n call) nodes
218

    
219
-- | Helper function that is used to read dictionaries of values.
220
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
221
sanitizeDictResults =
222
  foldr sanitize1 (Right [])
223
  where
224
    sanitize1 _ (Left e) = Left e
225
    sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
226
    sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
227

    
228
-- | Helper function to tranform JSON Result to Either RpcError b.
229
-- Note: For now we really only use it for b s.t. Rpc c b for some c
230
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
231
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
232
fromJResultToRes (J.Ok v) f = Right $ f v
233

    
234
-- | Helper function transforming JSValue to Rpc result type.
235
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
236
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
237

    
238
-- * RPC calls and results
239

    
240
-- ** Instance info
241

    
242
-- | InstanceInfo
243
--   Returns information about a single instance.
244

    
245
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
246
  [ simpleField "instance" [t| String |]
247
  , simpleField "hname" [t| Hypervisor |]
248
  ])
249

    
250
$(buildObject "InstanceInfo" "instInfo"
251
  [ simpleField "memory" [t| Int|]
252
  , simpleField "state"  [t| String |] -- It depends on hypervisor :(
253
  , simpleField "vcpus"  [t| Int |]
254
  , simpleField "time"   [t| Int |]
255
  ])
256

    
257
-- This is optional here because the result may be empty if instance is
258
-- not on a node - and this is not considered an error.
259
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
260
  [ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
261

    
262
instance RpcCall RpcCallInstanceInfo where
263
  rpcCallName _          = "instance_info"
264
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
265
  rpcCallAcceptOffline _ = False
266
  rpcCallData _ call     = J.encode
267
    ( rpcCallInstInfoInstance call
268
    , rpcCallInstInfoHname call
269
    )
270

    
271
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
272
  rpcResultFill _ res =
273
    case res of
274
      J.JSObject res' ->
275
        case J.fromJSObject res' of
276
          [] -> Right $ RpcResultInstanceInfo Nothing
277
          _ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
278
      _ -> Left $ JsonDecodeError
279
           ("Expected JSObject, got " ++ show (pp_value res))
280

    
281
-- ** AllInstancesInfo
282

    
283
-- | AllInstancesInfo
284
--   Returns information about all running instances on the given nodes
285
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
286
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
287

    
288
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
289
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
290

    
291
instance RpcCall RpcCallAllInstancesInfo where
292
  rpcCallName _          = "all_instances_info"
293
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
294
  rpcCallAcceptOffline _ = False
295
  rpcCallData _ call     = J.encode [rpcCallAllInstInfoHypervisors call]
296

    
297
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
298
  -- FIXME: Is there a simpler way to do it?
299
  rpcResultFill _ res =
300
    case res of
301
      J.JSObject res' ->
302
        let res'' = map (second J.readJSON) (J.fromJSObject res')
303
                        :: [(String, J.Result InstanceInfo)] in
304
        case sanitizeDictResults res'' of
305
          Left err -> Left err
306
          Right insts -> Right $ RpcResultAllInstancesInfo insts
307
      _ -> Left $ JsonDecodeError
308
           ("Expected JSObject, got " ++ show (pp_value res))
309

    
310
-- ** InstanceList
311

    
312
-- | InstanceList
313
-- Returns the list of running instances on the given nodes.
314
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
315
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
316

    
317
$(buildObject "RpcResultInstanceList" "rpcResInstList"
318
  [ simpleField "instances" [t| [String] |] ])
319

    
320
instance RpcCall RpcCallInstanceList where
321
  rpcCallName _          = "instance_list"
322
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
323
  rpcCallAcceptOffline _ = False
324
  rpcCallData _ call     = J.encode [rpcCallInstListHypervisors call]
325

    
326
instance Rpc RpcCallInstanceList RpcResultInstanceList where
327
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
328

    
329
-- ** NodeInfo
330

    
331
-- | NodeInfo
332
-- Return node information.
333
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
334
  [ simpleField "volume_groups" [t| [String] |]
335
  , simpleField "hypervisors" [t| [Hypervisor] |]
336
  , simpleField "exclusive_storage" [t| Map.Map String Bool |]
337
  ])
338

    
339
$(buildObject "VgInfo" "vgInfo"
340
  [ simpleField "name" [t| String |]
341
  , optionalField $ simpleField "vg_free" [t| Int |]
342
  , optionalField $ simpleField "vg_size" [t| Int |]
343
  ])
344

    
345
-- | We only provide common fields as described in hv_base.py.
346
$(buildObject "HvInfo" "hvInfo"
347
  [ simpleField "memory_total" [t| Int |]
348
  , simpleField "memory_free" [t| Int |]
349
  , simpleField "memory_dom0" [t| Int |]
350
  , simpleField "cpu_total" [t| Int |]
351
  , simpleField "cpu_nodes" [t| Int |]
352
  , simpleField "cpu_sockets" [t| Int |]
353
  ])
354

    
355
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
356
  [ simpleField "boot_id" [t| String |]
357
  , simpleField "vg_info" [t| [VgInfo] |]
358
  , simpleField "hv_info" [t| [HvInfo] |]
359
  ])
360

    
361
instance RpcCall RpcCallNodeInfo where
362
  rpcCallName _          = "node_info"
363
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
364
  rpcCallAcceptOffline _ = False
365
  rpcCallData n call     = J.encode
366
    ( rpcCallNodeInfoVolumeGroups call
367
    , rpcCallNodeInfoHypervisors call
368
    , fromMaybe (error $ "Programmer error: missing parameter for node named "
369
                         ++ nodeName n)
370
                $ Map.lookup (nodeName n) (rpcCallNodeInfoExclusiveStorage call)
371
    )
372

    
373
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
374
  rpcResultFill _ res =
375
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
376

    
377
-- ** Version
378

    
379
-- | Version
380
-- Query node version.
381
-- Note: We can't use THH as it does not know what to do with empty dict
382
data RpcCallVersion = RpcCallVersion {}
383
  deriving (Show, Eq)
384

    
385
instance J.JSON RpcCallVersion where
386
  showJSON _ = J.JSNull
387
  readJSON J.JSNull = return RpcCallVersion
388
  readJSON _ = fail "Unable to read RpcCallVersion"
389

    
390
$(buildObject "RpcResultVersion" "rpcResultVersion"
391
  [ simpleField "version" [t| Int |]
392
  ])
393

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

    
400
instance Rpc RpcCallVersion RpcResultVersion where
401
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
402

    
403
-- ** StorageList
404

    
405
-- | StorageList
406

    
407
-- FIXME: This may be moved to Objects
408
$(declareSADT "StorageField"
409
  [ ( "SFUsed",        'C.sfUsed)
410
  , ( "SFName",        'C.sfName)
411
  , ( "SFAllocatable", 'C.sfAllocatable)
412
  , ( "SFFree",        'C.sfFree)
413
  , ( "SFSize",        'C.sfSize)
414
  ])
415
$(makeJSONInstance ''StorageField)
416

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

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

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

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

    
445
-- ** TestDelay
446

    
447

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

    
453
-- | Result definition for test delay.
454
data RpcResultTestDelay = RpcResultTestDelay
455
                          deriving Show
456

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

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

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