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

Safe HaskellSafe
LanguageHaskell98

Language.Bash.Syntax

Contents

Description

Shell script types.

Synopsis

Commands

data Command Source #

A Bash command with redirections.

Constructors

Command ShellCommand [Redir] 
Instances
Eq Command Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data Command Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: Command -> Constr #

dataTypeOf :: Command -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Command Source # 
Instance details

Defined in Language.Bash.Syntax

Show Command Source # 
Instance details

Defined in Language.Bash.Syntax

Generic Command Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep Command :: * -> * #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Pretty Command Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Command Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Command = D1 (MetaData "Command" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Command" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShellCommand) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Redir])))

data ShellCommand Source #

A Bash command.

Constructors

SimpleCommand [Assign] [Word]

A simple command consisting of assignments followed by words.

AssignBuiltin Word [Either Assign Word]

The shell builtins declare, eval, export, local, readonly, and typeset can accept both assignments and words as arguments.

FunctionDef String List

A function name and definition.

Coproc String Command

A named coprocess.

Subshell List

A (...) list, denoting a subshell.

Group List

A {...} list.

Arith String

An arithmetic expression.

Cond (CondExpr Word)

A Bash [[...]] conditional expression.

For String WordList List

A for name in words command. If in words is absent, the word list defaults to "$@".

ArithFor String List

An arithmetic for ((...)) command.

Select String WordList List

A select name in words command. If in words is absent, the word list defaults to "$@".

Case Word [CaseClause]

A case command.

If List List (Maybe List)

An if command, with a predicate, consequent, and alternative. elif clauses are parsed as nested if statements.

Until List List

An until command.

While List List

A while command.

Instances
Eq ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

Data ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: ShellCommand -> Constr #

dataTypeOf :: ShellCommand -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

Show ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

Generic ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep ShellCommand :: * -> * #

Pretty ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep ShellCommand Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep ShellCommand = D1 (MetaData "ShellCommand" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (((C1 (MetaCons "SimpleCommand" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Assign]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Word])) :+: (C1 (MetaCons "AssignBuiltin" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Assign Word])) :+: C1 (MetaCons "FunctionDef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List)))) :+: ((C1 (MetaCons "Coproc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Command)) :+: C1 (MetaCons "Subshell" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List))) :+: (C1 (MetaCons "Group" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List)) :+: C1 (MetaCons "Arith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :+: (((C1 (MetaCons "Cond" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CondExpr Word))) :+: C1 (MetaCons "For" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WordList) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List)))) :+: (C1 (MetaCons "ArithFor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List)) :+: C1 (MetaCons "Select" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WordList) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List))))) :+: ((C1 (MetaCons "Case" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CaseClause])) :+: C1 (MetaCons "If" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe List))))) :+: (C1 (MetaCons "Until" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List)) :+: C1 (MetaCons "While" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 List))))))

data WordList Source #

A word list or "$@".

Constructors

Args 
WordList [Word] 
Instances
Eq WordList Source # 
Instance details

Defined in Language.Bash.Syntax

Data WordList Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: WordList -> Constr #

dataTypeOf :: WordList -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WordList Source # 
Instance details

Defined in Language.Bash.Syntax

Show WordList Source # 
Instance details

Defined in Language.Bash.Syntax

Generic WordList Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep WordList :: * -> * #

Methods

from :: WordList -> Rep WordList x #

to :: Rep WordList x -> WordList #

Pretty WordList Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep WordList Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep WordList = D1 (MetaData "WordList" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Args" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "WordList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Word])))

data CaseClause Source #

A single case clause.

Constructors

CaseClause [Word] List CaseTerm 
Instances
Eq CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

Data CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: CaseClause -> Constr #

dataTypeOf :: CaseClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

Show CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

Generic CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep CaseClause :: * -> * #

Pretty CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep CaseClause Source # 
Instance details

Defined in Language.Bash.Syntax

data CaseTerm Source #

A case clause terminator.

Constructors

Break
;;
FallThrough
;&
Continue
;;&
Instances
Bounded CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Enum CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Eq CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Data CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: CaseTerm -> Constr #

