Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Rpc.hs @ 5188fdb7

History | View | Annotate | Download (14.4 kB)

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

    
4
{-| Implementation of the RPC client.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2012 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
  , executeRpcCall
35

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

    
41
  , rpcResultFill
42

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

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

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

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

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

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

    
66
  , rpcTimeoutFromRaw -- FIXME: Not used anywhere
67
  ) where
68

    
69
import Control.Arrow (second)
70
import qualified Text.JSON as J
71
import Text.JSON.Pretty (pp_value)
72
import Text.JSON (makeObj)
73

    
74
#ifndef NO_CURL
75
import Network.Curl
76
import qualified Ganeti.Path as P
77
#endif
78

    
79
import qualified Ganeti.Constants as C
80
import Ganeti.Objects
81
import Ganeti.THH
82
import Ganeti.Compat
83
import Ganeti.JSON
84

    
85
#ifndef NO_CURL
86
-- | The curl options used for RPC.
87
curlOpts :: [CurlOption]
88
curlOpts = [ CurlFollowLocation False
89
           , CurlCAInfo P.nodedCertFile
90
           , CurlSSLVerifyHost 0
91
           , CurlSSLVerifyPeer True
92
           , CurlSSLCertType "PEM"
93
           , CurlSSLCert P.nodedCertFile
94
           , CurlSSLKeyType "PEM"
95
           , CurlSSLKey P.nodedCertFile
96
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
97
           ]
98
#endif
99

    
100
-- | Data type for RPC error reporting.
101
data RpcError
102
  = CurlDisabledError
103
  | CurlLayerError Node String
104
  | JsonDecodeError String
105
  | RpcResultError String
106
  | OfflineNodeError Node
107
  deriving Eq
108

    
109
instance Show RpcError where
110
  show CurlDisabledError =
111
    "RPC/curl backend disabled at compile time"
112
  show (CurlLayerError node code) =
113
    "Curl error for " ++ nodeName node ++ ", " ++ code
114
  show (JsonDecodeError msg) =
115
    "Error while decoding JSON from HTTP response: " ++ msg
116
  show (RpcResultError msg) =
117
    "Error reponse received from RPC server: " ++ msg
118
  show (OfflineNodeError node) =
119
    "Node " ++ nodeName node ++ " is marked as offline"
120

    
121
type ERpcError = Either RpcError
122

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

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

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

    
150
-- | Http Request definition.
151
data HttpClientRequest = HttpClientRequest
152
  { requestTimeout :: Int
153
  , requestUrl :: String
154
  , requestPostData :: String
155
  }
156

    
157
-- | Execute the request and return the result as a plain String. When
158
-- curl reports an error, we propagate it.
159
executeHttpRequest :: Node -> ERpcError HttpClientRequest
160
                   -> IO (ERpcError String)
161

    
162
executeHttpRequest _ (Left rpc_err) = return $ Left rpc_err
163
#ifdef NO_CURL
164
executeHttpRequest _ _ = return $ Left CurlDisabledError
165
#else
166
executeHttpRequest node (Right request) = do
167
  let reqOpts = [ CurlTimeout (fromIntegral $ requestTimeout request)
168
                , CurlPostFields [requestPostData request]
169
                ]
170
      url = requestUrl request
171
  -- FIXME: This is very similar to getUrl in Htools/Rapi.hs
172
  (code, !body) <- curlGetString url $ curlOpts ++ reqOpts
173
  return $ case code of
174
             CurlOK -> Right body
175
             _ -> Left $ CurlLayerError node (show code)
176
#endif
177

    
178
-- | Prepare url for the HTTP request.
179
prepareUrl :: (RpcCall a) => Node -> a -> String
180
prepareUrl node call =
181
  let node_ip = nodePrimaryIp node
182
      port = snd C.daemonsPortsGanetiNoded
183
      path_prefix = "https://" ++ node_ip ++ ":" ++ show port
184
  in path_prefix ++ "/" ++ rpcCallName call
185

    
186
-- | Create HTTP request for a given node provided it is online,
187
-- otherwise create empty response.
188
prepareHttpRequest ::  (RpcCall a) => Node -> a
189
                   -> ERpcError HttpClientRequest
190
prepareHttpRequest node call
191
  | rpcCallAcceptOffline call || not (nodeOffline node) =
192
      Right HttpClientRequest { requestTimeout = rpcCallTimeout call
193
                              , requestUrl = prepareUrl node call
194
                              , requestPostData = rpcCallData node call
195
                              }
196
  | otherwise = Left $ OfflineNodeError node
197

    
198
-- | Parse a result based on the received HTTP response.
199
rpcResultParse :: (Monad m, Rpc a b) => a -> String -> m (ERpcError b)
200
rpcResultParse call res = do
201
  res' <- fromJResult "Reading JSON response" $ J.decode res
202
  case res' of
203
    (True, res'') ->
204
       rpcResultFill call res''
205
    (False, jerr) -> case jerr of
206
       J.JSString msg -> return . Left $ RpcResultError (J.fromJSString msg)
207
       _ -> (return . Left) . JsonDecodeError $ show (pp_value jerr)
208

    
209
-- | Parse the response or propagate the error.
210
parseHttpResponse :: (Rpc a b) => a -> ERpcError String -> IO (ERpcError b)
211
parseHttpResponse _ (Left err) = return $ Left err
212
parseHttpResponse call (Right response) = rpcResultParse call response
213

    
214
-- | Execute RPC call for a sigle node.
215
executeSingleRpcCall :: (Rpc a b) => Node -> a -> IO (Node, ERpcError b)
216
executeSingleRpcCall node call = do
217
  let request = prepareHttpRequest node call
