| Safe Haskell | None |
|---|
Language.Bash.Syntax
Description
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 FuncName (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)
- | Assign (Assignment t)
- | Declare (Assignment t)
- | Local (Assignment t)
- | Export Identifier (Expression t)
- | IsSet VarName
- | ArrayUpdate Identifier (Expression t) (Expression t)
- | DictUpdate 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
- | ElementsSafe 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 FuncName
- funcName :: ByteString -> Maybe FuncName
- 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)
- data Assignment t
- = Var Identifier (Expression t)
- | Array Identifier [Expression t]
- | Dict Identifier [(Expression t, Expression t)]
Documentation
The Annotated type captures the annotatedness of a tree of Bash
statements. It is Foldable and a Functor.
Constructors
| Annotated | |
Fields
| |
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.
Constructors
| 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 FuncName (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) | |
| Assign (Assignment t) | |
| Declare (Assignment t) | |
| Local (Assignment t) | |
| Export Identifier (Expression t) | |
| IsSet VarName | |
| ArrayUpdate Identifier (Expression t) (Expression t) | |
| DictUpdate Identifier (Expression t) (Expression t) | |
| Redirect (Annotated t) Redirection FileDescriptor (Either (Expression t) FileDescriptor) |
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.
Constructors
Instances
| 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.
Constructors
| VarIdent Identifier | |
| VarSpecial SpecialVar |
varName :: ByteString -> Maybe VarNameSource
newtype Identifier Source
The type of legal Bash identifiers, strings beginning with letters or _
and containing letters, _ and digits.
Constructors
| Identifier ByteString |
Instances
identifier :: ByteString -> Maybe IdentifierSource
Produce an Identifier from a ByteString of legal format.
Bash functions can have surprising names. Once the word containing the name of the function has been identified by the Bash parser, the only constraint as of this writing is that it not be all digits and contain neither quotes nor dollar signs. Thus the following are all callable functions:
function http://duckduckgo.com { curl -sSfL http://duckduckgo.com?q="$1" ;}
function 123.0 { echo 123.0 ;}
function + { echo "$@" | sed 's/ / + /g' | bc ;}
Yet a function name may only be parsed if its surroundings constitute a valid function declaration. So we are not able to declare these functions:
function par()ens { echo '(' "$@" ')' ;}
function (parens) { echo '(' "$@" ')' ;}
(The parser thinks the parens are there to separate the function name from the function body.)
Some functions can be declared but not called. For example:
function for { echo for ;}
function x=y { echo x is y ;}
Calling the former results in a syntax error. A call to the latter is parsed as an assignment.
It is possible to override important builtins with function declarations. For example:
function set { echo Haha! ;}
function declare { echo Surprise! ;}
Overall, Bash function names are quite flexible but inconsistent and potentially a cause of grave errors.
Constructors
| Simple Identifier | |
| Fancy ByteString |
data SpecialVar Source
The names of special variables, with otherwise illegal identifiers, are represented by this type.
Constructors
| DollarQuestion | |
| DollarHyphen | |
| DollarDollar | |
| DollarBang | |
| DollarUnderscore | |
| Dollar0 | |
| Dollar1 | |
| Dollar2 | |
| Dollar3 | |
| Dollar4 | |
| Dollar5 | |
| Dollar6 | |
| Dollar7 | |
| Dollar8 | |
| Dollar9 |
Instances
specialVar :: ByteString -> Maybe SpecialVarSource
Try to render a SpecialVar from a ByteString.
Constructors
| ShortestLeading | |
| LongestLeading | |
| ShortestTrailing | |
| LongestTrailing |
newtype FileDescriptor Source
A file descriptor in Bash is simply a number between 0 and 255.
Constructors
| FileDescriptor Word8 |
data ConditionalExpression t Source
Unused at present.
Constructors
Instances
| Eq t => Eq (ConditionalExpression t) | |
| Ord t => Ord (ConditionalExpression t) | |
| Show t => Show (ConditionalExpression t) |
data Assignment t Source
Constructors
| Var Identifier (Expression t) | |
| Array Identifier [Expression t] | |
| Dict Identifier [(Expression t, Expression t)] |
Instances
| Functor Assignment | |
| Foldable Assignment | |
| Eq t => Eq (Assignment t) | |
| Ord t => Ord (Assignment t) | |
| Show t => Show (Assignment t) |