{-# LANGUAGE
DeriveDataTypeable
, DeriveFoldable
, CPP
, DeriveFunctor
, DeriveTraversable
, OverloadedStrings
#-}
module Language.Bash.Cond
( CondExpr(..)
, UnaryOp(..)
, BinaryOp(..)
, parseTestExpr
) where
import Prelude hiding (negate)
import Control.Applicative
import Data.Data (Data)
import Data.Typeable (Typeable)
import Text.Parsec hiding ((<|>), token)
import Text.Parsec.Expr hiding (Operator)
import Text.PrettyPrint hiding (parens)
#if __GLASGOW_HASKELL__ < 710
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
#endif
import Language.Bash.Operator
import Language.Bash.Pretty
data CondExpr a
= Unary UnaryOp a
| Binary a BinaryOp a
| Not (CondExpr a)
| And (CondExpr a) (CondExpr a)
| Or (CondExpr a) (CondExpr a)
deriving (Data, Eq, Read, Show, Typeable, Functor, Foldable, Traversable)
instance Pretty a => Pretty (CondExpr a) where
pretty = go (0 :: Int)
where
go _ (Unary op a) = pretty op <+> pretty a
go _ (Binary a op b) = pretty a <+> pretty op <+> pretty b
go _ (Not e) = "!" <+> go 2 e
go p (And e1 e2) = paren (p > 1) $ go 1 e1 <+> "&&" <+> go 1 e2
go p (Or e1 e2) = paren (p > 0) $ go 0 e1 <+> "||" <+> go 0 e2
paren False d = d
paren True d = "(" <+> d <+> ")"
data UnaryOp
= BlockFile
| CharacterFile
| Directory
| FileExists
| RegularFile
| SetGID
| Sticky
| NamedPipe
| Readable
| FileSize
| Terminal
| SetUID
| Writable
| Executable
| GroupOwned
| SymbolicLink
| Modified
| UserOwned
| Socket
| Optname
| Varname
| ZeroString
| NonzeroString
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator UnaryOp where
operatorTable =
zip [minBound .. maxBound]
(map (\c -> ['-', c]) "bcdefgkprstuwxGLNOSovzn") ++
[ (FileExists , "-a")
, (SymbolicLink, "-h")
]
instance Pretty UnaryOp where
pretty = prettyOperator
data BinaryOp
= SameFile
| NewerThan
| OlderThan
| StrMatch
| StrEQ
| StrNE
| StrLT
| StrGT
| ArithEQ
| ArithNE
| ArithLT
| ArithLE
| ArithGT
| ArithGE
deriving (Data, Eq, Ord, Read, Show, Typeable, Enum, Bounded)
instance Operator BinaryOp where
operatorTable =
zip [minBound .. maxBound]
[ "-ef", "-nt", "-ot"
, "=~", "==", "!=", "<", ">"
, "-eq", "-ne", "-lt", "-le", "-gt", "-ge"
] ++
[ (StrEQ, "=") ]
instance Pretty BinaryOp where
pretty = prettyOperator
type Parser = Parsec [String] ()
token :: (String -> Maybe a) -> Parser a
token = tokenPrim show (\pos _ _ -> pos)
word :: String -> Parser String
word s = token (\t -> if t == s then Just s else Nothing) <?> s
anyWord :: Parser String
anyWord = token Just
parens :: Parser a -> Parser a
parens p = word "(" *> p <* word ")"
nullaryExpr :: Parser (CondExpr String)
nullaryExpr = Unary NonzeroString <$> anyWord
unaryExpr :: Parser (CondExpr String)
unaryExpr = Unary <$> select word unaryOps <*> anyWord
<?> "unary expression"
where
unaryOps = filter ((`notElem` ["-a", "-o"]) . snd) operatorTable
standaloneUnaryExpr :: Parser (CondExpr String)
standaloneUnaryExpr = Unary <$> selectOperator word <*> anyWord
<?> "unary expression"
binaryExpr :: Parser (CondExpr String)
binaryExpr = Binary <$> anyWord <*> select word binaryOps <*> anyWord
<?> "binary expression"
where
binaryOps = filter ((/= "=~") . snd) operatorTable
binaryAndOrExpr :: Parser (CondExpr String)
binaryAndOrExpr = nullaryExpr <**> andOrOp <*> nullaryExpr
where
andOrOp = And <$ word "-a"
<|> Or <$ word "-o"
condExpr :: Parser (CondExpr String)
condExpr = expr
where
expr = buildExpressionParser opTable term
term = parens expr
<|> unaryExpr
<|> try binaryExpr
<|> nullaryExpr
opTable =
[ [Prefix (Not <$ word "!")]
, [Infix (And <$ word "-a") AssocLeft]
, [Infix (Or <$ word "-o") AssocLeft]
]
parseTestExpr :: [String] -> Either ParseError (CondExpr String)
parseTestExpr args = parse (testExpr <* eof) "" args
where
testExpr = case length args of
0 -> fail "no arguments"
1 -> oneArg
2 -> twoArg
3 -> threeArg
4 -> fourArg
_ -> condExpr
oneArg = nullaryExpr
twoArg = negate nullaryExpr
<|> standaloneUnaryExpr
threeArg = try binaryExpr
<|> try binaryAndOrExpr
<|> negate twoArg
<|> parens nullaryExpr
fourArg = negate threeArg
<|> condExpr
negate p = Not <$ word "!" <*> p