module Ganeti.Confd.Server
( main
) where
import Control.Concurrent
import Control.Exception
import Control.Monad (forever)
import qualified Data.ByteString as B
import Data.IORef
import Data.List
import qualified Data.Map as M
import qualified Network.Socket as S
import System.Posix.Files
import System.Posix.Types
import System.Time
import qualified Text.JSON as J
import System.INotify
import Ganeti.Daemon
import Ganeti.HTools.JSON
import Ganeti.HTools.Types
import Ganeti.HTools.Utils
import Ganeti.Objects
import Ganeti.Confd
import Ganeti.Config
import Ganeti.Hash
import Ganeti.Logging
import qualified Ganeti.Constants as C
type CRef = IORef (Result (ConfigData, LinkIpMap))
type FStat = (EpochTime, FileID, FileOffset)
nullFStat :: FStat
nullFStat = (1, 1, 1)
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
data ReloadModel = ReloadNotify
| ReloadPoll Int
deriving (Eq, Show)
data ServerState = ServerState
{ reloadModel :: ReloadModel
, reloadTime :: Integer
, reloadFStat :: FStat
}
maxIdlePollRounds :: Int
maxIdlePollRounds = 2
configReloadTimeout :: Int
configReloadTimeout = C.confdConfigReloadTimeout * 1000000
configReloadRatelimit :: Int
configReloadRatelimit = C.confdConfigReloadRatelimit * 1000000
initialPoll :: ReloadModel
initialPoll = ReloadPoll 0
initialState :: ServerState
initialState = ServerState initialPoll 0 nullFStat
data ConfigReload = ConfigToDate
| ConfigReloaded
| ConfigIOError
queryUnknownEntry :: StatusAnswer
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
queryArgumentError :: StatusAnswer
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
getCurrentTime :: IO Integer
getCurrentTime = do
TOD ctime _ <- getClockTime
return ctime
getClusterHmac :: IO HashKey
getClusterHmac = fmap B.unpack $ B.readFile C.confdHmacKey
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
nodeRole cfg name =
let cmaster = clusterMasterNode . configCluster $ cfg
mnode = M.lookup name . configNodes $ cfg
in case mnode of
Nothing -> Bad "Node not found"
Just node | cmaster == name -> Ok NodeRoleMaster
| nodeDrained node -> Ok NodeRoleDrained
| nodeOffline node -> Ok NodeRoleOffline
| nodeMasterCandidate node -> Ok NodeRoleCandidate
_ -> Ok NodeRoleRegular
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))
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 -> return (ReplyStatusOk, J.showJSON master_name)
PlainQuery _ -> return queryArgumentError
DictQuery reqq -> do
mnode <- getNode cfg master_name
let fvals =map (\field -> case field of
ReqFieldName -> master_name
ReqFieldIp -> clusterMasterIp cluster
ReqFieldMNodePip -> nodePrimaryIp mnode
) (confdReqQFields reqq)
return (ReplyStatusOk, J.showJSON fvals)
where master_name = clusterMasterNode cluster
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) []
(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) []
(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 = maybe (getDefaultNicLink cfg) id (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 <- getNode cfg node_name
let minors = concatMap (getInstMinorsForNode (nodeName node)) .
M.elems . configInstances $ cfg
encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
J.showJSON d, J.showJSON e, J.showJSON f] |
(a, b, c, d, e, f) <- minors]
return (ReplyStatusOk, J.showJSON encoded)
parseRequest :: HashKey -> String -> Result (String, String, ConfdRequest)
parseRequest key str = do
(SignedMessage hmac msg salt) <- fromJResult "parsing request" $ J.decode str
req <- if verifyMac key (Just salt) msg hmac
then fromJResult "parsing message" $ J.decode msg
else Bad "HMAC verification failed"
return (salt, msg, req)
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 }
signMessage :: HashKey -> String -> String -> SignedMessage
signMessage key salt msg =
SignedMessage { signedMsgMsg = msg
, signedMsgSalt = salt
, signedMsgHmac = hmac
}
where hmac = computeMac key (Just salt) msg
moveToPolling :: String -> INotify -> FilePath -> CRef -> MVar ServerState
-> IO ReloadModel
moveToPolling msg inotify path cref mstate = do
logInfo $ "Moving to polling mode: " ++ msg
let inotiaction = addNotifier inotify path cref mstate
_ <- forkIO $ onReloadTimer inotiaction path cref mstate
return initialPoll
moveToNotify :: IO ReloadModel
moveToNotify = do
logInfo "Moving to inotify mode"
return ReloadNotify
updateConfig :: FilePath -> CRef -> IO ()
updateConfig path r = do
newcfg <- loadConfig path
let !newdata = case newcfg of
Ok !cfg -> Ok (cfg, buildLinkIpInstnameMap cfg)
Bad _ -> Bad "Cannot load configuration"
writeIORef r newdata
case newcfg of
Ok cfg -> logInfo ("Loaded new config, serial " ++
show (configSerial cfg))
Bad msg -> logError $ "Failed to load config: " ++ msg
return ()
safeUpdateConfig :: FilePath -> FStat -> CRef -> IO (FStat, ConfigReload)
safeUpdateConfig path oldfstat cref = do
Control.Exception.catch
(do
nt <- needsReload oldfstat path
case nt of
Nothing -> return (oldfstat, ConfigToDate)
Just nt' -> do
updateConfig path cref
return (nt', ConfigReloaded)
) (\e -> do
let msg = "Failure during configuration update: " ++
show (e::IOError)
writeIORef cref (Bad msg)
return (nullFStat, ConfigIOError)
)
buildFileStatus :: FileStatus -> FStat
buildFileStatus ofs =
let modt = modificationTime ofs
inum = fileID ofs
fsize = fileSize ofs
in (modt, inum, fsize)
getFStat :: FilePath -> IO FStat
getFStat p = getFileStatus p >>= (return . buildFileStatus)
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
needsReload oldstat path = do
newstat <- getFStat path
return $ if newstat /= oldstat
then Just newstat
else Nothing
onTimeoutTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
onTimeoutTimer inotiaction path cref state = do
threadDelay configReloadTimeout
modifyMVar_ state (onTimeoutInner path cref)
_ <- inotiaction
onTimeoutTimer inotiaction path cref state
onTimeoutInner :: FilePath -> CRef -> ServerState -> IO ServerState
onTimeoutInner path cref state = do
(newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
return state { reloadFStat = newfstat }
onReloadTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
onReloadTimer inotiaction path cref state = do
continue <- modifyMVar state (onReloadInner inotiaction path cref)
if continue
then do
threadDelay configReloadRatelimit
onReloadTimer inotiaction path cref state
else
return ()
onReloadInner :: IO Bool -> FilePath -> CRef -> ServerState
-> IO (ServerState, Bool)
onReloadInner _ _ _ state@(ServerState { reloadModel = ReloadNotify } ) =
return (state, False)
onReloadInner inotiaction path cref
state@(ServerState { reloadModel = ReloadPoll pround } ) = do
(newfstat, reload) <- safeUpdateConfig path (reloadFStat state) cref
let state' = state { reloadFStat = newfstat }
newmode <- case reload of
ConfigToDate ->
if pround >= maxIdlePollRounds
then do
result <- inotiaction
if result
then moveToNotify
else return initialPoll
else return (ReloadPoll (pround + 1))
_ -> return initialPoll
let continue = case newmode of
ReloadNotify -> False
_ -> True
return (state' { reloadModel = newmode }, continue)
addNotifier :: INotify -> FilePath -> CRef -> MVar ServerState -> IO Bool
addNotifier inotify path cref mstate = do
Control.Exception.catch
(addWatch inotify [CloseWrite] path
(onInotify inotify path cref mstate) >> return True)
(\e -> const (return False) (e::IOError))
onInotify :: INotify -> String -> CRef -> MVar ServerState -> Event -> IO ()
onInotify inotify path cref mstate Ignored = do
logDebug "File lost, trying to re-establish notifier"
modifyMVar_ mstate $ \state -> do
result <- addNotifier inotify path cref mstate
(newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
let state' = state { reloadFStat = newfstat }
if result
then return state'
else do
mode <- moveToPolling "cannot re-establish inotify watch" inotify
path cref mstate
return state' { reloadModel = mode }
onInotify inotify path cref mstate _ = do
modifyMVar_ mstate $ \state ->
if (reloadModel state == ReloadNotify)
then do
ctime <- getCurrentTime
(newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
let state' = state { reloadFStat = newfstat, reloadTime = ctime }
if abs (reloadTime state ctime) <
fromIntegral C.confdConfigReloadRatelimit
then do
mode <- moveToPolling "too many reloads" inotify path cref mstate
return state' { reloadModel = mode }
else return state'
else return state
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
responder cfgref socket hmac msg peer = do
ctime <- getCurrentTime
case parseMessage hmac msg ctime of
Ok (origmsg, rq) -> do
logDebug $ "Processing request: " ++ origmsg
mcfg <- readIORef cfgref
let response = respondInner mcfg hmac rq
_ <- S.sendTo socket response peer
return ()
Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
return ()
parseMessage :: HashKey -> String -> Integer
-> Result (String, ConfdRequest)
parseMessage hmac msg curtime = do
(salt, origmsg, request) <- parseRequest hmac msg
ts <- tryRead "Parsing timestamp" salt::Result Integer
if (abs (ts curtime) > (fromIntegral C.confdMaxClockSkew))
then fail "Too old/too new timestamp or clock skew"
else return (origmsg, request)
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 = 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 confdMagicFourcc `isPrefixOf` msg
then (forkIO $ resp s hmac (drop 4 msg) peer) >> return ()
else logDebug "Invalid magic code!" >> return ()
return ()
main :: DaemonOptions -> IO ()
main opts = do
parseresult <- parseAddress opts C.defaultConfdPort
(af_family, bindaddr) <- exitIfBad "parsing bind address" parseresult
s <- S.socket af_family S.Datagram S.defaultProtocol
S.bindSocket s bindaddr
cref <- newIORef (Bad "Configuration not yet loaded")
statemvar <- newMVar initialState
hmac <- getClusterHmac
inotify <- initINotify
let inotiaction = addNotifier inotify C.clusterConfFile cref statemvar
_ <- forkIO $ onTimeoutTimer inotiaction C.clusterConfFile cref statemvar
_ <- forkIO $ onReloadTimer inotiaction C.clusterConfFile cref statemvar
forever $ listener s hmac (responder cref)