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

Safe HaskellNone

Language.Syntactic.Sharing.Graph

Contents

Description

Representation and manipulation of abstract syntax graphs

Synopsis

Representation

newtype NodeId Source

Node identifier

Constructors

NodeId 

Fields

nodeInteger :: Integer
 

data Node ctx a whereSource

Placeholder for a syntax tree

Constructors

Node :: Sat ctx a => NodeId -> Node ctx (Full a) 

Instances

WitnessCons (Node ctx) 
ToTree (Node ctx) 
Render (Node ctx) 
(AlphaEq dom dom dom env, NodeEqEnv dom env) => AlphaEq (Node ctx) (Node ctx) dom env 

data SomeAST dom whereSource

An ASTF with hidden result type

Constructors

SomeAST :: Typeable a => ASTF dom a -> SomeAST dom 

Instances

NodeEqEnv dom (EqEnv dom) 
VarEqEnv (EqEnv dom) 

class NodeEqEnv dom a whereSource

Environment for alpha-equivalence

Methods

prjNodeEqEnv :: a -> NodeEnv domSource

modNodeEqEnv :: (NodeEnv dom -> NodeEnv dom) -> a -> aSource

Instances

NodeEqEnv dom (EqEnv dom) 

type EqEnv dom = ([(VarId, VarId)], NodeEnv dom)Source

data ASG ctx dom a Source

"Abstract Syntax Graph"

A representation of a syntax tree with explicit sharing. An ASG is valid if and only if inlineAll succeeds (and the numNodes field is correct).

Constructors

ASG 

Fields

topExpression :: ASTF (Node ctx :+: dom) a

Top-level expression

graphNodes :: [(NodeId, SomeAST (Node ctx :+: dom))]

Mapping from node id to sub-expression

numNodes :: NodeId

Total number of nodes

showASG :: ToTree dom => ASG ctx dom a -> StringSource

Show syntax graph using ASCII art

drawASG :: ToTree dom => ASG ctx dom a -> IO ()Source

Print syntax graph using ASCII art

reindexNodesAST :: (NodeId -> NodeId) -> AST (Node ctx :+: dom) a -> AST (Node ctx :+: dom) aSource

Update the node identifiers in an AST using the supplied reindexing function

reindexNodes :: (NodeId -> NodeId) -> ASG ctx dom a -> ASG ctx dom aSource

Reindex the nodes according to the given index mapping. The number of nodes is unchanged, so if the index mapping is not 1:1, the resulting graph will contain duplicates.

reindexNodesFrom0 :: ASG ctx dom a -> ASG ctx dom aSource

Reindex the nodes to be in the range [0 .. l-1], where l is the number of nodes in the graph

nubNodes :: ASG ctx dom a -> ASG ctx dom aSource

Remove duplicate nodes from a graph. The function only looks at the NodeId of each node. The numNodes field is updated accordingly.

liftSome2 :: (forall a b. ASTF (Node ctx :+: dom) a -> ASTF (Node ctx :+: dom) b -> c) -> SomeAST (Node ctx :+: dom) -> SomeAST (Node ctx :+: dom) -> cSource

Folding

data SyntaxPF dom a whereSource

Pattern functor representation of an AST with Nodes

Constructors

AppPF :: a -> a -> SyntaxPF dom a 
NodePF :: NodeId -> a -> SyntaxPF dom a 
DomPF :: dom b -> SyntaxPF dom a 

Instances

foldGraph :: forall ctx dom a b. (SyntaxPF dom b -> b) -> ASG ctx dom a -> (b, (Array NodeId b, [(NodeId, b)]))Source

Folding over a graph

The user provides a function to fold a single constructor (an "algebra"). The result contains the result of folding the whole graph as well as the result of each internal node, represented both as an array and an association list. Each node is processed exactly once.

Inlining

inlineAll :: forall ctx dom a. Typeable a => ASG ctx dom a -> ASTF dom aSource

Convert an ASG to an AST by inlining all nodes

nodeChildren :: ASG ctx dom a -> [(NodeId, [NodeId])]Source

Find the child nodes of each node in an expression. The child nodes of a node n are the first nodes along all paths from n.

occurrences :: ASG ctx dom a -> Array NodeId IntSource

Count the number of occurrences of each node in an expression

inlineSingle :: forall ctx dom a. Typeable a => ASG ctx dom a -> ASG ctx dom aSource

Inline all nodes that are not shared

Sharing

hashNodes :: ExprEq dom => ASG ctx dom a -> (Array NodeId Hash, [(NodeId, Hash)])Source

Compute a table (both array and list representation) of hash values for each node

partitionNodes :: forall ctx dom a. (ExprEq dom, AlphaEq dom dom (Node ctx :+: dom) (EqEnv (Node ctx :+: dom))) => ASG ctx dom a -> [[NodeId]]Source

Partitions the nodes such that two nodes are in the same sub-list if and only if they are alpha-equivalent.

cse :: (ExprEq dom, AlphaEq dom dom (Node ctx :+: dom) (EqEnv (Node ctx :+: dom))) => ASG ctx dom a -> ASG ctx dom aSource

Common sub-expression elimination based on alpha-equivalence