Safe Haskell | None |
---|
Language.Bash
Description
Types and functions for generation of Bash scripts, with safe escaping and composition of a large subset of Bash statements and expressions.
This module is meant to be imported qualified -- perhaps as Bash
-- and
contains everything you need to build and render Bash scripts. For
examples of usage, look at Language.Bash.Lib.
- 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 Annotated t = Annotated {
- annotation :: t
- statement :: Statement t
- 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 Identifier
- identifier :: ByteString -> Maybe Identifier
- data SpecialVar
- specialVar :: ByteString -> Maybe SpecialVar
- data VarName
- varName :: ByteString -> Maybe VarName
- data FuncName
- funcName :: ByteString -> Maybe FuncName
- data Redirection
- newtype FileDescriptor = FileDescriptor Word8
- data Assignment t
- = Var Identifier (Expression t)
- | Array Identifier [Expression t]
- | Dict Identifier [(Expression t, Expression t)]
- class PP t where
- bytes :: PP t => t -> ByteString
- builder :: PP t => t -> Builder
- data PPState
- render :: PPState -> State PPState () -> Builder
- nlCol :: Word -> PPState
- script :: Annotation t => Statement t -> Builder
- script_sha1 :: forall t t'. (Annotation t, Annotation t') => ByteString -> Statement t -> Statement t' -> Builder
- module Language.Bash.Annotations
- module Language.Bash.Lib
Documentation
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) |
The Annotated
type captures the annotatedness of a tree of Bash
statements. It is Foldable
and a Functor
.
Constructors
Annotated | |
Fields
|
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.
data Identifier Source
The type of legal Bash identifiers, strings beginning with letters or _
and containing letters, _
and digits.
Instances
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.
Instances
specialVar :: ByteString -> Maybe SpecialVarSource
Try to render a SpecialVar
from a ByteString
.
Constructors
VarIdent Identifier | |
VarSpecial SpecialVar |
varName :: ByteString -> Maybe VarNameSource
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 |
newtype FileDescriptor Source
A file descriptor in Bash is simply a number between 0 and 255.
Constructors
FileDescriptor Word8 |
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) |
Instances
PP FileDescriptor | |
PP SpecialVar | |
PP FuncName | |
PP Identifier | |
Annotation t => PP (Expression t) | |
Annotation t => PP (Statement t) | |
Annotation t => PP (Annotated t) |
bytes :: PP t => t -> ByteStringSource
State of pretty printing -- string being built, indent levels, present column, brace nesting.
render :: PPState -> State PPState () -> BuilderSource
Produce a builder from a pretty printer state computation.
nlCol :: Word -> PPStateSource
Pretty printer state starting on a new line indented to the given column.
script :: Annotation t => Statement t -> BuilderSource
Produce a script beginning with #!/bin/bash
and a safe set statement.
script_sha1 :: forall t t'. (Annotation t, Annotation t') => ByteString -> Statement t -> Statement t' -> BuilderSource
Produce a script beginning with #!/bin/bash
and some (optional)
documentation. Cause the script to be scanned for SHA-1 hash of the setup
(first statement argument) and main (second statement argument) before
running the safe set statement and running the second argument.
module Language.Bash.Annotations
module Language.Bash.Lib