module Ganeti.Confd.Server
( main
, checkMain
, prepMain
) where
import Control.Applicative((<$>))
import Control.Concurrent
import Control.Monad (forever, liftM)
import Data.IORef
import Data.List
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import qualified Network.Socket as S
import System.Exit
import System.IO
import qualified Text.JSON as J
import Ganeti.BasicTypes
import Ganeti.Errors
import Ganeti.Daemon
import Ganeti.JSON
import Ganeti.Objects
import Ganeti.Confd.Types
import Ganeti.Confd.Utils
import Ganeti.Config
import Ganeti.ConfigReader
import Ganeti.Hash
import Ganeti.Logging
import qualified Ganeti.Constants as C
import qualified Ganeti.Query.Cluster as QCluster
import Ganeti.Utils
type CRef = IORef (Result (ConfigData, LinkIpMap))
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
queryUnknownEntry :: StatusAnswer
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
queryArgumentError :: StatusAnswer
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
gntErrorToResult :: ErrorResult a -> Result a
gntErrorToResult (Bad err) = Bad (show err)
gntErrorToResult (Ok x) = Ok x
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
nodeRole cfg name = do
cmaster <- errToResult $ QCluster.clusterMasterNodeName cfg
mnode <- errToResult $ getNode cfg name
let role = case mnode of
node | cmaster == name -> NodeRoleMaster
| nodeDrained node -> NodeRoleDrained
| nodeOffline node -> NodeRoleOffline
| nodeMasterCandidate node -> NodeRoleCandidate
_ -> NodeRoleRegular
return role
getNodePipByInstanceIp :: ConfigData
-> LinkIpMap
-> String
-> String
-> StatusAnswer
getNodePipByInstanceIp cfg linkipmap link instip =
case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
Nothing -> queryUnknownEntry
Just instname ->
case getInstPrimaryNode cfg instname of
Bad _ -> queryUnknownEntry
Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
uuidToNodeName :: ConfigData -> String -> Result String
uuidToNodeName cfg uuid = gntErrorToResult $ nodeName <$> getNode cfg uuid
encodeMinors :: ConfigData -> (String, Int, String, String, String, String)
-> Result J.JSValue
encodeMinors cfg (node_uuid, a, b, c, d, peer_uuid) = do
node_name <- uuidToNodeName cfg node_uuid
peer_name <- uuidToNodeName cfg peer_uuid
return . J.JSArray $ [J.showJSON node_name, J.showJSON a, J.showJSON b,
J.showJSON c, J.showJSON d, J.showJSON peer_name]
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
return (ReplyStatusOk, J.showJSON (configVersion cfg))
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
case confdRqQuery req of
EmptyQuery -> liftM ((,) ReplyStatusOk . J.showJSON) master_name
PlainQuery _ -> return queryArgumentError
DictQuery reqq -> do
mnode <- gntErrorToResult $ getNode cfg master_uuid
mname <- master_name
let fvals = map (\field -> case field of
ReqFieldName -> mname
ReqFieldIp -> clusterMasterIp cluster
ReqFieldMNodePip -> nodePrimaryIp mnode
) (confdReqQFields reqq)
return (ReplyStatusOk, J.showJSON fvals)
where master_uuid = clusterMasterNode cluster
master_name = errToResult $ QCluster.clusterMasterNodeName cfg
cluster = configCluster cfg
cfg = fst cdata
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
node_name <- case confdRqQuery req of
PlainQuery str -> return str
_ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
role <- nodeRole (fst cdata) node_name
return (ReplyStatusOk, J.showJSON role)
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
return (ReplyStatusOk, J.showJSON $
M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
(fromContainer . configNodes . fst $ cdata))
buildResponse cdata (ConfdRequest { confdRqType = ReqMcPipList }) =
return (ReplyStatusOk, J.showJSON $
M.foldlWithKey (\accu _ n -> if nodeMasterCandidate n
then nodePrimaryIp n:accu
else accu) []
(fromContainer . configNodes . fst $ cdata))
buildResponse (cfg, linkipmap)
req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
link <- case confdRqQuery req of
PlainQuery str -> return str
EmptyQuery -> return (getDefaultNicLink cfg)
_ -> fail "Invalid query type"
return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
, confdRqQuery = DictQuery query}) =
let (cfg, linkipmap) = cdata
link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
in case confdReqQIp query of
Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
Nothing -> return (ReplyStatusOk,
J.showJSON $
map (getNodePipByInstanceIp cfg linkipmap link)
(confdReqQIpList query))
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
return queryArgumentError
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
let cfg = fst cdata
node_name <- case confdRqQuery req of
PlainQuery str -> return str
_ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
node <- gntErrorToResult $ getNode cfg node_name
let minors = concatMap (getInstMinorsForNode (nodeUuid node)) .
M.elems . fromContainer . configInstances $ cfg
encoded <- mapM (encodeMinors cfg) minors
return (ReplyStatusOk, J.showJSON encoded)
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeInstances }) = do
let cfg = fst cdata
node_name <- case confdRqQuery req of
PlainQuery str -> return str
_ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
node <-
case getNode cfg node_name of
Ok n -> return n
Bad e -> fail $ "Node not found in the configuration: " ++ show e
let node_uuid = nodeUuid node
instances = getNodeInstances cfg node_uuid
return (ReplyStatusOk, J.showJSON instances)
serializeResponse :: Result StatusAnswer -> ConfdReply
serializeResponse r =
let (status, result) = case r of
Bad err -> (ReplyStatusError, J.showJSON err)
Ok (code, val) -> (code, val)
in ConfdReply { confdReplyProtocol = 1
, confdReplyStatus = status
, confdReplyAnswer = result
, confdReplySerial = 0 }
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
responder cfgref socket hmac msg peer = do
ctime <- getCurrentTime
case parseRequest hmac msg ctime of
Ok (origmsg, rq) -> do
logDebug $ "Processing request: " ++ rStripSpace origmsg
mcfg <- readIORef cfgref
let response = respondInner mcfg hmac rq
_ <- S.sendTo socket response peer
logDebug $ "Response sent: " ++ response
return ()
Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
return ()
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
-> ConfdRequest -> String
respondInner cfg hmac rq =
let rsalt = confdRqRsalt rq
innermsg = serializeResponse (cfg >>= flip buildResponse rq)
innerserialised = J.encodeStrict innermsg
outermsg = signMessage hmac rsalt innerserialised
outerserialised = C.confdMagicFourcc ++ J.encodeStrict outermsg
in outerserialised
listener :: S.Socket -> HashKey
-> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
-> IO ()
listener s hmac resp = do
(msg, _, peer) <- S.recvFrom s 4096
if C.confdMagicFourcc `isPrefixOf` msg
then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
else logDebug "Invalid magic code!" >> return ()
return ()
type PrepResult = (S.Socket, IORef (Result (ConfigData, LinkIpMap)))
checkMain :: CheckFn (S.Family, S.SockAddr)
checkMain opts = do
parseresult <- parseAddress opts C.defaultConfdPort
case parseresult of
Bad msg -> do
hPutStrLn stderr $ "parsing bind address: " ++ msg
return . Left $ ExitFailure 1
Ok v -> return $ Right v
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
prepMain _ (af_family, bindaddr) = do
s <- S.socket af_family S.Datagram S.defaultProtocol
S.bindSocket s bindaddr
cref <- newIORef (Bad "Configuration not yet loaded")
return (s, cref)
main :: MainFn (S.Family, S.SockAddr) PrepResult
main _ _ (s, cref) = do
let cfg_transform :: Result ConfigData -> Result (ConfigData, LinkIpMap)
cfg_transform = liftM (\cfg -> (cfg, buildLinkIpInstnameMap cfg))
initConfigReader cfg_transform cref
hmac <- getClusterHmac
forever $ listener s hmac (responder cref)