retrie-1.2.2: A powerful, easy-to-use codemodding tool for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Retrie.Types

Synopsis

Documentation

data Direction Source #

Constructors

LeftToRight 
RightToLeft 

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Retrie.Types

Queries and Matchers

data Query ast v Source #

Query is the primitive way to specify a matchable pattern (quantifiers and expression). Whenever the pattern is matched, the associated result will be returned.

Constructors

Query 

Instances

Instances details
Bifunctor Query Source # 
Instance details

Defined in Retrie.Types

Methods

bimap :: (a -> b) -> (c -> d) -> Query a c -> Query b d #

first :: (a -> b) -> Query a c -> Query b c #

second :: (b -> c) -> Query a b -> Query a c #

Functor (Query ast) Source # 
Instance details

Defined in Retrie.Types

Methods

fmap :: (a -> b) -> Query ast a -> Query ast b #

(<$) :: a -> Query ast b -> Query ast a #

(Data (Annotated ast), Show ast, Show v) => Show (Query ast v) Source # 
Instance details

Defined in Retrie.Types

Methods

showsPrec :: Int -> Query ast v -> ShowS #

show :: Query ast v -> String #

showList :: [Query ast v] -> ShowS #

newtype Matcher a Source #

Matcher is a compiled Query. Several queries can be compiled and then merged into a single compiled Matcher via Semigroup/Monoid.

Constructors

Matcher (IntMap (UMap a)) 

Instances

Instances details
Functor Matcher Source # 
Instance details

Defined in Retrie.Types

Methods

fmap :: (a -> b) -> Matcher a -> Matcher b #

(<$) :: a -> Matcher b -> Matcher a #

Monoid (Matcher a) Source # 
Instance details

Defined in Retrie.Types

Methods

mempty :: Matcher a #

mappend :: Matcher a -> Matcher a -> Matcher a #

mconcat :: [Matcher a] -> Matcher a #

Semigroup (Matcher a) Source # 
Instance details

Defined in Retrie.Types

Methods

(<>) :: Matcher a -> Matcher a -> Matcher a #

sconcat :: NonEmpty (Matcher a) -> Matcher a #

stimes :: Integral b => b -> Matcher a -> Matcher a #

mkMatcher :: Matchable ast => Query ast v -> Matcher v Source #

Compile a Query into a Matcher.

mkLocalMatcher :: Matchable ast => AlphaEnv -> Query ast v -> Matcher v Source #

Compile a Query into a Matcher within a given local scope. Useful for introducing local matchers which only match within a given local scope.

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

type Rewrite ast = Query ast (Template ast, MatchResultTransformer) Source #

A Rewrite is a Query specialized to Template results, which have all the information necessary to replace one expression with another.

mkRewrite :: Quantifiers -> Annotated ast -> Annotated ast -> Rewrite ast Source #

Make a Rewrite from given quantifiers and left- and right-hand sides.

type Rewriter = Matcher (RewriterResult Universe) Source #

A Rewriter is a complied Rewrite, much like a Matcher is a compiled Query.

mkRewriter :: Matchable ast => Rewrite ast -> Rewriter Source #

Compile a Rewrite into a Rewriter.

mkLocalRewriter :: Matchable ast => AlphaEnv -> Rewrite ast -> Rewriter Source #

Compile a Rewrite into a Rewriter with a given local scope. Useful for introducing local matchers which only match within a given local scope.

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 MatchResults 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

Instances details
Functor MatchResult Source # 
Instance details

Defined in Retrie.Types

Methods

fmap :: (a -> b) -> MatchResult a -> MatchResult b #

(<$) :: a -> MatchResult b -> MatchResult a #

data Template ast Source #

The right-hand side of a Rewrite.

Constructors

Template 

Fields

Instances

Instances details
Functor Template Source # 
Instance details

Defined in Retrie.Types

Methods

fmap :: (a -> b) -> Template a -> Template b #

(<$) :: a -> Template b -> Template a #

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 #

Add imports to a Rewrite. Whenever the Rewrite successfully rewrites an expression, the imports are inserted into the enclosing module.

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.

ppRewrite :: Rewrite Universe -> String Source #

Pretty-print a Rewrite for debugging.

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.

Instances

Instances details
Functor RewriterResult Source # 
Instance details

Defined in Retrie.Types

Methods

fmap :: (a -> b) -> RewriterResult a -> RewriterResult b #

(<$) :: a -> RewriterResult b -> RewriterResult a #

data ParentPrec Source #

Precedence of parent node in the AST.

Constructors

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.

data Context Source #

Context maintained by AST traversals.

Constructors

Context 

Fields