Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bash words and substitutions.
Synopsis
- type Word = [Span]
- data Span
- data Parameter = Parameter String (Maybe Word)
- data ParamSubst
- = Bare { }
- | Brace { }
- | Alt { }
- | Substring { }
- | Prefix { }
- | Indices { }
- | Length { }
- | Delete { }
- | Replace {
- indirect :: Bool
- parameter :: Parameter
- replaceAll :: Bool
- replaceDirection :: Maybe Direction
- pattern :: Word
- replacement :: Word
- | LetterCase {
- indirect :: Bool
- parameter :: Parameter
- letterCaseOp :: LetterCaseOp
- convertAll :: Bool
- pattern :: Word
- data AltOp
- data LetterCaseOp
- data Direction
- data ProcessSubstOp
- stringToWord :: String -> Word
- wordToString :: Word -> Maybe String
- unquote :: Word -> String
Words
An individual unit of a word.
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, |
ParamSubst ParamSubst | A parameter substitution. |
ArithSubst String | An arithmetic substitution. |
CommandSubst String | A command substitution. |
ProcessSubst ProcessSubstOp String | A process substitution. |
Instances
Parameters
A parameter name an optional subscript.
Instances
Data Parameter Source # | |
Defined in Language.Bash.Word 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 :: forall r r'. (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 # | |
Generic Parameter Source # | |
Read Parameter Source # | |
Show Parameter Source # | |
Eq Parameter Source # | |
Pretty Parameter Source # | |
Defined in Language.Bash.Word | |
type Rep Parameter Source # | |
Defined in Language.Bash.Word type Rep Parameter = D1 ('MetaData "Parameter" "Language.Bash.Word" "language-bash-0.11.1-inplace" '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.
Bare | |
Brace | |
Alt | |
Substring | |
Prefix | |
Indices | |
Length | |
Delete | |
Replace | |
| |
LetterCase | |
|
Instances
An alternation operator.
AltDefault |
|
AltAssign | '=', |
AltError |
|
AltReplace |
|
Instances
Data AltOp Source # | |
Defined in Language.Bash.Word 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 # 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 :: forall r r'. (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 # | |
Bounded AltOp Source # | |
Enum AltOp Source # | |
Generic AltOp Source # | |
Read AltOp Source # | |
Show AltOp Source # | |
Eq AltOp Source # | |
Ord AltOp Source # | |
Pretty AltOp Source # | |
Defined in Language.Bash.Word | |
type Rep AltOp Source # | |
Defined in Language.Bash.Word type Rep AltOp = D1 ('MetaData "AltOp" "Language.Bash.Word" "language-bash-0.11.1-inplace" 'False) ((C1 ('MetaCons "AltDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AltAssign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AltError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AltReplace" 'PrefixI 'False) (U1 :: Type -> Type))) |
data LetterCaseOp Source #
A letter case operator.
Instances
A string direction.
Instances
Process
data ProcessSubstOp Source #
A process substitution.
Instances
Manipulation
stringToWord :: String -> Word Source #
Convert a string to an unquoted word.