module Portage.Metadata
( Metadata(..)
, metadataFromFile
, makeDefaultMetadata
) where
import qualified Data.ByteString as B
import Control.Applicative
import Text.XML.Light
data Metadata = Metadata
{ metadata_emails :: [String]
-- , metadataMaintainers :: [String],
-- , metadataUseFlags :: [(String,String)]
} deriving (Show)
metadataFromFile :: FilePath -> IO (Maybe Metadata)
metadataFromFile fp = do
doc <- parseXMLDoc <$> B.readFile fp
return (doc >>= parseMetadata)
parseMetadata :: Element -> Maybe Metadata
parseMetadata xml =
return Metadata { metadata_emails = map strContent (findElements (unqual "email") xml) }
formatFlags :: (String, String) -> String
formatFlags (name, description) = "\t\t" ++ description ++ ""
-- don't use Text.XML.Light as we like our own pretty printer
makeDefaultMetadata :: String -> [(String, String)] -> String
makeDefaultMetadata long_description flags =
unlines [ ""
, ""
, ""
, "\t"
, "\t\thaskell@gentoo.org"
, "\t\tGentoo Haskell"
, "\t"
, if (formatFlags <$> flags) == [""]
then "\t"
else "\t"
, (init {- strip trailing newline-}
. unlines
. map (\l -> if l `elem` ["", ""]
then "\t" ++ l -- leading/trailing lines
else "\t\t" ++ l -- description itself
)
. lines
. showElement
. unode "longdescription"
. ("\n" ++) -- prepend newline to separate form
. (++ "\n") -- append newline
) long_description
, ""
]