module Ganeti.WConfd.Server where
import Control.Concurrent (forkIO)
import Control.Exception
import Control.Monad
import Control.Monad.Error
import Ganeti.BasicTypes
import qualified Ganeti.Constants as C
import Ganeti.Daemon
import Ganeti.Daemon.Utils (handleMasterVerificationOptions)
import Ganeti.Logging (logDebug)
import qualified Ganeti.Path as Path
import Ganeti.THH.RPC
import Ganeti.UDSServer
import Ganeti.Errors (formatError)
import Ganeti.Runtime
import Ganeti.Utils
import Ganeti.Utils.Livelock (mkLivelockFile)
import Ganeti.WConfd.ConfigState
import Ganeti.WConfd.ConfigVerify
import Ganeti.WConfd.ConfigWriter
import Ganeti.WConfd.Core
import Ganeti.WConfd.DeathDetection (cleanupLocksTask)
import Ganeti.WConfd.Monad
import Ganeti.WConfd.Persistent
handler :: DaemonHandle -> RpcServer WConfdMonadInt
handler _ = $( mkRpcM exportedFunctions )
type PrepResult = (Server, DaemonHandle)
checkMain :: CheckFn ()
checkMain = handleMasterVerificationOptions
prepMain :: PrepFn () PrepResult
prepMain _ _ = do
socket_path <- Path.defaultWConfdSocket
cleanupSocket socket_path
s <- describeError "binding to the socket" Nothing (Just socket_path)
$ connectServer serverConfig True socket_path
conf_file <- Path.clusterConfFile
dh <- toErrorBase
. withErrorT (strMsg . ("Initialization of the daemon failed" ++)
. formatError) $ do
ents <- getEnts
(cdata, cstat) <- loadConfigFromFile conf_file
verifyConfigErr cdata
lock <- readPersistent persistentLocks
tempres <- readPersistent persistentTempRes
(_, livelock) <- mkLivelockFile C.wconfLivelockPrefix
mkDaemonHandle conf_file
(mkConfigState cdata)
lock
tempres
(saveConfigAsyncTask conf_file cstat)
(distMCsAsyncTask ents conf_file)
distSSConfAsyncTask
(writePersistentAsyncTask persistentLocks)
(writePersistentAsyncTask persistentTempRes)
livelock
return (s, dh)
serverConfig :: ServerConfig
serverConfig = ServerConfig
FilePermissions { fpOwner = Just GanetiWConfd
, fpGroup = Just $ ExtraGroup DaemonsGroup
, fpPermissions = 0o0600
}
ConnectConfig { recvTmo = 60
, sendTmo = 60
}
main :: MainFn () PrepResult
main _ _ (server, dh) = do
logDebug "Starting the cleanup task"
_ <- forkIO $ runWConfdMonadInt cleanupLocksTask dh
finally
(forever $ runWConfdMonadInt (listener (handler dh) server) dh)
(liftIO $ closeServer server)
options :: [OptType]
options =
[ oNoDaemonize
, oNoUserChecks
, oDebug
, oSyslogUsage
, oForceNode
, oNoVoting
, oYesDoIt
]