Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Custom SYB traversals explicitly designed for operating over the GHC AST.
Synopsis
- genericIsSubspan :: forall ast. Typeable ast => Proxy (Located ast) -> SrcSpan -> GenericQ (Maybe (Bool, ast))
- mkBindListT :: forall b m. (Data b, Monad m) => (Int -> b -> m [b]) -> GenericM m
- everywhereM' :: forall m. Monad m => GenericM m -> GenericM m
- smallestM :: forall m a. Monad m => GenericQ (Maybe (Bool, a)) -> (a -> GenericM m) -> GenericM m
- largestM :: forall m a. Monad m => GenericQ (Maybe (Bool, a)) -> (a -> GenericM m) -> GenericM m
Documentation
:: forall ast. Typeable ast | |
=> Proxy (Located ast) | The type of nodes we'd like to consider. |
-> SrcSpan | |
-> GenericQ (Maybe (Bool, ast)) |
A generic query intended to be used for calling smallestM
and
largestM
. If the current node is a Located
, returns whether or not the
given SrcSpan
is a subspan. For all other nodes, returns Nothing
, which
indicates uncertainty. The search strategy in smallestM
et al. will
continue searching uncertain nodes.
mkBindListT :: forall b m. (Data b, Monad m) => (Int -> b -> m [b]) -> GenericM m Source #
Lift a function that replaces a value with several values into a generic
function. The result doesn't perform any searching, so should be driven via
everywhereM
or friends.
The Int
argument is the index in the list being bound.
everywhereM' :: forall m. Monad m => GenericM m -> GenericM m Source #
Apply a monadic transformation everywhere in a top-down manner.
smallestM :: forall m a. Monad m => GenericQ (Maybe (Bool, a)) -> (a -> GenericM m) -> GenericM m Source #
Apply the given GenericM
at all every node whose children fail the
GenericQ
, but which passes the query itself.
The query must be a monotonic function when it returns Just
. That is, if
s
is a subtree of t
, q t
should return Just True
if q s
does. It
is the True-to-false edge of the query that triggers the transformation.
Why is the query a Maybe Bool
? The GHC AST intersperses Located
nodes
with data nodes, so for any given node we can only definitely return an
answer if it's a Located
. See genericIsSubspan
for how this parameter is
used.
largestM :: forall m a. Monad m => GenericQ (Maybe (Bool, a)) -> (a -> GenericM m) -> GenericM m Source #
Apply the given GenericM
at every node that passes the GenericQ
, but
don't descend into children if the query matches. Because this traversal is
root-first, this policy will find the largest subtrees for which the query
holds true.
Why is the query a Maybe Bool
? The GHC AST intersperses Located
nodes
with data nodes, so for any given node we can only definitely return an
answer if it's a Located
. See genericIsSubspan
for how this parameter is
used.