language-bash-0.7.0: Parsing and pretty-printing Bash shell scripts

Safe HaskellSafe
LanguageHaskell98

Language.Bash.Word

Contents

Description

Bash words and substitutions.

Synopsis

Words

type Word = [Span] Source #

A Bash word, broken up into logical spans.

data Span Source #

An individual unit of a word.

Constructors

Char Char

A normal character.

Escape Char

An escaped character.

Single Word

A single-quoted string.

Double Word

A double-quoted string.

ANSIC Word

A ANSI C string.

Locale Word

A locale-translated string.

Backquote Word

A backquote-style command substitution. To extract the command string, unquote the word inside.

ParamSubst ParamSubst

A parameter substitution.

ArithSubst String

An arithmetic substitution.

CommandSubst String

A command substitution.

ProcessSubst ProcessSubstOp String

A process substitution.

Instances

Eq Span Source # 

Methods

(==) :: Span -> Span -> Bool #

(/=) :: Span -> Span -> Bool #

Data Span Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span #

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Span) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) #

gmapT :: (forall b. Data b => b -> b) -> Span -> Span #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

Read Span Source # 
Show Span Source # 

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Pretty Span Source # 

Parameters

data Parameter Source #

A parameter name an optional subscript.

Constructors

Parameter String (Maybe Word) 

Instances

Eq Parameter Source # 
Data Parameter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parameter -> c Parameter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parameter #

toConstr :: Parameter -> Constr #

dataTypeOf :: Parameter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Parameter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parameter) #

gmapT :: (forall b. Data b => b -> b) -> Parameter -> Parameter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r #

gmapQ :: (forall d. Data d => d -> u) -> Parameter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parameter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

Read Parameter Source # 
Show Parameter Source # 
Pretty Parameter Source # 

data ParamSubst Source #

A parameter substitution.

Constructors

Bare 

Fields

Brace 

Fields

Alt 

Fields

Substring 

Fields

Prefix 

Fields

Indices 

Fields

Length 

Fields

Delete 

Fields

Replace 

Fields

LetterCase 

Fields

Instances

Eq ParamSubst Source # 
Data ParamSubst Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParamSubst -> c ParamSubst #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParamSubst #

toConstr :: ParamSubst -> Constr #

dataTypeOf :: ParamSubst -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParamSubst) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParamSubst) #

gmapT :: (forall b. Data b => b -> b) -> ParamSubst -> ParamSubst #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParamSubst -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParamSubst -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParamSubst -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParamSubst -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParamSubst -> m ParamSubst #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSubst -> m ParamSubst #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParamSubst -> m ParamSubst #

Read ParamSubst Source # 
Show ParamSubst Source # 
Pretty ParamSubst Source # 

data AltOp Source #

An alternation operator.

Constructors

AltDefault

-, :-

AltAssign

'=', :=

AltError

?, :?

AltReplace

+, :+

Instances

Bounded AltOp Source # 
Enum AltOp Source # 
Eq AltOp Source # 

Methods

(==) :: AltOp -> AltOp -> Bool #

(/=) :: AltOp -> AltOp -> Bool #

Data AltOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AltOp -> c AltOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AltOp #

toConstr :: AltOp -> Constr #

dataTypeOf :: AltOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AltOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltOp) #

gmapT :: (forall b. Data b => b -> b) -> AltOp -> AltOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AltOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AltOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> AltOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AltOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AltOp -> m AltOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AltOp -> m AltOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AltOp -> m AltOp #

Ord AltOp Source # 

Methods

compare :: AltOp -> AltOp -> Ordering #

(<) :: AltOp -> AltOp -> Bool #

(<=) :: AltOp -> AltOp -> Bool #

(>) :: AltOp -> AltOp -> Bool #

(>=) :: AltOp -> AltOp -> Bool #

max :: AltOp -> AltOp -> AltOp #

min :: AltOp -> AltOp -> AltOp #

Read AltOp Source # 
Show AltOp Source # 

Methods

showsPrec :: Int -> AltOp -> ShowS #

show :: AltOp -> String #

showList :: [AltOp] -> ShowS #

Pretty AltOp Source # 

data LetterCaseOp Source #

A letter case operator.

Constructors

ToLower 
ToUpper 

Instances

Bounded LetterCaseOp Source # 
Enum LetterCaseOp Source # 
Eq LetterCaseOp Source # 
Data LetterCaseOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LetterCaseOp -> c LetterCaseOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LetterCaseOp #

toConstr :: LetterCaseOp -> Constr #

dataTypeOf :: LetterCaseOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LetterCaseOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LetterCaseOp) #

gmapT :: (forall b. Data b => b -> b) -> LetterCaseOp -> LetterCaseOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LetterCaseOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LetterCaseOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> LetterCaseOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LetterCaseOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LetterCaseOp -> m LetterCaseOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterCaseOp -> m LetterCaseOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterCaseOp -> m LetterCaseOp #

Ord LetterCaseOp Source # 
Read LetterCaseOp Source # 
Show LetterCaseOp Source # 
Pretty LetterCaseOp Source # 

data Direction Source #

A string direction.

Constructors

Front 
Back 

Instances

Bounded Direction Source # 
Enum Direction Source # 
Eq Direction Source # 
Data Direction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Direction -> c Direction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Direction #

toConstr :: Direction -> Constr #

dataTypeOf :: Direction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Direction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction) #

gmapT :: (forall b. Data b => b -> b) -> Direction -> Direction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Direction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Direction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

Ord Direction Source # 
Read Direction Source # 
Show Direction Source # 
Pretty Direction Source # 

Process

data ProcessSubstOp Source #

A process substitution.

Constructors

ProcessIn
<
ProcessOut
>

Instances

Bounded ProcessSubstOp Source # 
Enum ProcessSubstOp Source # 
Eq ProcessSubstOp Source # 
Data ProcessSubstOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProcessSubstOp -> c ProcessSubstOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProcessSubstOp #

toConstr :: ProcessSubstOp -> Constr #

dataTypeOf :: ProcessSubstOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProcessSubstOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProcessSubstOp) #

gmapT :: (forall b. Data b => b -> b) -> ProcessSubstOp -> ProcessSubstOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProcessSubstOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProcessSubstOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProcessSubstOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProcessSubstOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProcessSubstOp -> m ProcessSubstOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessSubstOp -> m ProcessSubstOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessSubstOp -> m ProcessSubstOp #

Ord ProcessSubstOp Source # 
Read ProcessSubstOp Source # 
Show ProcessSubstOp Source # 
Pretty ProcessSubstOp Source # 

Manipulation

stringToWord :: String -> Word Source #

Convert a string to an unquoted word.

unquote :: Word -> String Source #

Remove all quoting characters from a word.