Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Rpc.hs @ 6fddde87

History | View | Annotate | Download (9.1 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
  , RpcResult
32
  , Rpc
33
  , RpcError(..)
34
  , executeRpcCall
35

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

    
41
  , rpcResultFill
42

    
43
  , InstanceInfo(..)
44
  , RpcCallAllInstancesInfo(..)
45
  , RpcResultAllInstancesInfo(..)
46

    
47
  , RpcCallInstanceList(..)
48
  , RpcResultInstanceList(..)
49

    
50
  , HvInfo(..)
51
  , VgInfo(..)
52
  , RpcCallNodeInfo(..)
53
  , RpcResultNodeInfo(..)
54

    
55
  , rpcTimeoutFromRaw -- FIXME: Not used anywhere
56
  ) where
57

    
58
import qualified Text.JSON as J
59
import Text.JSON (makeObj)
60

    
61
#ifndef NO_CURL
62
import Network.Curl
63
import qualified Ganeti.Path as P
64
#endif
65

    
66
import qualified Ganeti.Constants as C
67
import Ganeti.Objects
68
import Ganeti.THH
69
import Ganeti.Compat
70
import Ganeti.JSON
71

    
72
#ifndef NO_CURL
73
-- | The curl options used for RPC.
74
curlOpts :: [CurlOption]
75
curlOpts = [ CurlFollowLocation False
76
           , CurlCAInfo P.nodedCertFile
77
           , CurlSSLVerifyHost 0
78
           , CurlSSLVerifyPeer True
79
           , CurlSSLCertType "PEM"
80
           , CurlSSLCert P.nodedCertFile
81
           , CurlSSLKeyType "PEM"
82
           , CurlSSLKey P.nodedCertFile
83
           , CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
84
           ]
85
#endif
86

    
87
-- | Data type for RPC error reporting.
88
data RpcError
89
  = CurlDisabledError
90
  | CurlLayerError Node String
91
  | JsonDecodeError String
92
  | RpcResultError String
93
  | OfflineNodeError Node
94
  deriving Eq
95

    
96
instance Show RpcError where
97
  show CurlDisabledError =
98
    "RPC/curl backend disabled at compile time"
99
  show (CurlLayerError node code) =
100
    "Curl error for " ++ nodeName node ++ ", " ++ code
101
  show (JsonDecodeError msg) =
102
    "Error while decoding JSON from HTTP response: " ++ msg
103
  show (RpcResultError msg) =
104
    "Error reponse received from RPC server: " ++ msg
105
  show (OfflineNodeError node) =
106
    "Node " ++ nodeName node ++ " is marked as offline"
