syntactic-1.4: Generic abstract syntax, and utilities for embedded languages

Safe HaskellNone

Language.Syntactic.Traversal

Description

Generic traversals of AST terms

Synopsis

Documentation

gmapQ :: forall dom b. (forall a. ASTF dom a -> b) -> forall a. ASTF dom 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 dom. (forall a. ASTF dom a -> ASTF dom a) -> forall a. ASTF dom a -> ASTF dom aSource

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

everywhereUp :: (forall a. ASTF dom a -> ASTF dom a) -> forall a. ASTF dom a -> ASTF dom aSource

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

everywhereDown :: (forall a. ASTF dom a -> ASTF dom a) -> forall a. ASTF dom a -> ASTF dom aSource

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

data Args c sig whereSource

List of symbol arguments

Constructors

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

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 sigSource

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

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

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

listFold :: forall dom b. (forall sig. dom sig -> [b] -> b) -> forall a. ASTF dom a -> bSource

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

match :: forall dom a c. (forall sig. a ~ DenResult sig => dom sig -> Args (AST dom) sig -> c (Full a)) -> ASTF dom 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

query :: forall dom a c. (forall sig. a ~ DenResult sig => dom sig -> Args (AST dom) sig -> c (Full a)) -> ASTF dom a -> c (Full a)Source

Deprecated: Please use `match` instead.

simpleMatch :: forall dom a b. (forall sig. a ~ DenResult sig => dom sig -> Args (AST dom) sig -> b) -> ASTF dom a -> bSource

A version of match with a simpler result type

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

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

simpleFold :: forall dom b. (forall sig. dom sig -> Args (Const b) sig -> b) -> forall a. ASTF dom a -> bSource

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

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

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

data WrapFull c a whereSource

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 :: c a -> WrapFull c (Full a) 

Fields

unwrapFull :: c a