218
  response <- executeHttpRequest node request
219
  result <- parseHttpResponse call response
220
  return (node, result)
221

    
222
-- | Execute RPC call for many nodes in parallel.
223
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
224
executeRpcCall nodes call =
225
  sequence $ parMap rwhnf (uncurry executeSingleRpcCall)
226
               (zip nodes $ repeat call)
227

    
228
-- | Helper function that is used to read dictionaries of values.
229
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
230
sanitizeDictResults [] = Right []
231
sanitizeDictResults ((_, J.Error err):_) = Left $ JsonDecodeError err
232
sanitizeDictResults ((name, J.Ok val):xs) =
233
  case sanitizeDictResults xs of
234
    Left err -> Left err
235
    Right res' -> Right $ (name, val):res'
236

    
237
-- * RPC calls and results
238

    
239
-- | InstanceInfo
240
--   Returns information about a single instance.
241

    
242
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
243
  [ simpleField "instance" [t| String |]
244
  , simpleField "hname" [t| Hypervisor |]
245
  ])
246

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

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

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

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

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

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

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

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

    
308
-- | InstanceList
309
-- Returns the list of running instances on the given nodes.
310
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
311
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
312

    
313
$(buildObject "RpcResultInstanceList" "rpcResInstList"
314
  [ simpleField "instances" [t| [String] |] ])
315

    
316
instance RpcCall RpcCallInstanceList where
317
  rpcCallName _ = "instance_list"
318
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
319
  rpcCallAcceptOffline _ = False
320
  rpcCallData _ call = J.encode [rpcCallInstListHypervisors call]
321

    
322

    
323
instance Rpc RpcCallInstanceList RpcResultInstanceList where
324
  rpcResultFill _ res =
325
    return $ case J.readJSON res of
326
      J.Error err -> Left $ JsonDecodeError err
327
      J.Ok insts -> Right $ RpcResultInstanceList insts
328

    
329
-- | NodeInfo
330
-- Return node information.
331
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
332
  [ simpleField "volume_groups" [t| [String] |]
333
  , simpleField "hypervisors" [t| [Hypervisor] |]
334
  ])
335

    
336
$(buildObject "VgInfo" "vgInfo"
337
  [ simpleField "name" [t| String |]
338
  , optionalField $ simpleField "vg_free" [t| Int |]
339
  , optionalField $ simpleField "vg_size" [t| Int |]
340
  ])
341

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

    
352
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
353
  [ simpleField "boot_id" [t| String |]
354
  , simpleField "vg_info" [t| [VgInfo] |]
355
  , simpleField "hv_info" [t| [HvInfo] |]
356
  ])
357

    
358
instance RpcCall RpcCallNodeInfo where
359
  rpcCallName _ = "node_info"
360
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
361
  rpcCallAcceptOffline _ = False
362
  rpcCallData _ call = J.encode ( rpcCallNodeInfoVolumeGroups call
363
                                , rpcCallNodeInfoHypervisors call
364
                                )
365

    
366
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
367
  rpcResultFill _ res =
368
    return $ case J.readJSON res of
369
      J.Error err -> Left $ JsonDecodeError err
370
      J.Ok (boot_id, vg_info, hv_info) ->
371
          Right $ RpcResultNodeInfo boot_id vg_info hv_info
372

    
373
-- | Version
374
-- Query node version.
375
-- Note: We can't use THH as it does not know what to do with empty dict
376
data RpcCallVersion = RpcCallVersion {}
377
  deriving (Show, Read, Eq)
378

    
379
instance J.JSON RpcCallVersion where
380
  showJSON _ = J.JSNull
381
  readJSON J.JSNull = return RpcCallVersion
382
  readJSON _ = fail "Unable to read RpcCallVersion"
383

    
384
$(buildObject "RpcResultVersion" "rpcResultVersion"
385
  [ simpleField "version" [t| Int |]
386
  ])
387

    
388
instance RpcCall RpcCallVersion where
389
  rpcCallName _ = "version"
390
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
391
  rpcCallAcceptOffline _ = True
392
  rpcCallData call _ = J.encode [call]
393

    
394
instance Rpc RpcCallVersion RpcResultVersion where
395
  rpcResultFill _ res =
396
    return $ case J.readJSON res of
397
      J.Error err -> Left $ JsonDecodeError err
398
      J.Ok ver -> Right $ RpcResultVersion ver
399

    
400
-- | StorageList
401
-- Get list of storage units.
402
-- FIXME: This may be moved to Objects
403
$(declareSADT "StorageType"
404
  [ ( "STLvmPv", 'C.stLvmPv )
405
  , ( "STFile",  'C.stFile )
406
  , ( "STLvmVg", 'C.stLvmVg )
407
  ])
408
$(makeJSONInstance ''StorageType)
409

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

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

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

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

    
443
instance Rpc RpcCallStorageList RpcResultStorageList where
444
  rpcResultFill call res =
445
    let sfields = rpcCallStorageListFields call in
446
    return $ case J.readJSON res of
447
      J.Error err -> Left $ JsonDecodeError err
448
      J.Ok res_lst -> Right $ RpcResultStorageList (map (zip sfields) res_lst)
449