Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Language.Bash.Cond
Description
Bash conditional commands.
Synopsis
- data CondExpr a
- data UnaryOp
- data BinaryOp
- parseTestExpr :: [String] -> Either ParseError (CondExpr String)
Documentation
Bash conditional expressions.
Constructors
Unary UnaryOp a | |
Binary a BinaryOp a | |
Not (CondExpr a) | |
And (CondExpr a) (CondExpr a) | |
Or (CondExpr a) (CondExpr a) |
Instances
Unary conditional operators.
Constructors
BlockFile | -b |
CharacterFile | -c |
Directory | -d |
FileExists |
|
RegularFile | -f |
SetGID | -g |
Sticky | -k |
NamedPipe | -p |
Readable | -r |
FileSize | -s |
Terminal | -t |
SetUID | -u |
Writable | -w |
Executable | -x |
GroupOwned | -G |
SymbolicLink |
|
Modified | -N |
UserOwned | -O |
Socket | -S |
Optname | -o |
Varname | -v |
ZeroString | -z |
NonzeroString |
|
Instances
Data UnaryOp Source # | |
Defined in Language.Bash.Cond Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryOp -> c UnaryOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryOp # toConstr :: UnaryOp -> Constr # dataTypeOf :: UnaryOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryOp) # gmapT :: (forall b. Data b => b -> b) -> UnaryOp -> UnaryOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r # gmapQ :: (forall d. Data d => d -> u) -> UnaryOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # | |
Bounded UnaryOp Source # | |
Enum UnaryOp Source # | |
Generic UnaryOp Source # | |
Read UnaryOp Source # | |
Show UnaryOp Source # | |
Eq UnaryOp Source # | |
Ord UnaryOp Source # | |
Pretty UnaryOp Source # | |
Defined in Language.Bash.Cond | |
type Rep UnaryOp Source # | |
Defined in Language.Bash.Cond type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Language.Bash.Cond" "language-bash-0.11.1-inplace" 'False) ((((C1 ('MetaCons "BlockFile" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharacterFile" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Directory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FileExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RegularFile" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SetGID" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Sticky" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedPipe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Readable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FileSize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Terminal" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "SetUID" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Writable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Executable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GroupOwned" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SymbolicLink" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Modified" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UserOwned" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Socket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Optname" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Varname" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZeroString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonzeroString" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
Binary conditional operators.
Constructors
SameFile | -ef |
NewerThan | -nt |
OlderThan | -ot |
StrMatch | =~ |
StrEQ |
|
StrNE | != |
StrLT | < |
StrGT | > |
ArithEQ | -eq |
ArithNE | -ne |
ArithLT | -lt |
ArithLE | -le |
ArithGT | -gt |
ArithGE | -ge |
Instances
Data BinaryOp Source # | |
Defined in Language.Bash.Cond Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinaryOp -> c BinaryOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinaryOp # toConstr :: BinaryOp -> Constr # dataTypeOf :: BinaryOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinaryOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinaryOp) # gmapT :: (forall b. Data b => b -> b) -> BinaryOp -> BinaryOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r # gmapQ :: (forall d. Data d => d -> u) -> BinaryOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinaryOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp # | |
Bounded BinaryOp Source # | |
Enum BinaryOp Source # | |
Defined in Language.Bash.Cond | |
Generic BinaryOp Source # | |
Read BinaryOp Source # | |
Show BinaryOp Source # | |
Eq BinaryOp Source # | |
Ord BinaryOp Source # | |
Defined in Language.Bash.Cond | |
Pretty BinaryOp Source # | |
Defined in Language.Bash.Cond | |
type Rep BinaryOp Source # | |
Defined in Language.Bash.Cond type Rep BinaryOp = D1 ('MetaData "BinaryOp" "Language.Bash.Cond" "language-bash-0.11.1-inplace" 'False) (((C1 ('MetaCons "SameFile" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewerThan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OlderThan" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StrMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrEQ" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StrNE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrLT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "StrGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArithEQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArithNE" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ArithLT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArithLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArithGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArithGE" 'PrefixI 'False) (U1 :: Type -> Type))))) |
parseTestExpr :: [String] -> Either ParseError (CondExpr String) Source #
Parse a conditional expression for the Bash test
builtin.