-- |A module for working with debian relationships module Linspire.Debian.Relation.String ( -- * Types PkgName , AndRelation , OrRelation , Relations , Relation(..) , ArchitectureReq(..) , VersionReq(..) -- * Helper Functions , checkVersionReq -- * Relation Parser , RelParser , ParseRelations(..) , pRelations ) where -- Standard GHC Modules import Data.List import Text.ParserCombinators.Parsec -- Local Modules import Linspire.Debian.Relation.Common import Linspire.Debian.Version -- * ParseRelations instance ParseRelations String where parseRelations str = case parse pRelations str str of Right relations -> Right (filter (/= []) relations) x -> x -- * Relation Parser type RelParser a = CharParser () a pRelations :: RelParser Relations pRelations = sepBy pOrRelation (char ',') pOrRelation :: RelParser OrRelation pOrRelation = sepBy pRelation (char '|') whiteChar = oneOf [' ','\t','\n'] pRelation :: RelParser Relation pRelation = do skipMany whiteChar pkgName <- many1 (noneOf [' ',',','|','\t','\n']) skipMany whiteChar mVerReq <- pMaybeVerReq skipMany whiteChar mArch <- pMaybeArch return $ Rel pkgName mVerReq mArch pMaybeVerReq :: RelParser (Maybe VersionReq) pMaybeVerReq = do char '(' skipMany whiteChar op <- pVerReq skipMany whiteChar version <- many1 (noneOf [' ',')','\t','\n']) skipMany whiteChar char ')' return $ Just (op (parseDebianVersion version)) <|> do return $ Nothing pVerReq = do char '<' (do char '<' <|> char ' ' <|> char '\t' return $ SLT <|> do char '=' return $ LTE) <|> do string "=" return $ EEQ <|> do char '>' (do char '=' return $ GRE <|> do char '>' <|> char ' ' <|> char '\t' return $ SGR) pMaybeArch :: RelParser (Maybe ArchitectureReq) pMaybeArch = do char '[' (do archs <- pArchExcept char ']' return (Just (ArchExcept archs)) <|> do archs <- pArchOnly char ']' return (Just (ArchOnly archs)) ) <|> return Nothing -- Some packages (e.g. coreutils) have architecture specs like [!i386 -- !hppa], even though this doesn't really make sense: once you have -- one !, anything else you include must also be (implicitly) a !. pArchExcept :: RelParser [String] pArchExcept = sepBy (char '!' >> many1 (noneOf [']',' '])) (skipMany1 whiteChar) pArchOnly :: RelParser [String] pArchOnly = sepBy (many1 (noneOf [']',' '])) (skipMany1 whiteChar)