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

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.Sharing.Graph

Contents

Description

Representation and manipulation of abstract syntax graphs

Synopsis

Representation

newtype NodeId Source #

Node identifier

Constructors

NodeId 

Fields

Instances
Enum NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Eq NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

(==) :: NodeId -> NodeId -> Bool #

(/=) :: NodeId -> NodeId -> Bool #

Integral NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Num NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Ord NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Real NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Show NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Ix NodeId Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

p ~ Sat dom => NodeEqEnv dom (EqEnv dom p) Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

prjNodeEqEnv :: EqEnv dom p -> NodeEnv dom (Sat dom) Source #

modNodeEqEnv :: (NodeEnv dom (Sat dom) -> NodeEnv dom (Sat dom)) -> EqEnv dom p -> EqEnv dom p Source #

VarEqEnv (EqEnv dom p) Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

prjVarEqEnv :: EqEnv dom p -> [(VarId, VarId)] Source #

modVarEqEnv :: ([(VarId, VarId)] -> [(VarId, VarId)]) -> EqEnv dom p -> EqEnv dom p Source #

data Node a where Source #

Placeholder for a syntax tree

Constructors

Node :: NodeId -> Node (Full a) 
Instances
StringTree Node Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Render Node Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

renderSym :: Node sig -> String Source #

renderArgs :: [String] -> Node sig -> String Source #

Constrained Node Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Associated Types

type Sat Node :: * -> Constraint Source #

Methods

exprDict :: Node a -> Dict (Sat Node (DenResult a)) Source #

(AlphaEq dom dom dom env, NodeEqEnv dom env) => AlphaEq Node Node dom env Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

alphaEqSym :: Node a -> Args (AST dom) a -> Node b -> Args (AST dom) b -> Reader env Bool Source #

type Sat Node Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

type Sat Node = Top

class NodeEqEnv dom a where Source #

Environment for alpha-equivalence

Minimal complete definition

prjNodeEqEnv, modNodeEqEnv

Methods

prjNodeEqEnv :: a -> NodeEnv dom (Sat dom) Source #

modNodeEqEnv :: (NodeEnv dom (Sat dom) -> NodeEnv dom (Sat dom)) -> a -> a Source #

Instances
p ~ Sat dom => NodeEqEnv dom (EqEnv dom p) Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

prjNodeEqEnv :: EqEnv dom p -> NodeEnv dom (Sat dom) Source #

modNodeEqEnv :: (NodeEnv dom (Sat dom) -> NodeEnv dom (Sat dom)) -> EqEnv dom p -> EqEnv dom p Source #

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

type NodeEnv dom p = (Array NodeId Hash, Array NodeId (ASTB dom p)) Source #

data ASG 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

type NodeDomain dom = (Node :+: dom) :|| Sat dom Source #

showASG :: forall dom a. StringTree dom => ASG dom a -> String Source #

Show syntax graph using ASCII art

drawASG :: StringTree dom => ASG dom a -> IO () Source #

Print syntax graph using ASCII art

reindexNodesAST :: (NodeId -> NodeId) -> AST (NodeDomain dom) a -> AST (NodeDomain dom) a Source #

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

reindexNodes :: (NodeId -> NodeId) -> ASG dom a -> ASG dom a Source #

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 dom a -> ASG dom a Source #

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

nubNodes :: ASG dom a -> ASG dom a Source #

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

Folding

data SyntaxPF dom a where Source #

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
Functor (SyntaxPF dom) Source # 
Instance details

Defined in Language.Syntactic.Sharing.Graph

Methods

fmap :: (a -> b) -> SyntaxPF dom a -> SyntaxPF dom b #

(<$) :: a -> SyntaxPF dom b -> SyntaxPF dom a #

foldGraph :: forall dom a b. (SyntaxPF dom b -> b) -> ASG 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 dom a. ConstrainedBy dom Typeable => ASG dom a -> ASTF dom a Source #

Convert an ASG to an AST by inlining all nodes

nodeChildren :: ASG 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 dom a -> Array NodeId Int Source #

Count the number of occurrences of each node in an expression

inlineSingle :: forall dom a. ConstrainedBy dom Typeable => ASG dom a -> ASG dom a Source #

Inline all nodes that are not shared

Sharing

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

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

partitionNodes :: forall dom a. (Equality dom, AlphaEq dom dom (NodeDomain dom) (EqEnv (NodeDomain dom) (Sat dom))) => ASG 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 :: (Equality dom, AlphaEq dom dom (NodeDomain dom) (EqEnv (NodeDomain dom) (Sat dom))) => ASG dom a -> ASG dom a Source #

Common sub-expression elimination based on alpha-equivalence