module Ganeti.Rpc
( RpcCall
, Rpc
, RpcError(..)
, ERpcError
, explainRpcError
, executeRpcCall
, logRpcErrors
, rpcCallName
, rpcCallTimeout
, rpcCallData
, rpcCallAcceptOffline
, rpcResultFill
, InstanceInfo(..)
, RpcCallInstanceInfo(..)
, RpcResultInstanceInfo(..)
, RpcCallAllInstancesInfo(..)
, RpcResultAllInstancesInfo(..)
, RpcCallInstanceList(..)
, RpcResultInstanceList(..)
, HvInfo(..)
, VgInfo(..)
, RpcCallNodeInfo(..)
, RpcResultNodeInfo(..)
, RpcCallVersion(..)
, RpcResultVersion(..)
, StorageField(..)
, RpcCallStorageList(..)
, RpcResultStorageList(..)
, RpcCallTestDelay(..)
, RpcResultTestDelay(..)
, RpcCallExportList(..)
, RpcResultExportList(..)
, rpcTimeoutFromRaw
) where
import Control.Arrow (second)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import qualified Text.JSON as J
import Text.JSON.Pretty (pp_value)
import Network.Curl
import qualified Ganeti.Path as P
import Ganeti.BasicTypes
import qualified Ganeti.Constants as C
import Ganeti.Logging
import Ganeti.Objects
import Ganeti.THH
import Ganeti.Types
import Ganeti.Curl.Multi
import Ganeti.Utils
curlOpts :: [CurlOption]
curlOpts = [ CurlFollowLocation False
, CurlSSLVerifyHost 0
, CurlSSLVerifyPeer True
, CurlSSLCertType "PEM"
, CurlSSLKeyType "PEM"
, CurlConnectTimeout (fromIntegral C.rpcConnectTimeout)
]
data RpcError
= CurlLayerError String
| JsonDecodeError String
| RpcResultError String
| OfflineNodeError
deriving (Show, Eq)
explainRpcError :: RpcError -> String
explainRpcError (CurlLayerError code) =
"Curl error:" ++ code
explainRpcError (JsonDecodeError msg) =
"Error while decoding JSON from HTTP response: " ++ msg
explainRpcError (RpcResultError msg) =
"Error reponse received from RPC server: " ++ msg
explainRpcError OfflineNodeError =
"Node is marked offline"
type ERpcError = Either RpcError
$(declareIADT "RpcTimeout"
[ ( "Urgent", 'C.rpcTmoUrgent )
, ( "Fast", 'C.rpcTmoFast )
, ( "Normal", 'C.rpcTmoNormal )
, ( "Slow", 'C.rpcTmoSlow )
, ( "FourHours", 'C.rpcTmo4hrs )
, ( "OneDay", 'C.rpcTmo1day )
])
class (J.JSON a) => RpcCall a where
rpcCallName :: a -> String
rpcCallTimeout :: a -> Int
rpcCallData :: Node -> a -> String
rpcCallAcceptOffline :: a -> Bool
class (RpcCall a, J.JSON b) => Rpc a b | a -> b, b -> a where
rpcResultFill :: a -> J.JSValue -> ERpcError b
data HttpClientRequest = HttpClientRequest
{ requestUrl :: String
, requestData :: String
, requestOpts :: [CurlOption]
}
isIpV6 :: String -> Bool
isIpV6 = (':' `elem`)
prepareUrl :: (RpcCall a) => Node -> a -> String
prepareUrl node call =
let node_ip = nodePrimaryIp node
node_address = if isIpV6 node_ip
then "[" ++ node_ip ++ "]"
else node_ip
port = snd C.daemonsPortsGanetiNoded
path_prefix = "https://" ++ node_address ++ ":" ++ show port
in path_prefix ++ "/" ++ rpcCallName call
prepareHttpRequest :: (RpcCall a) => [CurlOption] -> Node -> a
-> ERpcError HttpClientRequest
prepareHttpRequest opts node call
| rpcCallAcceptOffline call || not (nodeOffline node) =
Right HttpClientRequest { requestUrl = prepareUrl node call
, requestData = rpcCallData node call
, requestOpts = opts ++ curlOpts
}
| otherwise = Left OfflineNodeError
parseHttpReply :: (Rpc a b) =>
a -> ERpcError (CurlCode, String) -> ERpcError b
parseHttpReply _ (Left e) = Left e
parseHttpReply call (Right (CurlOK, body)) = parseHttpResponse call body
parseHttpReply _ (Right (code, err)) =
Left . CurlLayerError $ "code: " ++ show code ++ ", explanation: " ++ err
parseHttpResponse :: (Rpc a b) => a -> String -> ERpcError b
parseHttpResponse call res =
case J.decode res of
J.Error val -> Left $ JsonDecodeError val
J.Ok (True, res'') -> rpcResultFill call res''
J.Ok (False, jerr) -> case jerr of
J.JSString msg -> Left $ RpcResultError (J.fromJSString msg)
_ -> Left . JsonDecodeError $ show (pp_value jerr)
logRpcErrors :: [(a, ERpcError b)] -> IO ()
logRpcErrors allElems =
let logOneRpcErr (_, Right _) = return ()
logOneRpcErr (_, Left err) =
logError $ "Error in the RPC HTTP reply: " ++ show err
in mapM_ logOneRpcErr allElems
executeRpcCall :: (Rpc a b) => [Node] -> a -> IO [(Node, ERpcError b)]
executeRpcCall nodes call = do
cert_file <- P.nodedCertFile
let opts = [ CurlTimeout (fromIntegral $ rpcCallTimeout call)
, CurlSSLCert cert_file
, CurlSSLKey cert_file
, CurlCAInfo cert_file
]
opts_urls = map (\n ->
case prepareHttpRequest opts n call of
Left v -> Left v
Right request ->
Right (CurlPostFields [requestData request]:
requestOpts request,
requestUrl request)
) nodes
let (lefts, rights, trail) = splitEithers opts_urls
results <- execMultiCall rights
results' <- case recombineEithers lefts results trail of
Bad msg -> error msg
Ok r -> return r
let results'' = map (parseHttpReply call) results'
pairedList = zip nodes results''
logRpcErrors pairedList
return pairedList
sanitizeDictResults :: [(String, J.Result a)] -> ERpcError [(String, a)]
sanitizeDictResults =
foldr sanitize1 (Right [])
where
sanitize1 _ (Left e) = Left e
sanitize1 (_, J.Error e) _ = Left $ JsonDecodeError e
sanitize1 (name, J.Ok v) (Right res) = Right $ (name, v) : res
fromJResultToRes :: J.Result a -> (a -> b) -> ERpcError b
fromJResultToRes (J.Error v) _ = Left $ JsonDecodeError v
fromJResultToRes (J.Ok v) f = Right $ f v
fromJSValueToRes :: (J.JSON a) => J.JSValue -> (a -> b) -> ERpcError b
fromJSValueToRes val = fromJResultToRes (J.readJSON val)
$(buildObject "RpcCallInstanceInfo" "rpcCallInstInfo"
[ simpleField "instance" [t| String |]
, simpleField "hname" [t| Hypervisor |]
])
$(buildObject "InstanceInfo" "instInfo"
[ simpleField "memory" [t| Int|]
, simpleField "state" [t| String |]
, simpleField "vcpus" [t| Int |]
, simpleField "time" [t| Int |]
])
$(buildObject "RpcResultInstanceInfo" "rpcResInstInfo"
[ optionalField $ simpleField "inst_info" [t| InstanceInfo |]])
instance RpcCall RpcCallInstanceInfo where
rpcCallName _ = "instance_info"
rpcCallTimeout _ = rpcTimeoutToRaw Urgent
rpcCallAcceptOffline _ = False
rpcCallData _ call = J.encode
( rpcCallInstInfoInstance call
, rpcCallInstInfoHname call
)
instance Rpc RpcCallInstanceInfo RpcResultInstanceInfo where
rpcResultFill _ res =
case res of
J.JSObject res' ->
case J.fromJSObject res' of
[] -> Right $ RpcResultInstanceInfo Nothing
_ -> fromJSValueToRes res (RpcResultInstanceInfo . Just)
_ -> Left $ JsonDecodeError
("Expected JSObject, got " ++ show (pp_value res))
$(buildObject "RpcCallAllInstancesInfo" "rpcCallAllInstInfo"
[ simpleField "hypervisors" [t| [Hypervisor] |] ])
$(buildObject "RpcResultAllInstancesInfo" "rpcResAllInstInfo"
[ simpleField "instances" [t| [(String, InstanceInfo)] |] ])
instance RpcCall RpcCallAllInstancesInfo where
rpcCallName _ = "all_instances_info"
rpcCallTimeout _ = rpcTimeoutToRaw Urgent
rpcCallAcceptOffline _ = False
rpcCallData _ call = J.encode [rpcCallAllInstInfoHypervisors call]
instance Rpc RpcCallAllInstancesInfo RpcResultAllInstancesInfo where
rpcResultFill _ res =
case res of
J.JSObject res' ->
let res'' = map (second J.readJSON) (J.fromJSObject res')
:: [(String, J.Result InstanceInfo)] in
case sanitizeDictResults res'' of
Left err -> Left err
Right insts -> Right $ RpcResultAllInstancesInfo insts
_ -> Left $ JsonDecodeError
("Expected JSObject, got " ++ show (pp_value res))
$(buildObject "RpcCallInstanceList" "rpcCallInstList"
[ simpleField "hypervisors" [t| [Hypervisor] |] ])
$(buildObject "RpcResultInstanceList" "rpcResInstList"
[ simpleField "instances" [t| [String] |] ])
instance RpcCall RpcCallInstanceList where
rpcCallName _ = "instance_list"
rpcCallTimeout _ = rpcTimeoutToRaw Urgent
rpcCallAcceptOffline _ = False
rpcCallData _ call = J.encode [rpcCallInstListHypervisors call]
instance Rpc RpcCallInstanceList RpcResultInstanceList where
rpcResultFill _ res = fromJSValueToRes res RpcResultInstanceList
$(buildObject "RpcCallNodeInfo" "rpcCallNodeInfo"
[ simpleField "volume_groups" [t| [String] |]
, simpleField "hypervisors" [t| [Hypervisor] |]
, simpleField "exclusive_storage" [t| Map.Map String Bool |]
])
$(buildObject "VgInfo" "vgInfo"
[ simpleField "name" [t| String |]
, optionalField $ simpleField "vg_free" [t| Int |]
, optionalField $ simpleField "vg_size" [t| Int |]
])
$(buildObject "HvInfo" "hvInfo"
[ simpleField "memory_total" [t| Int |]
, simpleField "memory_free" [t| Int |]
, simpleField "memory_dom0" [t| Int |]
, simpleField "cpu_total" [t| Int |]
, simpleField "cpu_nodes" [t| Int |]
, simpleField "cpu_sockets" [t| Int |]
])
$(buildObject "RpcResultNodeInfo" "rpcResNodeInfo"
[ simpleField "boot_id" [t| String |]
, simpleField "vg_info" [t| [VgInfo] |]
, simpleField "hv_info" [t| [HvInfo] |]
])
instance RpcCall RpcCallNodeInfo where
rpcCallName _ = "node_info"
rpcCallTimeout _ = rpcTimeoutToRaw Urgent
rpcCallAcceptOffline _ = False
rpcCallData n call = J.encode
( rpcCallNodeInfoVolumeGroups call
, rpcCallNodeInfoHypervisors call
, fromMaybe (error $ "Programmer error: missing parameter for node named "
++ nodeName n)
$ Map.lookup (nodeName n) (rpcCallNodeInfoExclusiveStorage call)
)
instance Rpc RpcCallNodeInfo RpcResultNodeInfo where
rpcResultFill _ res =
fromJSValueToRes res (\(b, vg, hv) -> RpcResultNodeInfo b vg hv)
$(buildObject "RpcCallVersion" "rpcCallVersion" [])
$(buildObject "RpcResultVersion" "rpcResultVersion"
[ simpleField "version" [t| Int |]
])
instance RpcCall RpcCallVersion where
rpcCallName _ = "version"
rpcCallTimeout _ = rpcTimeoutToRaw Urgent
rpcCallAcceptOffline _ = True
rpcCallData _ = J.encode
instance Rpc RpcCallVersion RpcResultVersion where
rpcResultFill _ res = fromJSValueToRes res RpcResultVersion
$(declareSADT "StorageField"
[ ( "SFUsed", 'C.sfUsed)
, ( "SFName", 'C.sfName)
, ( "SFAllocatable", 'C.sfAllocatable)
, ( "SFFree", 'C.sfFree)
, ( "SFSize", 'C.sfSize)
])
$(makeJSONInstance ''StorageField)
$(buildObject "RpcCallStorageList" "rpcCallStorageList"
[ simpleField "su_name" [t| StorageType |]
, simpleField "su_args" [t| [String] |]
, simpleField "name" [t| String |]
, simpleField "fields" [t| [StorageField] |]
])
$(buildObject "RpcResultStorageList" "rpcResStorageList"
[ simpleField "storage" [t| [[(StorageField, J.JSValue)]] |] ])
instance RpcCall RpcCallStorageList where
rpcCallName _ = "storage_list"
rpcCallTimeout _ = rpcTimeoutToRaw Normal
rpcCallAcceptOffline _ = False
rpcCallData _ call = J.encode
( rpcCallStorageListSuName call
, rpcCallStorageListSuArgs call
, rpcCallStorageListName call
, rpcCallStorageListFields call
)
instance Rpc RpcCallStorageList RpcResultStorageList where
rpcResultFill call res =
let sfields = rpcCallStorageListFields call in
fromJSValueToRes res (RpcResultStorageList . map (zip sfields))
$(buildObject "RpcCallTestDelay" "rpcCallTestDelay"
[ simpleField "duration" [t| Double |]
])
data RpcResultTestDelay = RpcResultTestDelay
deriving Show
instance J.JSON RpcResultTestDelay where
showJSON _ = J.JSNull
readJSON J.JSNull = return RpcResultTestDelay
readJSON _ = fail "Unable to read RpcResultTestDelay"
instance RpcCall RpcCallTestDelay where
rpcCallName _ = "test_delay"
rpcCallTimeout = ceiling . (+ 5) . rpcCallTestDelayDuration
rpcCallAcceptOffline _ = False
rpcCallData _ call = J.encode [rpcCallTestDelayDuration call]
instance Rpc RpcCallTestDelay RpcResultTestDelay where
rpcResultFill _ res = fromJSValueToRes res id
$(buildObject "RpcCallExportList" "rpcCallExportList" [])
$(buildObject "RpcResultExportList" "rpcResExportList"
[ simpleField "exports" [t| [String] |]
])
instance RpcCall RpcCallExportList where
rpcCallName _ = "export_list"
rpcCallTimeout _ = rpcTimeoutToRaw Fast
rpcCallAcceptOffline _ = False
rpcCallData _ = J.encode
instance Rpc RpcCallExportList RpcResultExportList where
rpcResultFill _ res = fromJSValueToRes res RpcResultExportList