Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Direction
- data Query ast v = Query {
- qQuantifiers :: Quantifiers
- qPattern :: Annotated ast
- qResult :: v
- newtype Matcher a = Matcher (IntMap (UMap a))
- mkMatcher :: Matchable ast => Query ast v -> Matcher v
- mkLocalMatcher :: Matchable ast => AlphaEnv -> Query ast v -> Matcher v
- runMatcher :: (Matchable ast, MonadIO m) => Context -> Matcher v -> ast -> TransformT m [(Substitution, v)]
- type Rewrite ast = Query ast (Template ast, MatchResultTransformer)
- mkRewrite :: Quantifiers -> Annotated ast -> Annotated ast -> Rewrite ast
- type Rewriter = Matcher (RewriterResult Universe)
- mkRewriter :: Matchable ast => Rewrite ast -> Rewriter
- mkLocalRewriter :: Matchable ast => AlphaEnv -> Rewrite ast -> Rewriter
- runRewriter :: forall ast m. (Matchable ast, MonadIO m) => (RewriterResult Universe -> RewriterResult Universe) -> Context -> Rewriter -> ast -> TransformT m (MatchResult ast)
- data MatchResult ast
- = MatchResult Substitution (Template ast)
- | NoMatch
- data Template ast = Template {
- tTemplate :: Annotated ast
- tImports :: AnnotatedImports
- tDependents :: Maybe [Rewrite Universe]
- type MatchResultTransformer = Context -> MatchResult Universe -> IO (MatchResult Universe)
- defaultTransformer :: MatchResultTransformer
- addRewriteImports :: AnnotatedImports -> Rewrite ast -> Rewrite ast
- setRewriteTransformer :: MatchResultTransformer -> Rewrite ast -> Rewrite ast
- toURewrite :: Matchable ast => Rewrite ast -> Rewrite Universe
- fromURewrite :: Matchable ast => Rewrite Universe -> Rewrite ast
- ppRewrite :: Rewrite Universe -> String
- rewritesWithDependents :: [Rewrite ast] -> [Rewrite ast]
- data RewriterResult ast = RewriterResult {}
- data ParentPrec
- data Context = Context {}
Documentation
Queries and Matchers
Query
is the primitive way to specify a matchable pattern (quantifiers
and expression). Whenever the pattern is matched, the associated result
will be returned.
Query | |
|
Matcher
is a compiled Query
. Several queries can be compiled and then
merged into a single compiled Matcher
via Semigroup
/Monoid
.
runMatcher :: (Matchable ast, MonadIO m) => Context -> Matcher v -> ast -> TransformT m [(Substitution, v)] Source #
Run a Matcher
on an expression in the given AlphaEnv
and return the
results from any matches. Results are accompanied by a Substitution
, which
maps Quantifiers
from the original Query
to the expressions they unified
with.
Rewrites and Rewriters
mkRewrite :: Quantifiers -> Annotated ast -> Annotated ast -> Rewrite ast Source #
Make a Rewrite
from given quantifiers and left- and right-hand sides.
runRewriter :: forall ast m. (Matchable ast, MonadIO m) => (RewriterResult Universe -> RewriterResult Universe) -> Context -> Rewriter -> ast -> TransformT m (MatchResult ast) Source #
Run a Rewriter
on an expression in the given AlphaEnv
and return the
MatchResult
s from any matches. Takes an extra function for rewriting the
RewriterResult
, which is run *before* the MatchResultTransformer
is run.
data MatchResult ast Source #
The result of matching the left-hand side of a Rewrite
.
Instances
Functor MatchResult Source # | |
Defined in Retrie.Types fmap :: (a -> b) -> MatchResult a -> MatchResult b # (<$) :: a -> MatchResult b -> MatchResult a # |
The right-hand side of a Rewrite
.
Template | |
|
type MatchResultTransformer = Context -> MatchResult Universe -> IO (MatchResult Universe) Source #
A MatchResultTransformer
allows the user to specify custom logic to
modify the result of matching the left-hand side of a rewrite
(the MatchResult
). The MatchResult
generated by this function is used
to effect the resulting AST rewrite.
For example, this transformer looks at the matched expression to build the resulting expression:
fancyMigration :: MatchResultTransformer fancyMigration ctxt matchResult | MatchResult sub t <- matchResult , HoleExpr e <- lookupSubst sub "x" = do e' <- ... some fancy IO computation using 'e' ... return $ MatchResult (extendSubst sub "x" (HoleExpr e')) t | otherwise = NoMatch main :: IO () main = runScript $ \opts -> do rrs <- parseRewrites opts [Adhoc "forall x. ... = ..."] return $ apply [ setRewriteTransformer fancyMigration rr | rr <- rrs ]
Since the MatchResultTransformer
can also modify the Template
, you
can construct an entirely novel right-hand side, add additional imports,
or inject new dependent rewrites.
defaultTransformer :: MatchResultTransformer Source #
The default transformer. Returns the MatchResult
unchanged.
Functions on Rewrites
addRewriteImports :: AnnotatedImports -> Rewrite ast -> Rewrite ast Source #
setRewriteTransformer :: MatchResultTransformer -> Rewrite ast -> Rewrite ast Source #
Set the MatchResultTransformer
for a Rewrite
.
toURewrite :: Matchable ast => Rewrite ast -> Rewrite Universe Source #
Inject a type-specific rewrite into the universal type.
fromURewrite :: Matchable ast => Rewrite Universe -> Rewrite ast Source #
Project a type-specific rewrite from the universal type.
rewritesWithDependents :: [Rewrite ast] -> [Rewrite ast] Source #
Filter a list of rewrites for those that introduce dependent rewrites.
Internal
data RewriterResult ast Source #
Wrapper that allows us to attach extra derived information to the
Template
supplied by the Rewrite
. Saves the user from specifying it.
RewriterResult | |
|
Instances
Functor RewriterResult Source # | |
Defined in Retrie.Types fmap :: (a -> b) -> RewriterResult a -> RewriterResult b # (<$) :: a -> RewriterResult b -> RewriterResult a # |
data ParentPrec Source #
Precedence of parent node in the AST.
HasPrec Fixity | Parent has precedence info. |
IsLhs | We are a pattern in a left-hand-side |
IsHsAppsTy | Parent is HsAppsTy |
NeverParen | Based on parent, we should never add parentheses. |
Context
maintained by AST traversals.
Context | |
|