module Ganeti.Hypervisor.Xen.XmParser
( xmListParser
, lispConfigParser
, xmUptimeParser
, uptimeLineParser
) where
import Control.Applicative
import Control.Monad
import qualified Data.Attoparsec.Combinator as AC
import qualified Data.Attoparsec.Text as A
import Data.Attoparsec.Text (Parser)
import Data.Char
import Data.List
import Data.Text (unpack)
import qualified Data.Map as Map
import Ganeti.BasicTypes
import Ganeti.Hypervisor.Xen.Types
lispConfigParser :: Parser LispConfig
lispConfigParser =
A.skipSpace *>
( listConfigP
<|> doubleP
<|> stringP
)
<* A.skipSpace
where listConfigP = LCList <$> (A.char '(' *> liftA2 (++)
(many middleP)
(((:[]) <$> finalP) <|> (rparen *> pure [])))
doubleP = LCDouble <$> A.rational <* A.skipSpace <* A.endOfInput
innerDoubleP = LCDouble <$> A.rational
stringP = LCString . unpack <$> A.takeWhile1 (not . (\c -> isSpace c
|| c `elem` "()"))
wspace = AC.many1 A.space
rparen = A.skipSpace *> A.char ')'
finalP = listConfigP <* rparen
<|> innerDoubleP <* rparen
<|> stringP <* rparen
middleP = listConfigP <* wspace
<|> innerDoubleP <* wspace
<|> stringP <* wspace
findConf :: String -> [LispConfig] -> Result LispConfig
findConf key configs =
case find (isNamed key) configs of
(Just c) -> Ok c
_ -> Bad "Configuration not found"
getValue :: (FromLispConfig a) => String -> [LispConfig] -> Result a
getValue key configs = findConf key configs >>= fromLispConfig
extractValues :: LispConfig -> Result [LispConfig]
extractValues c = tail `fmap` fromLispConfig c
isNamed :: String -> LispConfig -> Bool
isNamed key (LCList (LCString x:_)) = x == key
isNamed _ _ = False
parseState :: String -> ActualState
parseState s =
case s of
"r-----" -> ActualRunning
"-b----" -> ActualBlocked
"--p---" -> ActualPaused
"---s--" -> ActualShutdown
"----c-" -> ActualCrashed
"-----d" -> ActualDying
_ -> ActualUnknown
getDomainConfig :: LispConfig -> Result Domain
getDomainConfig configData = do
domainConf <-
if isNamed "domain" configData
then extractValues configData
else Bad $ "Not a domain configuration: " ++ show configData
domid <- getValue "domid" domainConf
name <- getValue "name" domainConf
cpuTime <- getValue "cpu_time" domainConf
state <- getValue "state" domainConf
let actualState = parseState state
return $ Domain domid name cpuTime actualState Nothing
xmListParser :: Parser (Map.Map String Domain)
xmListParser = do
configs <- lispConfigParser `AC.manyTill` A.endOfInput
let domains = map getDomainConfig configs
foldResult m (Ok val) = Ok $ Map.insert (domName val) val m
foldResult _ (Bad msg) = Bad msg
case foldM foldResult Map.empty domains of
Ok d -> return d
Bad msg -> fail msg
xmUptimeParser :: Parser (Map.Map Int UptimeInfo)
xmUptimeParser = do
_ <- headerParser
uptimes <- uptimeLineParser `AC.manyTill` A.endOfInput
return $ Map.fromList [(uInfoID u, u) | u <- uptimes]
where headerParser = A.string "Name" <* A.skipSpace <* A.string "ID"
<* A.skipSpace <* A.string "Uptime" <* A.skipSpace
uptimeLineParser :: Parser UptimeInfo
uptimeLineParser = do
name <- A.takeTill isSpace <* A.skipSpace
idNum <- A.decimal <* A.skipSpace
uptime <- A.takeTill (`elem` "\n\r") <* A.skipSpace
return . UptimeInfo (unpack name) idNum $ unpack uptime