language-bash-0.8.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 # 
Instance details

Defined in Language.Bash.Word

Methods

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

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

Data Span Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Show Span Source # 
Instance details

Defined in Language.Bash.Word

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep Span :: * -> * #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

Pretty Span Source # 
Instance details

Defined in Language.Bash.Word

type Rep Span Source # 
Instance details

Defined in Language.Bash.Word

type Rep Span = D1 (MetaData "Span" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (((C1 (MetaCons "Char" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: C1 (MetaCons "Escape" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))) :+: (C1 (MetaCons "Single" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: (C1 (MetaCons "Double" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: C1 (MetaCons "ANSIC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word))))) :+: ((C1 (MetaCons "Locale" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: (C1 (MetaCons "Backquote" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: C1 (MetaCons "ParamSubst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParamSubst)))) :+: (C1 (MetaCons "ArithSubst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "CommandSubst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "ProcessSubst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessSubstOp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))

Parameters

data Parameter Source #

A parameter name an optional subscript.

Constructors

Parameter String (Maybe Word) 
Instances
Eq Parameter Source # 
Instance details

Defined in Language.Bash.Word

Data Parameter Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Show Parameter Source # 
Instance details

Defined in Language.Bash.Word

Generic Parameter Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep Parameter :: * -> * #

Pretty Parameter Source # 
Instance details

Defined in Language.Bash.Word

type Rep Parameter Source # 
Instance details

Defined in Language.Bash.Word

type Rep Parameter = D1 (MetaData "Parameter" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Parameter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word))))

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 # 
Instance details

Defined in Language.Bash.Word

Data ParamSubst Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Show ParamSubst Source # 
Instance details

Defined in Language.Bash.Word

Generic ParamSubst Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep ParamSubst :: * -> * #

Pretty ParamSubst Source # 
Instance details

Defined in Language.Bash.Word

type Rep ParamSubst Source # 
Instance details

Defined in Language.Bash.Word

type Rep ParamSubst = D1 (MetaData "ParamSubst" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (((C1 (MetaCons "Bare" PrefixI True) (S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :+: C1 (MetaCons "Brace" PrefixI True) (S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter))) :+: (C1 (MetaCons "Alt" PrefixI True) ((S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :*: (S1 (MetaSel (Just "testNull") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "altOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AltOp) :*: S1 (MetaSel (Just "altWord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))) :+: (C1 (MetaCons "Substring" PrefixI True) ((S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :*: (S1 (MetaSel (Just "subOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word) :*: S1 (MetaSel (Just "subLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word))) :+: C1 (MetaCons "Prefix" PrefixI True) (S1 (MetaSel (Just "prefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "modifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))))) :+: ((C1 (MetaCons "Indices" PrefixI True) (S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :+: C1 (MetaCons "Length" PrefixI True) (S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter))) :+: (C1 (MetaCons "Delete" PrefixI True) ((S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :*: (S1 (MetaSel (Just "longest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "deleteDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Direction) :*: S1 (MetaSel (Just "pattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))) :+: (C1 (MetaCons "Replace" PrefixI True) ((S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter) :*: S1 (MetaSel (Just "replaceAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :*: (S1 (MetaSel (Just "replaceDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Direction)) :*: (S1 (MetaSel (Just "pattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word) :*: S1 (MetaSel (Just "replacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))) :+: C1 (MetaCons "LetterCase" PrefixI True) ((S1 (MetaSel (Just "indirect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter)) :*: (S1 (MetaSel (Just "letterCaseOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LetterCaseOp) :*: (S1 (MetaSel (Just "convertAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "pattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word))))))))

data AltOp Source #

An alternation operator.

Constructors

AltDefault

-, :-

AltAssign

'=', :=

AltError

?, :?

AltReplace

+, :+

Instances
Bounded AltOp Source # 
Instance details

Defined in Language.Bash.Word

Enum AltOp Source # 
Instance details

Defined in Language.Bash.Word

Eq AltOp Source # 
Instance details

Defined in Language.Bash.Word

Methods

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

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

Data AltOp Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Show AltOp Source # 
Instance details

Defined in Language.Bash.Word

Methods

showsPrec :: Int -> AltOp -> ShowS #

show :: AltOp -> String #

showList :: [AltOp] -> ShowS #

Generic AltOp Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep AltOp :: * -> * #

Methods

from :: AltOp -> Rep AltOp x #

to :: Rep AltOp x -> AltOp #

Pretty AltOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep AltOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep AltOp = D1 (MetaData "AltOp" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) ((C1 (MetaCons "AltDefault" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AltAssign" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "AltError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AltReplace" PrefixI False) (U1 :: * -> *)))

data LetterCaseOp Source #

A letter case operator.

Constructors

ToLower 
ToUpper 
Instances
Bounded LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Enum LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Eq LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Data LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Read LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Show LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Generic LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep LetterCaseOp :: * -> * #

Pretty LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep LetterCaseOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep LetterCaseOp = D1 (MetaData "LetterCaseOp" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "ToLower" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ToUpper" PrefixI False) (U1 :: * -> *))

data Direction Source #

A string direction.

Constructors

Front 
Back 
Instances
Bounded Direction Source # 
Instance details

Defined in Language.Bash.Word

Enum Direction Source # 
Instance details

Defined in Language.Bash.Word

Eq Direction Source # 
Instance details

Defined in Language.Bash.Word

Data Direction Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Read Direction Source # 
Instance details

Defined in Language.Bash.Word

Show Direction Source # 
Instance details

Defined in Language.Bash.Word

Generic Direction Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep Direction :: * -> * #

Pretty Direction Source # 
Instance details

Defined in Language.Bash.Word

type Rep Direction Source # 
Instance details

Defined in Language.Bash.Word

type Rep Direction = D1 (MetaData "Direction" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Front" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Back" PrefixI False) (U1 :: * -> *))

Process

data ProcessSubstOp Source #

A process substitution.

Constructors

ProcessIn
<
ProcessOut
>
Instances
Bounded ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Enum ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Eq ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Data ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

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 # 
Instance details

Defined in Language.Bash.Word

Read ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Show ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Generic ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

Associated Types

type Rep ProcessSubstOp :: * -> * #

Pretty ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep ProcessSubstOp Source # 
Instance details

Defined in Language.Bash.Word

type Rep ProcessSubstOp = D1 (MetaData "ProcessSubstOp" "Language.Bash.Word" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "ProcessIn" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ProcessOut" PrefixI False) (U1 :: * -> *))

Manipulation

stringToWord :: String -> Word Source #

Convert a string to an unquoted word.

wordToString :: Word -> Maybe String Source #

If a word is a plain, unquoted string (e.g. the result of stringToWord), returns Just that string; otherwise, returns Nothing.

unquote :: Word -> String Source #

Remove all quoting characters from a word.