Language.Sh.Map
- class (Monad m, Functor m) => ExpressionMapperM m f | f -> m where
- mapCommandsM :: f -> [Command] -> m [Command]
- defaultMapCommandsM :: f -> [Command] -> m [Command]
- mapCommandM :: f -> Command -> m Command
- defaultMapCommandM :: f -> Command -> m Command
- mapListM :: f -> AndOrList -> m AndOrList
- defaultMapListM :: f -> AndOrList -> m AndOrList
- mapPipelineM :: f -> Pipeline -> m Pipeline
- defaultMapPipelineM :: f -> Pipeline -> m Pipeline
- mapStatementM :: f -> Statement -> m Statement
- defaultMapStatementM :: f -> Statement -> m Statement
- mapCompoundM :: f -> CompoundStatement -> m CompoundStatement
- defaultMapCompoundM :: f -> CompoundStatement -> m CompoundStatement
- mapTermsM :: f -> Term -> m [Term]
- defaultMapTermsM :: f -> Term -> m [Term]
- mapTermM :: f -> Term -> m Term
- defaultMapTermM :: f -> Term -> m Term
- mapWordM :: f -> Word -> m Word
- defaultMapWordM :: f -> Word -> m Word
- mapLexemesM :: f -> Lexeme -> m [Lexeme]
- defaultMapLexemesM :: f -> Lexeme -> m [Lexeme]
- mapLexemeM :: f -> Lexeme -> m Lexeme
- defaultMapLexemeM :: f -> Lexeme -> m Lexeme
- mapExpansionM :: f -> Expansion -> m Expansion
- defaultMapExpansionM :: f -> Expansion -> m Expansion
- mapAssignmentM :: f -> Assignment -> m Assignment
- defaultMapAssignmentM :: f -> Assignment -> m Assignment
- mapRedirM :: f -> Redir -> m Redir
- defaultMapRedirM :: f -> Redir -> m Redir
- class ExpressionMapper f where
- mapCommands :: f -> [Command] -> [Command]
- defaultMapCommands :: f -> [Command] -> [Command]
- mapCommand :: f -> Command -> Command
- defaultMapCommand :: f -> Command -> Command
- mapList :: f -> AndOrList -> AndOrList
- defaultMapList :: f -> AndOrList -> AndOrList
- mapPipeline :: f -> Pipeline -> Pipeline
- defaultMapPipeline :: f -> Pipeline -> Pipeline
- mapStatement :: f -> Statement -> Statement
- defaultMapStatement :: f -> Statement -> Statement
- mapCompound :: f -> CompoundStatement -> CompoundStatement
- defaultMapCompound :: f -> CompoundStatement -> CompoundStatement
- mapTerms :: f -> Term -> [Term]
- defaultMapTerms :: f -> Term -> [Term]
- mapTerm :: f -> Term -> Term
- defaultMapTerm :: f -> Term -> Term
- mapWord :: f -> Word -> Word
- defaultMapWord :: f -> Word -> Word
- mapLexemes :: f -> Lexeme -> [Lexeme]
- defaultMapLexemes :: f -> Lexeme -> [Lexeme]
- mapLexeme :: f -> Lexeme -> Lexeme
- defaultMapLexeme :: f -> Lexeme -> Lexeme
- mapExpansion :: f -> Expansion -> Expansion
- defaultMapExpansion :: f -> Expansion -> Expansion
- mapAssignment :: f -> Assignment -> Assignment
- defaultMapAssignment :: f -> Assignment -> Assignment
- mapRedir :: f -> Redir -> Redir
- defaultMapRedir :: f -> Redir -> Redir
Documentation
class (Monad m, Functor m) => ExpressionMapperM m f | f -> m whereSource
The idea here is to prevent duplicating code needlessly. We could go even more extreme and make a third parameter, but then we have WAY too many instances, and they all depend on every other one anyway... class Applicative a => ExpressionMapper a f t where mapSh :: f -> t -> a t
Methods
mapCommandsM :: f -> [Command] -> m [Command]Source
defaultMapCommandsM :: f -> [Command] -> m [Command]Source
mapCommandM :: f -> Command -> m CommandSource
defaultMapCommandM :: f -> Command -> m CommandSource
mapListM :: f -> AndOrList -> m AndOrListSource
defaultMapListM :: f -> AndOrList -> m AndOrListSource
mapPipelineM :: f -> Pipeline -> m PipelineSource
defaultMapPipelineM :: f -> Pipeline -> m PipelineSource
mapStatementM :: f -> Statement -> m StatementSource
defaultMapStatementM :: f -> Statement -> m StatementSource
mapCompoundM :: f -> CompoundStatement -> m CompoundStatementSource
defaultMapCompoundM :: f -> CompoundStatement -> m CompoundStatementSource
mapTermsM :: f -> Term -> m [Term]Source
defaultMapTermsM :: f -> Term -> m [Term]Source
mapTermM :: f -> Term -> m TermSource
defaultMapTermM :: f -> Term -> m TermSource
mapWordM :: f -> Word -> m WordSource
defaultMapWordM :: f -> Word -> m WordSource
mapLexemesM :: f -> Lexeme -> m [Lexeme]Source
defaultMapLexemesM :: f -> Lexeme -> m [Lexeme]Source
mapLexemeM :: f -> Lexeme -> m LexemeSource
defaultMapLexemeM :: f -> Lexeme -> m LexemeSource
mapExpansionM :: f -> Expansion -> m ExpansionSource
defaultMapExpansionM :: f -> Expansion -> m ExpansionSource
mapAssignmentM :: f -> Assignment -> m AssignmentSource
defaultMapAssignmentM :: f -> Assignment -> m AssignmentSource
mapRedirM :: f -> Redir -> m RedirSource
defaultMapRedirM :: f -> Redir -> m RedirSource
Instances
(Monad m, Functor m) => ExpressionMapperM m (Redir -> m Redir) | |
(Monad m, Functor m) => ExpressionMapperM m (Assignment -> m Assignment) | |
(Monad m, Functor m) => ExpressionMapperM m (Expansion -> m Expansion) | |
(Monad m, Functor m) => ExpressionMapperM m (Lexeme -> m [Lexeme]) | |
(Monad m, Functor m) => ExpressionMapperM m (Lexeme -> m Lexeme) | |
(Monad m, Functor m) => ExpressionMapperM m (Word -> m Word) | |
(Monad m, Functor m) => ExpressionMapperM m (CompoundStatement -> m CompoundStatement) | |
(Monad m, Functor m) => ExpressionMapperM m (Statement -> m Statement) | |
(Monad m, Functor m) => ExpressionMapperM m (Pipeline -> m Pipeline) | |
(Monad m, Functor m) => ExpressionMapperM m (AndOrList -> m AndOrList) | |
(Monad m, Functor m) => ExpressionMapperM m (Command -> m Command) |
class ExpressionMapper f whereSource
Methods
mapCommands :: f -> [Command] -> [Command]Source
defaultMapCommands :: f -> [Command] -> [Command]Source
mapCommand :: f -> Command -> CommandSource
defaultMapCommand :: f -> Command -> CommandSource
mapList :: f -> AndOrList -> AndOrListSource
defaultMapList :: f -> AndOrList -> AndOrListSource
mapPipeline :: f -> Pipeline -> PipelineSource
defaultMapPipeline :: f -> Pipeline -> PipelineSource
mapStatement :: f -> Statement -> StatementSource
defaultMapStatement :: f -> Statement -> StatementSource
mapCompound :: f -> CompoundStatement -> CompoundStatementSource
defaultMapCompound :: f -> CompoundStatement -> CompoundStatementSource
mapTerms :: f -> Term -> [Term]Source
defaultMapTerms :: f -> Term -> [Term]Source
mapTerm :: f -> Term -> TermSource
defaultMapTerm :: f -> Term -> TermSource
mapWord :: f -> Word -> WordSource
defaultMapWord :: f -> Word -> WordSource
mapLexemes :: f -> Lexeme -> [Lexeme]Source
defaultMapLexemes :: f -> Lexeme -> [Lexeme]Source
mapLexeme :: f -> Lexeme -> LexemeSource
defaultMapLexeme :: f -> Lexeme -> LexemeSource
mapExpansion :: f -> Expansion -> ExpansionSource
defaultMapExpansion :: f -> Expansion -> ExpansionSource
mapAssignment :: f -> Assignment -> AssignmentSource
defaultMapAssignment :: f -> Assignment -> AssignmentSource
mapRedir :: f -> Redir -> RedirSource
defaultMapRedir :: f -> Redir -> RedirSource
Instances
ExpressionMapper (Assignment -> Assignment) | |
ExpressionMapper (Redir -> Redir) | |
ExpressionMapper (Expansion -> Expansion) | |
ExpressionMapper (Lexeme -> [Lexeme]) | |
ExpressionMapper (Lexeme -> Lexeme) | |
ExpressionMapper (Word -> Word) | |
ExpressionMapper (CompoundStatement -> CompoundStatement) | |
ExpressionMapper (Statement -> Statement) | |
ExpressionMapper (Pipeline -> Pipeline) | |
ExpressionMapper (AndOrList -> AndOrList) | |
ExpressionMapper (Command -> Command) |