dataTypeOf :: CaseTerm -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Read CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Show CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Generic CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep CaseTerm :: * -> * #

Methods

from :: CaseTerm -> Rep CaseTerm x #

to :: Rep CaseTerm x -> CaseTerm #

Pretty CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep CaseTerm Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep CaseTerm = D1 (MetaData "CaseTerm" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Break" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "FallThrough" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Continue" PrefixI False) (U1 :: * -> *)))

Redirections

data Redir Source #

A redirection.

Constructors

Redir

A redirection.

Fields

Heredoc

A here document.

Fields

Instances
Eq Redir Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data Redir Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: Redir -> Constr #

dataTypeOf :: Redir -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Redir Source # 
Instance details

Defined in Language.Bash.Syntax

Show Redir Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

showsPrec :: Int -> Redir -> ShowS #

show :: Redir -> String #

showList :: [Redir] -> ShowS #

Generic Redir Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep Redir :: * -> * #

Methods

from :: Redir -> Rep Redir x #

to :: Rep Redir x -> Redir #

Pretty Redir Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Redir Source # 
Instance details

Defined in Language.Bash.Syntax

data IODesc Source #

A redirection file descriptor.

Constructors

IONumber Int

A file descriptor number.

IOVar String

A variable {varname} to allocate a file descriptor for.

Instances
Eq IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: IODesc -> Constr #

dataTypeOf :: IODesc -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

Show IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

Generic IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep IODesc :: * -> * #

Methods

from :: IODesc -> Rep IODesc x #

to :: Rep IODesc x -> IODesc #

