module Ganeti.Metad.ConfigServer where
import Control.Concurrent
import Control.Exception (try, finally)
import Control.Monad (unless)
import Text.JSON
import System.IO.Error (isEOFError)
import Ganeti.Path as Path
import Ganeti.Daemon (DaemonOptions, cleanupSocket, describeError)
import qualified Ganeti.Logging as Logging
import Ganeti.Runtime (GanetiDaemon(..), GanetiGroup(..), MiscGroup(..))
import Ganeti.UDSServer (Client, ConnectConfig(..), Server, ServerConfig(..))
import qualified Ganeti.UDSServer as UDSServer
import Ganeti.Utils (FilePermissions(..))
import Ganeti.Metad.Config as Config
import Ganeti.Metad.Types (InstanceParams)
updateConfig :: MVar InstanceParams -> String -> IO ()
updateConfig config str =
case decode str of
Error err ->
Logging.logDebug $ show err
Ok x ->
case Config.getInstanceParams x of
Error err ->
Logging.logError $ "Could not get instance parameters: " ++ err
Ok (name, instanceParams) -> do
cfg <- takeMVar config
let cfg' = mergeConfig cfg instanceParams
putMVar config cfg'
Logging.logInfo $
"Updated instance " ++ show name ++ " configuration"
Logging.logDebug $ "Instance configuration: " ++ show cfg'
acceptConfig :: MVar InstanceParams -> Client -> IO ()
acceptConfig config client =
do res <- try $ UDSServer.recvMsg client
case res of
Left err -> do
unless (isEOFError err) .
Logging.logDebug $ show err
return ()
Right str -> do
Logging.logDebug $ "Received: " ++ str
updateConfig config str
acceptClients :: MVar InstanceParams -> Server -> IO ()
acceptClients config server =
do client <- UDSServer.acceptClient server
_ <- forkIO $ acceptConfig config client
acceptClients config server
start :: DaemonOptions -> MVar InstanceParams -> IO ()
start _ config = do
socket_path <- Path.defaultMetadSocket
cleanupSocket socket_path
server <- describeError "binding to the socket" Nothing (Just socket_path)
$ UDSServer.connectServer metadConfig True socket_path
finally
(acceptClients config server)
(UDSServer.closeServer server)
where
metadConfig =
ServerConfig
FilePermissions { fpOwner = Just GanetiMetad
, fpGroup = Just $ ExtraGroup DaemonsGroup
, fpPermissions = 0o0600
}
ConnectConfig { recvTmo = 60
, sendTmo = 60
}