module Ganeti.Ssconf
( SSKey(..)
, sSKeyToRaw
, sSKeyFromRaw
, hvparamsSSKey
, getPrimaryIPFamily
, parseNodesVmCapable
, getNodesVmCapable
, getMasterCandidatesIps
, getMasterNode
, parseHypervisorList
, getHypervisorList
, parseEnabledUserShutdown
, getEnabledUserShutdown
, keyToFilename
, sSFilePrefix
, SSConf(..)
, emptySSConf
) where
import Prelude ()
import Ganeti.Prelude
import Control.Arrow ((&&&))
import Control.Exception
import Control.Monad (forM, liftM)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import qualified Network.Socket as Socket
import System.FilePath ((</>))
import System.IO.Error (isDoesNotExistError)
import qualified Text.JSON as J
import qualified AutoConf
import Ganeti.BasicTypes
import qualified Ganeti.Constants as C
import qualified Ganeti.ConstantUtils as CU
import Ganeti.JSON (GenericContainer(..), HasStringRepr(..))
import qualified Ganeti.Path as Path
import Ganeti.THH
import Ganeti.Types (Hypervisor)
import qualified Ganeti.Types as Types
import Ganeti.Utils
maxFileSize :: Int
maxFileSize = 131072
sSFilePrefix :: FilePath
sSFilePrefix = C.ssconfFileprefix
$(declareLADT ''String "SSKey" (
map (ssconfConstructorName &&& id) . CU.toList $ C.validSsKeys
))
instance HasStringRepr SSKey where
fromStringRepr = sSKeyFromRaw
toStringRepr = sSKeyToRaw
hvparamsSSKey :: Types.Hypervisor -> SSKey
hvparamsSSKey Types.Kvm = SSHvparamsKvm
hvparamsSSKey Types.XenPvm = SSHvparamsXenPvm
hvparamsSSKey Types.Chroot = SSHvparamsChroot
hvparamsSSKey Types.XenHvm = SSHvparamsXenHvm
hvparamsSSKey Types.Lxc = SSHvparamsLxc
hvparamsSSKey Types.Fake = SSHvparamsFake
keyToFilename :: FilePath
-> SSKey
-> FilePath
keyToFilename cfgpath key =
cfgpath </> sSFilePrefix ++ sSKeyToRaw key
catchIOErrors :: Maybe a
-> IO a
-> IO (Result a)
catchIOErrors def action =
Control.Exception.catch
(do
result <- action
return (Ok result)
) (\err -> let bad_result = Bad (show err)
in return $ if isDoesNotExistError err
then maybe bad_result Ok def
else bad_result)
readSSConfFile :: Maybe FilePath
-> Maybe String
-> SSKey
-> IO (Result String)
readSSConfFile optpath def key = do
dpath <- Path.dataDir
result <- catchIOErrors def . readFile .
keyToFilename (fromMaybe dpath optpath) $ key
return (liftM (take maxFileSize) result)
parseKeyValue :: Monad m => String -> String -> m (String, String)
parseKeyValue desc str =
case sepSplit '=' str of
[key, value] -> return (key, value)
_ -> fail $ "Failed to parse key-value pair for " ++ desc
parseIPFamily :: Int -> Result Socket.Family
parseIPFamily fam | fam == AutoConf.pyAfInet4 = Ok Socket.AF_INET
| fam == AutoConf.pyAfInet6 = Ok Socket.AF_INET6
| otherwise = Bad $ "Unknown af_family value: " ++ show fam
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
getPrimaryIPFamily optpath = do
result <- readSSConfFile optpath
(Just (show AutoConf.pyAfInet4))
SSPrimaryIpFamily
return (liftM rStripSpace result >>=
tryRead "Parsing af_family" >>= parseIPFamily)
parseNodesVmCapable :: String -> Result [(String, Bool)]
parseNodesVmCapable str =
forM (lines str) $ \line -> do
(key, val) <- parseKeyValue "Parsing node_vm_capable" line
val' <- tryRead "Parsing value of node_vm_capable" val
return (key, val')
getNodesVmCapable :: Maybe FilePath -> IO (Result [(String, Bool)])
getNodesVmCapable optPath =
(parseNodesVmCapable =<<) <$> readSSConfFile optPath Nothing SSNodeVmCapable
getMasterCandidatesIps :: Maybe FilePath -> IO (Result [String])
getMasterCandidatesIps optPath = do
result <- readSSConfFile optPath Nothing SSMasterCandidatesIps
return $ liftM lines result
getMasterNode :: Maybe FilePath -> IO (Result String)
getMasterNode optPath = do
result <- readSSConfFile optPath Nothing SSMasterNode
return (liftM rStripSpace result)
parseHypervisorList :: String -> Result [Hypervisor]
parseHypervisorList str =
mapM Types.hypervisorFromRaw $ lines str
getHypervisorList :: Maybe FilePath -> IO (Result [Hypervisor])
getHypervisorList optPath =
(parseHypervisorList =<<) <$>
readSSConfFile optPath Nothing SSHypervisorList
parseEnabledUserShutdown :: String -> Result Bool
parseEnabledUserShutdown str =
tryRead "Parsing enabled_user_shutdown" (rStripSpace str)
getEnabledUserShutdown :: Maybe FilePath -> IO (Result Bool)
getEnabledUserShutdown optPath =
(parseEnabledUserShutdown =<<) <$>
readSSConfFile optPath Nothing SSEnabledUserShutdown
newtype SSConf = SSConf { getSSConf :: M.Map SSKey [String] }
deriving (Eq, Ord, Show)
instance J.JSON SSConf where
showJSON = J.showJSON . GenericContainer . getSSConf
readJSON = liftM (SSConf . fromContainer) . J.readJSON
emptySSConf :: SSConf
emptySSConf = SSConf M.empty