Safe Haskell | None |
---|---|
Language | Haskell2010 |
Representation and manipulation of abstract syntax graphs
- newtype NodeId = NodeId {}
- showNode :: NodeId -> String
- data Node a where
- class NodeEqEnv dom a where
- prjNodeEqEnv :: a -> NodeEnv dom (Sat dom)
- modNodeEqEnv :: (NodeEnv dom (Sat dom) -> NodeEnv dom (Sat dom)) -> a -> a
- type EqEnv dom p = ([(VarId, VarId)], NodeEnv dom p)
- type NodeEnv dom p = (Array NodeId Hash, Array NodeId (ASTB dom p))
- data ASG dom a = ASG {
- topExpression :: ASTF (NodeDomain dom) a
- graphNodes :: [(NodeId, ASTSAT (NodeDomain dom))]
- numNodes :: NodeId
- type NodeDomain dom = (Node :+: dom) :|| Sat dom
- showASG :: forall dom a. StringTree dom => ASG dom a -> String
- drawASG :: StringTree dom => ASG dom a -> IO ()
- reindexNodesAST :: (NodeId -> NodeId) -> AST (NodeDomain dom) a -> AST (NodeDomain dom) a
- reindexNodes :: (NodeId -> NodeId) -> ASG dom a -> ASG dom a
- reindexNodesFrom0 :: ASG dom a -> ASG dom a
- nubNodes :: ASG dom a -> ASG dom a
- data SyntaxPF dom a where
- foldGraph :: forall dom a b. (SyntaxPF dom b -> b) -> ASG dom a -> (b, (Array NodeId b, [(NodeId, b)]))
- inlineAll :: forall dom a. ConstrainedBy dom Typeable => ASG dom a -> ASTF dom a
- nodeChildren :: ASG dom a -> [(NodeId, [NodeId])]
- occurrences :: ASG dom a -> Array NodeId Int
- inlineSingle :: forall dom a. ConstrainedBy dom Typeable => ASG dom a -> ASG dom a
- hashNodes :: Equality dom => ASG dom a -> (Array NodeId Hash, [(NodeId, Hash)])
- partitionNodes :: forall dom a. (Equality dom, AlphaEq dom dom (NodeDomain dom) (EqEnv (NodeDomain dom) (Sat dom))) => ASG dom a -> [[NodeId]]
- cse :: (Equality dom, AlphaEq dom dom (NodeDomain dom) (EqEnv (NodeDomain dom) (Sat dom))) => ASG dom a -> ASG dom a
Representation
Node identifier
Placeholder for a syntax tree
class NodeEqEnv dom a where Source
Environment for alpha-equivalence
prjNodeEqEnv :: a -> NodeEnv dom (Sat dom) Source
modNodeEqEnv :: (NodeEnv dom (Sat dom) -> NodeEnv dom (Sat dom)) -> a -> a Source
(~) (* -> Constraint) p (Sat dom) => NodeEqEnv dom (EqEnv dom p) 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).
ASG | |
|
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
Folding
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
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