Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Rpc.hs @ 08f7d24d

History | View | Annotate | Download (15.1 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 Ganeti.BasicTypes
82
import qualified Ganeti.Constants as C
83
import Ganeti.Objects
84
import Ganeti.THH
85
import Ganeti.Types
86
import Ganeti.Curl.Multi
87
import Ganeti.Utils
88

    
89
-- * Base RPC functionality and types
90

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

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

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

    
120
type ERpcError = Either RpcError
121

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

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

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

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

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

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

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

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

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

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

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

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

    
241
-- * RPC calls and results
242

    
243
-- ** Instance info
244

    
245
-- | InstanceInfo
246
--   Returns information about a single instance.
247

    
248
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
249
  [ simpleField "instance" [t| String |]
250
  , simpleField "hname" [t| Hypervisor |]
251
  ])
252

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

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

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

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

    
284
-- ** AllInstancesInfo
285

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

    
291
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
292
  [ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
293

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

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

    
313
-- ** InstanceList
314

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

    
320
$(buildObject "RpcResultInstanceList" "rpcResInstList"
321
  [ simpleField "instances" [t| [String] |] ])
322

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

    
329
instance Rpc RpcCallInstanceList RpcResultInstanceList where
330
  rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
331

    
332
-- ** NodeInfo
333

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

    
342
$(buildObject "VgInfo" "vgInfo"
343
  [ simpleField "name" [t| String |]
344
  , optionalField $ simpleField "vg_free" [t| Int |]
345
  , optionalField $ simpleField "vg_size" [t| Int |]
346
  ])
347

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

    
358
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
359
  [ simpleField "boot_id" [t| String |]
360
  , simpleField "vg_info" [t| [VgInfo] |]
361
  , simpleField "hv_info" [t| [HvInfo] |]
362
  ])
363

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

    
376
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
377
  rpcResultFill _ res =
378
    fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
379

    
380
-- ** Version
381

    
382
-- | Query node version.
383
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
384

    
385
-- | Query node reply.
386
$(buildObject "RpcResultVersion" "rpcResultVersion"
387
  [ simpleField "version" [t| Int |]
388
  ])
389

    
390
instance RpcCall RpcCallVersion where
391
  rpcCallName _          = "version"
392
  rpcCallTimeout _       = rpcTimeoutToRaw Urgent
393
  rpcCallAcceptOffline _ = True
394
  rpcCallData _          = J.encode
395

    
396
instance Rpc RpcCallVersion RpcResultVersion where
397
  rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
398

    
399
-- ** StorageList
400

    
401
-- | StorageList
402

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

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

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

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

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

    
441
-- ** TestDelay
442

    
443

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

    
449
-- | Result definition for test delay.
450
data RpcResultTestDelay = RpcResultTestDelay
451
                          deriving Show
452

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

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

    
465
instance Rpc RpcCallTestDelay RpcResultTestDelay where
466
  rpcResultFill _ res = fromJSValueToRes res id