Safe Haskell | None |
---|
Bash statements and expressions. The statement tree is a functor, supporting arbitrary annotations; this is intended to support analysis of effects and privilege levels as well as commenting and arbitrary code inclusion.
- data Annotated t = Annotated {
- annotation :: t
- statement :: Statement t
- data Statement t
- = Empty
- | SimpleCommand (Expression t) [Expression t]
- | NoOp ByteString
- | Bang (Annotated t)
- | AndAnd (Annotated t) (Annotated t)
- | OrOr (Annotated t) (Annotated t)
- | Pipe (Annotated t) (Annotated t)
- | Sequence (Annotated t) (Annotated t)
- | Background (Annotated t) (Annotated t)
- | Group (Annotated t)
- | Subshell (Annotated t)
- | Function Identifier (Annotated t)
- | IfThen (Annotated t) (Annotated t)
- | IfThenElse (Annotated t) (Annotated t) (Annotated t)
- | For Identifier [Expression t] (Annotated t)
- | Case (Expression t) [(Expression t, Annotated t)]
- | While (Annotated t) (Annotated t)
- | Until (Annotated t) (Annotated t)
- | VarAssign Identifier (Expression t)
- | Export Identifier (Expression t)
- | ArrayDecl Identifier [Expression t]
- | ArrayUpdate Identifier (Expression t) (Expression t)
- | ArrayAssign Identifier [Expression t]
- | DictDecl Identifier [(Identifier, Expression t)]
- | DictUpdate Identifier (Expression t) (Expression t)
- | DictAssign Identifier [(Expression t, Expression t)]
- | Redirect (Annotated t) Redirection FileDescriptor (Either (Expression t) FileDescriptor)
- data Expression t
- = Literal Bash
- | Asterisk
- | QuestionMark
- | Tilde
- | ReadVar VarName
- | ReadVarSafe VarName
- | ReadArray Identifier (Expression t)
- | ReadArraySafe Identifier (Expression t)
- | ARGVElements
- | ARGVLength
- | Elements Identifier
- | Keys Identifier
- | Length VarName
- | Trim Trim VarName (Expression t)
- | ArrayLength Identifier
- | Concat (Expression t) (Expression t)
- | Eval (Annotated t)
- | EvalUnquoted (Annotated t)
- | ProcessIn (Annotated t)
- | ProcessOut (Annotated t)
- literal :: ByteString -> Expression t
- data VarName
- varName :: ByteString -> Maybe VarName
- newtype Identifier = Identifier ByteString
- identifier :: ByteString -> Maybe Identifier
- data SpecialVar
- = DollarQuestion
- | DollarHyphen
- | DollarDollar
- | DollarBang
- | DollarUnderscore
- | Dollar0
- | Dollar1
- | Dollar2
- | Dollar3
- | Dollar4
- | Dollar5
- | Dollar6
- | Dollar7
- | Dollar8
- | Dollar9
- specialVar :: ByteString -> Maybe SpecialVar
- specialVarBytes :: SpecialVar -> ByteString
- data Trim
- newtype FileDescriptor = FileDescriptor Word8
- data Redirection
- data ConditionalExpression t
- = File_a (Expression t)
- | File_b (Expression t)
- | File_c (Expression t)
- | File_d (Expression t)
- | File_e (Expression t)
- | File_f (Expression t)
- | File_g (Expression t)
- | File_h (Expression t)
- | File_k (Expression t)
- | File_p (Expression t)
- | File_r (Expression t)
- | File_s (Expression t)
- | File_t (Expression t)
- | File_u (Expression t)
- | File_w (Expression t)
- | File_x (Expression t)
- | File_O (Expression t)
- | File_G (Expression t)
- | File_L (Expression t)
- | File_S (Expression t)
- | File_N (Expression t)
- | File_nt (Expression t) (Expression t)
- | File_ot (Expression t) (Expression t)
- | File_ef (Expression t) (Expression t)
- | OptSet (Expression t)
- | StringEmpty (Expression t)
- | StringNonempty (Expression t)
- | StringEq (Expression t) (Expression t)
- | StringNotEq (Expression t) (Expression t)
- | StringLT (Expression t) (Expression t)
- | StringGT (Expression t) (Expression t)
- | StringRE (Expression t) (Expression t)
- | NumEq (Expression t) (Expression t)
- | NumNotEq (Expression t) (Expression t)
- | NumLT (Expression t) (Expression t)
- | NumLEq (Expression t) (Expression t)
- | NumGT (Expression t) (Expression t)
- | NumGEq (Expression t) (Expression t)
- | Not (Expression t) (Expression t)
- | And (Expression t) (Expression t)
- | Or (Expression t) (Expression t)
Documentation
The Annotated
type captures the annotatedness of a tree of Bash
statements. It is Foldable
and a Functor
.
Annotated | |
|
The Statement
type captures the different kind of statements that may
exist in a Bash statement tree. It is mutually recursive with Annotated
.
It is a Foldable
and a Functor
.
data Expression t Source
The type of Bash expressions, handling many kinds of variable reference as
well as eval and process substitution. It is Foldable
and a Functor
.
Functor Expression | |
Foldable Expression | |
Eq t => Eq (Expression t) | |
Ord t => Ord (Expression t) | |
Show t => Show (Expression t) | |
IsString (Expression t) | |
Annotation t => PP (Expression t) |
literal :: ByteString -> Expression tSource
Escape a ByteString
to produce a literal expression.
varName :: ByteString -> Maybe VarNameSource
newtype Identifier Source
The type of legal Bash identifiers, strings beginning with letters or _
and containing letters, _
and digits.
identifier :: ByteString -> Maybe IdentifierSource
Produce an Identifier
from a ByteString
of legal format.
data SpecialVar Source
The names of special variables, with otherwise illegal identifiers, are represented by this type.
specialVar :: ByteString -> Maybe SpecialVarSource
Try to render a SpecialVar
from a ByteString
.
newtype FileDescriptor Source
A file descriptor in Bash is simply a number between 0 and 255.
data Redirection Source
Redirection "directions".
data ConditionalExpression t Source
Unused at present.
Eq t => Eq (ConditionalExpression t) | |
Ord t => Ord (ConditionalExpression t) | |
Show t => Show (ConditionalExpression t) |