Pretty IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep IODesc Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep IODesc = D1 (MetaData "IODesc" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "IONumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "IOVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data RedirOp Source #

A redirection operator.

Instances
Bounded RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Enum RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Eq RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: RedirOp -> Constr #

dataTypeOf :: RedirOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Read RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Show RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Generic RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep RedirOp :: * -> * #

Methods

from :: RedirOp -> Rep RedirOp x #

to :: Rep RedirOp x -> RedirOp #

Pretty RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep RedirOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep RedirOp = D1 (MetaData "RedirOp" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (((C1 (MetaCons "In" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Out" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OutOr" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Append" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AndOut" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "AndAppend" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "HereString" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InAnd" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OutAnd" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InOut" PrefixI False) (U1 :: * -> *)))))

data HeredocOp Source #

A here document operator.

Constructors

Here
<<
HereStrip
<<-
Instances
Bounded HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Enum HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Eq HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Data HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: HeredocOp -> Constr #

dataTypeOf :: HeredocOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Read HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Show HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Generic HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep HeredocOp :: * -> * #

Pretty HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep HeredocOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep HeredocOp = D1 (MetaData "HeredocOp" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Here" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "HereStrip" PrefixI False) (U1 :: * -> *))

Lists

newtype List Source #

A compound list of statements.

Constructors

List [Statement] 
Instances
Eq List Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data List Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: List -> Constr #

dataTypeOf :: List -> DataType #

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

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

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

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

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

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

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

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

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

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

Read List Source # 
Instance details

Defined in Language.Bash.Syntax

Show List Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Generic List Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep List :: * -> * #

Methods

from :: List -> Rep List x #

to :: Rep List x -> List #

Pretty List Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep List Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep List = D1 (MetaData "List" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" True) (C1 (MetaCons "List" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement])))

data Statement Source #

A single statement in a list.

Constructors

Statement AndOr ListTerm 
Instances
Eq Statement Source # 
Instance details

Defined in Language.Bash.Syntax

Data Statement Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: Statement -> Constr #

dataTypeOf :: Statement -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Statement Source # 
Instance details

Defined in Language.Bash.Syntax

Show Statement Source # 
Instance details

Defined in Language.Bash.Syntax

Generic Statement Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep Statement :: * -> * #

Pretty Statement Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Statement Source # 
Instance details

Defined in Language.Bash.Syntax

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

data ListTerm Source #

A statement terminator.

Instances
Bounded ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Enum ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Eq ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Data ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: ListTerm -> Constr #

dataTypeOf :: ListTerm -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Read ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Show ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Generic ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep ListTerm :: * -> * #

Methods

from :: ListTerm -> Rep ListTerm x #

to :: Rep ListTerm x -> ListTerm #

Pretty ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep ListTerm Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep ListTerm = D1 (MetaData "ListTerm" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Sequential" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Asynchronous" PrefixI False) (U1 :: * -> *))

data AndOr Source #

A right-associative list of pipelines.

Constructors

Last Pipeline

The last pipeline of a list.

And Pipeline AndOr

A && construct.

Or Pipeline AndOr

A || construct.

Instances
Eq AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: AndOr -> Constr #

dataTypeOf :: AndOr -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

Show AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

showsPrec :: Int -> AndOr -> ShowS #

show :: AndOr -> String #

showList :: [AndOr] -> ShowS #

Generic AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep AndOr :: * -> * #

Methods

from :: AndOr -> Rep AndOr x #

to :: Rep AndOr x -> AndOr #

Pretty AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep AndOr Source # 
Instance details

Defined in Language.Bash.Syntax

data Pipeline Source #

A (possibly timed or inverted) pipeline, linked with | or |&.

Constructors

Pipeline 

Fields

  • timed :: Bool

    True if the pipeline is timed with time.

  • timedPosix :: Bool

    True if the pipeline is timed with the -p flag.

  • inverted :: Bool

    True if the pipeline is inverted with !.

  • commands :: [Command]

    A list of commands, separated by |, or |&. command1 |& command2 is treated as a shorthand for command1 2>&1 | command2.

Instances
Eq Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Data Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: Pipeline -> Constr #

dataTypeOf :: Pipeline -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Show Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Generic Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep Pipeline :: * -> * #

Methods

from :: Pipeline -> Rep Pipeline x #

to :: Rep Pipeline x -> Pipeline #

Pretty Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Pipeline Source # 
Instance details

Defined in Language.Bash.Syntax

Assignments

data Assign Source #

An assignment.

Instances
Eq Assign Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data Assign Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: Assign -> Constr #

dataTypeOf :: Assign -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Assign Source # 
Instance details

Defined in Language.Bash.Syntax

Show Assign Source # 
Instance details

Defined in Language.Bash.Syntax

Generic Assign Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep Assign :: * -> * #

Methods

from :: Assign -> Rep Assign x #

to :: Rep Assign x -> Assign #

Pretty Assign Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep Assign Source # 
Instance details

Defined in Language.Bash.Syntax

data AssignOp Source #

An assignment operator.

Constructors

Equals
=
PlusEquals
+=
Instances
Bounded AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Enum AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Eq AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Data AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: AssignOp -> Constr #

dataTypeOf :: AssignOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Read AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Show AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Generic AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep AssignOp :: * -> * #

Methods

from :: AssignOp -> Rep AssignOp x #

to :: Rep AssignOp x -> AssignOp #

Pretty AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep AssignOp Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep AssignOp = D1 (MetaData "AssignOp" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "Equals" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PlusEquals" PrefixI False) (U1 :: * -> *))

data RValue Source #

The right side of an assignment.

Constructors

RValue Word

A simple word.

RArray [(Maybe Word, Word)]

An array assignment, as (subscript, word) pairs.

Instances
Eq RValue Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

Data RValue Source # 
Instance details

Defined in Language.Bash.Syntax

Methods

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

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

toConstr :: RValue -> Constr #

dataTypeOf :: RValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RValue Source # 
Instance details

Defined in Language.Bash.Syntax

Show RValue Source # 
Instance details

Defined in Language.Bash.Syntax

Generic RValue Source # 
Instance details

Defined in Language.Bash.Syntax

Associated Types

type Rep RValue :: * -> * #

Methods

from :: RValue -> Rep RValue x #

to :: Rep RValue x -> RValue #

Pretty RValue Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep RValue Source # 
Instance details

Defined in Language.Bash.Syntax

type Rep RValue = D1 (MetaData "RValue" "Language.Bash.Syntax" "language-bash-0.8.0-Laf0XeX753qAQYqu5TsBj5" False) (C1 (MetaCons "RValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: C1 (MetaCons "RArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Maybe Word, Word)])))