cerl_trees
Basic functions on Core Erlang abstract syntax trees.
Basic functions on Core Erlang abstract syntax trees.
Syntax trees are defined in the module cerl.
DATA TYPES
cerl() = cerl() (see module cerl)
Functions
depth(Tree::cerl()) -> integer()
Returns the length of the longest path in the tree. A leaf
node has depth zero, the tree representing "{foo,
bar}
" has depth one, etc.
size(Tree::cerl()) -> integer()
Returns the number of nodes in Tree
.
map(F::Function, Tree::cerl()) -> cerl()
Function = (cerl()) -> cerl()
Maps a function onto the nodes of a tree. This replaces each node in the tree by the result of applying the given function on the original node, bottom-up.
See also: mapfold/3.
fold(F::Function, Unit::term(), Tree::cerl()) -> term()
Function = (cerl(), term()) -> term()
Does a fold operation over the nodes of the tree. The result
is the value of Function(X1, Function(X2, ... Function(Xn,
Unit) ... ))
, where X1, ..., Xn
are the nodes
of Tree
in a post-order traversal.
See also: mapfold/3.
mapfold(F::Function, Initial::term(), Tree::cerl()) -> {cerl(), term()}
Function = (cerl(), term()) -> {cerl(), term()}
variables(Tree::cerl()) -> [var_name()]
integer() | atom() | {atom(), integer()}
Returns an ordered-set list of the names of all variables in
the syntax tree. (This includes function name variables.) An
exception is thrown if Tree
does not represent a
well-formed Core Erlang syntax tree.
See also: free_variables/1.
free_variables(Tree::cerl()) -> [var_name()]
label(T::cerl() (see module cerl)) -> {cerl() (see module cerl), integer()}
Equivalent to label(Tree, 0).
label(Tree::cerl(), N::integer()) -> {cerl(), integer()}
Labels each expression in the tree. A term {label,
L}
is prefixed to the annotation list of each expression node,
where L is a unique number for every node, except for variables (and
function name variables) which get the same label if they represent
the same variable. Constant literal nodes are not labeled.
The returned value is a tuple {NewTree, Max}
, where
NewTree
is the labeled tree and Max
is 1
plus the largest label value used. All previous annotation terms on
the form {label, X}
are deleted.
The values of L used in the tree is a dense range from
N
to Max - 1
, where N =< Max
=< N + size(Tree)
. Note that it is possible that no
labels are used at all, i.e., N = Max
.
Note: All instances of free variables will be given distinct labels.