107

    
108
rpcErrorJsonReport :: (Monad m) => J.Result a -> m (Either RpcError a)
109
rpcErrorJsonReport (J.Error x) = return . Left $ JsonDecodeError x
110
rpcErrorJsonReport (J.Ok x) = return $ Right x
111

    
112
-- | Basic timeouts for RPC calls.
113
$(declareIADT "RpcTimeout"
114
  [ ( "Urgent",    'C.rpcTmoUrgent )
115
  , ( "Fast",      'C.rpcTmoFast )
116
  , ( "Normal",    'C.rpcTmoNormal )
117
  , ( "Slow",      'C.rpcTmoSlow )
118
  , ( "FourHours", 'C.rpcTmo4hrs )
119
  , ( "OneDay",    'C.rpcTmo1day )
120
  ])
121

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

    
133
  rpcCallData _ = J.encode
134

    
135
-- | A generic class for RPC results with default implementation.
136
class (J.JSON a) => RpcResult a where
137
  -- | Create a result based on the received HTTP response.
138
  rpcResultFill :: (Monad m) => String -> m (Either RpcError a)
139

    
140
  rpcResultFill res = rpcErrorJsonReport $  J.decode res
141

    
142
-- | Generic class that ensures matching RPC call with its respective
143
-- result.
144
class (RpcCall a, RpcResult b) => Rpc a b | a -> b
145

    
146
-- | Http Request definition.
147
data HttpClientRequest = HttpClientRequest
148
  { requestTimeout :: Int
149
  , requestUrl :: String
150
  , requestPostData :: String
151
  }
152

    
153
-- | Execute the request and return the result as a plain String. When
154
-- curl reports an error, we propagate it.
155
executeHttpRequest :: Node -> Either RpcError HttpClientRequest
156
                   -> IO (Either RpcError String)
157

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

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

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

    
194
-- | Parse the response or propagate the error.
195
parseHttpResponse :: (Monad m, RpcResult a) => Either RpcError String
196
                  -> m (Either RpcError a)
197
parseHttpResponse (Left err) = return $ Left err
198
parseHttpResponse (Right response) = rpcResultFill response
199

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

    
208
-- | Execute RPC call for many nodes in parallel.
209
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, Either RpcError b)]
210
executeRpcCall nodes call =
211
  sequence $ parMap rwhnf (uncurry executeSingleRpcCall)
212
               (zip nodes $ repeat call)
213

    
214
-- * RPC calls and results
215

    
216
-- | AllInstancesInfo
217
--   Returns information about all instances on the given nodes
218
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
219
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
220

    
221
$(buildObject "InstanceInfo" "instInfo"
222
  [ simpleField "name"   [t| String |]
223
  , simpleField "memory" [t| Int|]
224
  , simpleField "state"  [t| AdminState |]
225
  , simpleField "vcpus"  [t| Int |]
226
  , simpleField "time"   [t| Int |]
227
  ])
228

    
229
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
230
  [ simpleField "instances" [t| [InstanceInfo] |] ])
231

    
232
instance RpcCall RpcCallAllInstancesInfo where
233
  rpcCallName _ = "all_instances_info"
234
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
235
  rpcCallAcceptOffline _ = False
236

    
237
instance RpcResult RpcResultAllInstancesInfo
238

    
239
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo
240

    
241
-- | InstanceList
242
-- Returns the list of running instances on the given nodes.
243
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
244
  [ simpleField "hypervisors" [t| [Hypervisor] |] ])
245

    
246
$(buildObject "RpcResultInstanceList" "rpcResInstList"
247
  [ simpleField "node"      [t| Node |]
248
  , simpleField "instances" [t| [String] |]
249
  ])
250

    
251
instance RpcCall RpcCallInstanceList where
252
  rpcCallName _ = "instance_list"
253
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
254
  rpcCallAcceptOffline _ = False
255

    
256
instance RpcResult RpcResultInstanceList
257

    
258
instance Rpc RpcCallInstanceList RpcResultInstanceList
259

    
260
-- | NodeInfo
261
-- Return node information.
262
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
263
  [ simpleField "hypervisors" [t| [Hypervisor] |]
264
  , simpleField "volume_groups" [t| [String] |]
265
  ])
266

    
267
$(buildObject "VgInfo" "vgInfo"
268
  [ simpleField "name" [t| String |]
269
  , simpleField "free" [t| Int |]
270
  , simpleField "size" [t| Int |]
271
  ])
272

    
273
-- | We only provide common fields as described in hv_base.py.
274
$(buildObject "HvInfo" "hvInfo"
275
  [ simpleField "memory_total" [t| Int |]
276
  , simpleField "memory_free" [t| Int |]
277
  , simpleField "memory_dom0" [t| Int |]
278
  , simpleField "cpu_total" [t| Int |]
279
  , simpleField "cpu_nodes" [t| Int |]
280
  , simpleField "cpu_sockets" [t| Int |]
281
  ])
282

    
283
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
284
  [ simpleField "boot_id" [t| String |]
285
  , simpleField "vg_info" [t| [VgInfo] |]
286
  , simpleField "hv_info" [t| [HvInfo] |]
287
  ])
288

    
289
instance RpcCall RpcCallNodeInfo where
290
  rpcCallName _ = "node_info"
291
  rpcCallTimeout _ = rpcTimeoutToRaw Urgent
292
  rpcCallAcceptOffline _ = False
293

    
294
instance RpcResult RpcResultNodeInfo
295

    
296
instance Rpc RpcCallNodeInfo RpcResultNodeInfo