syntactic-3.6.3: Generic representation and manipulation of abstract syntax

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Traversal

Description

Generic traversals of AST terms

Synopsis

Documentation

gmapQ :: forall sym b. (forall a. ASTF sym a -> b) -> forall a. ASTF sym a -> [b] Source #

Map a function over all immediate sub-terms, collecting the results in a list (corresponds to the function with the same name in Scrap Your Boilerplate)

gmapT :: forall sym. (forall a. ASTF sym a -> ASTF sym a) -> forall a. ASTF sym a -> ASTF sym a Source #

Map a function over all immediate sub-terms (corresponds to the function with the same name in Scrap Your Boilerplate)

everywhereUp :: (forall a. ASTF sym a -> ASTF sym a) -> forall a. ASTF sym a -> ASTF sym a Source #

Apply a transformation bottom-up over an AST (corresponds to everywhere in Scrap Your Boilerplate)

everywhereDown :: (forall a. ASTF sym a -> ASTF sym a) -> forall a. ASTF sym a -> ASTF sym a Source #

Apply a transformation top-down over an AST (corresponds to everywhere' in Scrap Your Boilerplate)

universe :: ASTF sym a -> [EF (AST sym)] Source #

List all sub-terms (corresponds to universe in Uniplate)

data Args c sig where Source #

List of symbol arguments

Constructors

Nil :: Args c (Full a) 
(:*) :: c (Full a) -> Args c sig -> Args c (a :-> sig) infixr 9 

listArgs :: (forall a. c (Full a) -> b) -> Args c sig -> [b] Source #

Map a function over an Args list and collect the results in an ordinary list

mapArgs :: (forall a. c1 (Full a) -> c2 (Full a)) -> forall sig. Args c1 sig -> Args c2 sig Source #

Map a function over an Args list

mapArgsA :: Applicative f => (forall a. c1 (Full a) -> f (c2 (Full a))) -> forall sig. Args c1 sig -> f (Args c2 sig) Source #

Map an applicative function over an Args list

mapArgsM :: Monad m => (forall a. c1 (Full a) -> m (c2 (Full a))) -> forall sig. Args c1 sig -> m (Args c2 sig) Source #

Map a monadic function over an Args list

foldrArgs :: (forall a. c (Full a) -> b -> b) -> b -> forall sig. Args c sig -> b Source #

Right fold for an Args list

appArgs :: AST sym sig -> Args (AST sym) sig -> ASTF sym (DenResult sig) Source #

Apply a (partially applied) symbol to a list of argument terms

listFold :: forall sym b. (forall sig. sym sig -> [b] -> b) -> forall a. ASTF sym a -> b Source #

Fold an AST using a list to hold the results of sub-terms

match :: forall sym a c. (forall sig. a ~ DenResult sig => sym sig -> Args (AST sym) sig -> c (Full a)) -> ASTF sym a -> c (Full a) Source #

"Pattern match" on an AST using a function that gets direct access to the top-most symbol and its sub-trees

simpleMatch :: forall sym a b. (forall sig. a ~ DenResult sig => sym sig -> Args (AST sym) sig -> b) -> ASTF sym a -> b Source #

A version of match with a simpler result type

fold :: forall sym c. (forall sig. sym sig -> Args c sig -> c (Full (DenResult sig))) -> forall a. ASTF sym a -> c (Full a) Source #

Fold an AST using an Args list to hold the results of sub-terms

simpleFold :: forall sym b. (forall sig. sym sig -> Args (Const b) sig -> b) -> forall a. ASTF sym a -> b Source #

Simplified version of fold for situations where all intermediate results have the same type

matchTrans :: forall sym sym' c a. (forall sig. a ~ DenResult sig => sym sig -> Args (AST sym) sig -> c (ASTF sym' a)) -> ASTF sym a -> c (ASTF sym' a) Source #

A version of match where the result is a transformed syntax tree, wrapped in a type constructor c

mapAST :: (forall sig'. sym1 sig' -> sym2 sig') -> AST sym1 sig -> AST sym2 sig Source #

Update the symbols in an AST

data WrapFull c a where Source #

Can be used to make an arbitrary type constructor indexed by (Full a). This is useful as the type constructor parameter of Args. That is, use

Args (WrapFull c) ...

instead of

Args c ...

if c is not indexed by (Full a).

Constructors

WrapFull :: {..} -> WrapFull c (Full a) 

Fields

toTree :: forall dom a b. (forall sig. dom sig -> b) -> ASTF dom a -> Tree b Source #

Convert an AST to a Tree