erl_syntax_lib
Support library for abstract Erlang syntax trees.
Support library for abstract Erlang syntax trees.
This module contains utility functions for working with the abstract data type defined in the module erl_syntax.
DATA TYPES
info_pair() = {key(), term()}
key() = attributes | errors | exports | functions | imports | module | records | rules | warnings
ordset(T) = ordset(T) (see module //stdlib/ordsets)
syntaxTree() = syntaxTree() (see module erl_syntax)
An abstract syntax tree. See the erl_syntax module for details.
Functions
map(F::Function, Tree::syntaxTree()) -> syntaxTree()
Function = (syntaxTree()) -> syntaxTree()
Applies a function to each node of a syntax tree. The result of each application replaces the corresponding original node. The order of traversal is bottom-up.
See also: map_subtrees/2.
map_subtrees(F::Function, Tree::syntaxTree()) -> syntaxTree()
Function = (Tree) -> Tree1
Applies a function to each immediate subtree of a syntax tree. The result of each application replaces the corresponding original node.
See also: map/2.
fold(F::Function, Start::term(), Tree::syntaxTree()) -> term()
Function = (syntaxTree(), term()) -> term()
Folds a function over all nodes of a syntax tree. The result is
the value of Function(X1, Function(X2, ... Function(Xn, Start)
... ))
, where [X1, X2, ..., Xn]
are the nodes of
Tree
in a post-order traversal.
See also: fold_subtrees/3, foldl_listlist/3.
fold_subtrees(F::Function, Start::term(), Tree::syntaxTree()) -> term()
Function = (syntaxTree(), term()) -> term()
Folds a function over the immediate subtrees of a syntax tree.
This is similar to fold/3
, but only on the immediate
subtrees of Tree
, in left-to-right order; it does not
include the root node of Tree
.
See also: fold/3.
foldl_listlist(F::Function, Start::term(), Ls::[[term()]]) -> term()
Function = (term(), term()) -> term()
mapfold(F::Function, Start::term(), Tree::syntaxTree()) -> {syntaxTree(), term()}
Function = (syntaxTree(), term()) -> {syntaxTree(), term()}
Combines map and fold in a single operation. This is similar to
map/2
, but also propagates an extra value from each
application of the Function
to the next, while doing a
post-order traversal of the tree like fold/3
. The value
Start
is passed to the first function application, and
the final result is the result of the last application.
mapfold_subtrees(F::Function, Start::term(), Tree::syntaxTree()) -> {syntaxTree(), term()}
Function = (syntaxTree(), term()) -> {syntaxTree(), term()}
Does a mapfold operation over the immediate subtrees of a syntax
tree. This is similar to mapfold/3
, but only on the
immediate subtrees of Tree
, in left-to-right order; it
does not include the root node of Tree
.
See also: mapfold/3.
mapfoldl_listlist(F::Function, S::State, Ls::[[term()]]) -> {[[term()]], term()}
Function = (term(), term()) -> {term(), term()}
Like lists:mapfoldl/3
, but over a list of lists.
The list of lists in the result has the same structure as the given
list of lists.
variables(Tree::syntaxTree()) -> set(atom())
set(T) (see module //stdlib/sets)
Returns the names of variables occurring in a syntax tree, The result is a set of variable names represented by atoms. Macro names are not included.
See also: sets(3).
new_variable_name(Used::set(atom())) -> atom()
Returns an atom which is not already in the set Used
. This is
equivalent to new_variable_name(Function, Used)
, where Function
maps a given integer N
to the atom whose name consists of "V
"
followed by the numeral for N
.
See also: new_variable_name/2.
new_variable_name(F::Function, Used::set(atom())) -> atom()
Function = (integer()) -> atom()
Returns a user-named atom which is not already in the set
Used
. The atom is generated by applying the given
Function
to a generated integer. Integers are generated
using an algorithm which tries to keep the names randomly distributed
within a reasonably small range relative to the number of elements in
the set.
This function uses the module random
to generate new
keys. The seed it uses may be initialized by calling
random:seed/0
or random:seed/3
before this
function is first called.
See also: random(3), sets(3), new_variable_name/1.
new_variable_names(N::integer(), Used::set(atom())) -> [atom()]
new_variable_names(N::integer(), F::Function, Used::set(atom())) -> [atom()]
Function = (integer()) -> atom()
annotate_bindings(Tree::syntaxTree(), Bindings::ordset(atom())) -> syntaxTree()
Adds or updates annotations on nodes in a syntax tree.
Bindings
specifies the set of bound variables in the
environment of the top level node. The following annotations are
affected:
{env, Vars}
, representing the input environment of the subtree.{bound, Vars}
, representing the variables that are bound in the subtree.{free, Vars}
, representing the free variables in the subtree.
Bindings
and Vars
are ordered-set lists
(cf. module ordsets
) of atoms representing variable
names.
See also: ordsets(3), annotate_bindings/1.
annotate_bindings(Tree::syntaxTree()) -> syntaxTree()
Adds or updates annotations on nodes in a syntax tree.
Equivalent to annotate_bindings(Tree, Bindings)
where
the top-level environment Bindings
is taken from the
annotation {env, Bindings}
on the root node of
Tree
. An exception is thrown if no such annotation
should exist.
See also: annotate_bindings/2.
is_fail_expr(Tree::syntaxTree()) -> boolean()
Returns true
if Tree
represents an
expression which never terminates normally. Note that the reverse
does not apply. Currently, the detected cases are calls to
exit/1
, throw/1
,
erlang:error/1
and erlang:error/2
.
See also: erlang:error/1, erlang:error/2, erlang:exit/1, erlang:throw/1.
analyze_forms(Forms) -> [{Key, term()}]
Forms = syntaxTree() | [syntaxTree()]
Key = attributes | errors | exports | functions | imports | module | records | rules | warnings
Analyzes a sequence of "program forms". The given
Forms
may be a single syntax tree of type
form_list
, or a list of "program form" syntax trees. The
returned value is a list of pairs {Key, Info}
, where
each value of Key
occurs at most once in the list; the
absence of a particular key indicates that there is no well-defined
value for that key.
Each entry in the resulting list contains the following corresponding information about the program forms:
{attributes, Attributes}
Attributes = [{atom(), term()}]
Attributes
is a list of pairs representing the
names and corresponding values of all so-called "wild"
attributes (as e.g. "-compile(...)
") occurring in
Forms
(cf. analyze_wild_attribute/1
).
We do not guarantee that each name occurs at most once in the
list. The order of listing is not defined.
{errors, Errors}
Errors = [term()]
Errors
is the list of error descriptors of all
error_marker
nodes that occur in
Forms
. The order of listing is not defined.
{exports, Exports}
Exports = [FunctionName]
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Exports
is a list of representations of those
function names that are listed by export declaration attributes
in Forms
(cf.
analyze_export_attribute/1
). We do not guarantee
that each name occurs at most once in the list. The order of
listing is not defined.
{functions, Functions}
Functions = [{atom(), integer()}]
Functions
is a list of the names of the functions
that are defined in Forms
(cf.
analyze_function/1
). We do not guarantee that each
name occurs at most once in the list. The order of listing is
not defined.
{imports, Imports}
Imports = [{Module, Names}]
Module = atom()
Names = [FunctionName]
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Imports
is a list of pairs representing those
module names and corresponding function names that are listed
by import declaration attributes in Forms
(cf.
analyze_import_attribute/1
), where each
Module
occurs at most once in
Imports
. We do not guarantee that each name occurs
at most once in the lists of function names. The order of
listing is not defined.
{module, ModuleName}
ModuleName = atom()
ModuleName
is the name declared by a module
attribute in Forms
. If no module name is defined
in Forms
, the result will contain no entry for the
module
key. If multiple module name declarations
should occur, all but the first will be ignored.
{records, Records}
Records = [{atom(), Fields}]
Fields = [{atom(), Default}]
Default = none | syntaxTree()
Records
is a list of pairs representing the names
and corresponding field declarations of all record declaration
attributes occurring in Forms
. For fields declared
without a default value, the corresponding value for
Default
is the atom none
(cf.
analyze_record_attribute/1
). We do not guarantee
that each record name occurs at most once in the list. The
order of listing is not defined.
{rules, Rules}
Rules = [{atom(), integer()}]
Rules
is a list of the names of the rules that are
defined in Forms
(cf.
analyze_rule/1
). We do not guarantee that each
name occurs at most once in the list. The order of listing is
not defined.
{warnings, Warnings}
Warnings = [term()]
Warnings
is the list of error descriptors of all
warning_marker
nodes that occur in
Forms
. The order of listing is not defined.
The evaluation throws syntax_error
if an ill-formed
Erlang construct is encountered.
See also: analyze_export_attribute/1, analyze_function/1, analyze_import_attribute/1, analyze_record_attribute/1, analyze_rule/1, analyze_wild_attribute/1, erl_syntax:error_marker_info/1, erl_syntax:warning_marker_info/1.
analyze_form(Node::syntaxTree()) -> {atom(), term()} | atom()
Analyzes a "source code form" node. If Node
is a
"form" type (cf. erl_syntax:is_form/1
), the returned
value is a tuple {Type, Info}
where Type
is
the node type and Info
depends on Type
, as
follows:
{attribute, Info}
where Info = analyze_attribute(Node)
.
{error_marker, Info}
where Info =
erl_syntax:error_marker_info(Node)
.
{function, Info}
where Info = analyze_function(Node)
.
{rule, Info}
where Info = analyze_rule(Node)
.
{warning_marker, Info}
where Info =
erl_syntax:warning_marker_info(Node)
.
For other types of forms, only the node type is returned.
The evaluation throws syntax_error
if
Node
is not well-formed.
See also: analyze_attribute/1, analyze_function/1, analyze_rule/1, erl_syntax:error_marker_info/1, erl_syntax:is_form/1, erl_syntax:warning_marker_info/1.
analyze_attribute(Node::syntaxTree()) -> preprocessor | {atom(), atom()}
Analyzes an attribute node. If Node
represents a
preprocessor directive, the atom preprocessor
is
returned. Otherwise, if Node
represents a module
attribute "-<em>Name</em>...
", a tuple {Name,
Info}
is returned, where Info
depends on
Name
, as follows:
{module, Info}
where Info =
analyze_module_attribute(Node)
.
{export, Info}
where Info =
analyze_export_attribute(Node)
.
{import, Info}
where Info =
analyze_import_attribute(Node)
.
{file, Info}
where Info =
analyze_file_attribute(Node)
.
{record, Info}
where Info =
analyze_record_attribute(Node)
.
{Name, Info}
where {Name, Info} =
analyze_wild_attribute(Node)
.
The evaluation throws syntax_error
if Node
does not represent a well-formed module attribute.
See also: analyze_export_attribute/1, analyze_file_attribute/1, analyze_import_attribute/1, analyze_module_attribute/1, analyze_record_attribute/1, analyze_wild_attribute/1.
analyze_module_attribute(Node::syntaxTree()) -> Name::atom() | {Name::atom(), Variables::[atom()]}
Returns the module name and possible parameters declared by a
module attribute. If the attribute is a plain module declaration such
as -module(name)
, the result is the module name. If the attribute
is a parameterized module declaration, the result is a tuple
containing the module name and a list of the parameter variable
names.
The evaluation throws syntax_error
if Node
does not represent a
well-formed module attribute.
See also: analyze_attribute/1.
analyze_export_attribute(Node::syntaxTree()) -> [FunctionName]
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Returns the list of function names declared by an export attribute. We do not guarantee that each name occurs at most once in the list. The order of listing is not defined.
The evaluation throws syntax_error
if Node
does not represent a
well-formed export attribute.
See also: analyze_attribute/1.
analyze_function_name(Node::syntaxTree()) -> FunctionName
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Returns the function name represented by a syntax tree. If
Node
represents a function name, such as
"foo/1
" or "bloggs:fred/2
", a uniform
representation of that name is returned. Different nestings of arity
and module name qualifiers in the syntax tree does not affect the
result.
The evaluation throws syntax_error
if
Node
does not represent a well-formed function name.
analyze_import_attribute(Node::syntaxTree()) -> {atom(), [FunctionName]} | atom()
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Returns the module name and (if present) list of function names
declared by an import attribute. The returned value is an atom
Module
or a pair {Module, Names}
, where
Names
is a list of function names declared as imported
from the module named by Module
. We do not guarantee
that each name occurs at most once in Names
. The order
of listing is not defined.
The evaluation throws syntax_error
if Node
does not represent a
well-formed import attribute.
See also: analyze_attribute/1.
analyze_wild_attribute(Node::syntaxTree()) -> {atom(), term()}
Returns the name and value of a "wild" attribute. The result is
the pair {Name, Value}
, if Node
represents "-Name(Value)
".
Note that no checking is done whether Name
is a
reserved attribute name such as module
or
export
: it is assumed that the attribute is "wild".
The evaluation throws syntax_error
if Node
does not represent a
well-formed wild attribute.
See also: analyze_attribute/1.
analyze_record_attribute(Node::syntaxTree()) -> {atom(), Fields}
Fields = [{atom(), none | syntaxTree()}]
Returns the name and the list of fields of a record declaration
attribute. The result is a pair {Name, Fields}
, if
Node
represents "-record(Name, {...}).
",
where Fields
is a list of pairs {Label,
Default}
for each field "Label
" or "Label =
<em>Default</em>
" in the declaration, listed in left-to-right
order. If the field has no default-value declaration, the value for
Default
will be the atom none
. We do not
guarantee that each label occurs at most one in the list.
The evaluation throws syntax_error
if
Node
does not represent a well-formed record declaration
attribute.
See also: analyze_attribute/1, analyze_record_field/1.
analyze_record_expr(Node::syntaxTree()) -> {atom(), Info} | atom()
Info = {atom(), [{atom(), Value}]} | {atom(), atom()} | atom()
Value = none | syntaxTree()
Returns the record name and field name/names of a record
expression. If Node
has type record_expr
,
record_index_expr
or record_access
, a pair
{Type, Info}
is returned, otherwise an atom
Type
is returned. Type
is the node type of
Node
, and Info
depends on
Type
, as follows:
record_expr
:{atom(), [{atom(), Value}]}
record_access
:{atom(), atom()} | atom()
record_index_expr
:{atom(), atom()}
For a record_expr
node, Info
represents
the record name and the list of descriptors for the involved fields,
listed in the order they appear. (See
analyze_record_field/1
for details on the field
descriptors). For a record_access
node,
Info
represents the record name and the field name (or
if the record name is not included, only the field name; this is
allowed only in Mnemosyne-query syntax). For a
record_index_expr
node, Info
represents the
record name and the name field name.
The evaluation throws syntax_error
if
Node
represents a record expression that is not
well-formed.
See also: analyze_record_attribute/1, analyze_record_field/1.
analyze_record_field(Node::syntaxTree()) -> {atom(), Value}
Value = none | syntaxTree()
Returns the label and value-expression of a record field
specifier. The result is a pair {Label, Value}
, if
Node
represents "Label = <em>Value</em>
" or
"Label
", where in the first case, Value
is
a syntax tree, and in the second case Value
is
none
.
The evaluation throws syntax_error
if
Node
does not represent a well-formed record field
specifier.
See also: analyze_record_attribute/1, analyze_record_expr/1.
analyze_file_attribute(Node::syntaxTree()) -> {string(), integer()}
Returns the file name and line number of a file
attribute. The result is the pair {File, Line}
if
Node
represents "-file(File, Line).
".
The evaluation throws syntax_error
if
Node
does not represent a well-formed file
attribute.
See also: analyze_attribute/1.
analyze_function(Node::syntaxTree()) -> {atom(), integer()}
Returns the name and arity of a function definition. The result
is a pair {Name, A}
if Node
represents a
function definition "Name(<em>P_1</em>, ..., <em>P_A</em>) ->
...
".
The evaluation throws syntax_error
if
Node
does not represent a well-formed function
definition.
See also: analyze_rule/1.
analyze_rule(Node::syntaxTree()) -> {atom(), integer()}
Returns the name and arity of a Mnemosyne rule. The result is a
pair {Name, A}
if Node
represents a rule
"Name(<em>P_1</em>, ..., <em>P_A</em>) :- ...
".
The evaluation throws syntax_error
if
Node
does not represent a well-formed Mnemosyne
rule.
See also: analyze_function/1.
analyze_implicit_fun(Node::syntaxTree()) -> FunctionName
FunctionName = atom() | {atom(), integer()} | {ModuleName, FunctionName}
ModuleName = atom()
Returns the name of an implicit fun expression "fun
<em>F</em>
". The result is a representation of the function
name F
. (Cf. analyze_function_name/1
.)
The evaluation throws syntax_error
if
Node
does not represent a well-formed implicit fun.
See also: analyze_function_name/1.
analyze_application(Node::syntaxTree()) -> FunctionName | Arity
FunctionName = {atom(), Arity} | {ModuleName, FunctionName}
Arity = integer()
ModuleName = atom()
Returns the name of a called function. The result is a
representation of the name of the applied function F/A
,
if Node
represents a function application
"<em>F</em>(<em>X_1</em>, ..., <em>X_A</em>)
". If the
function is not explicitly named (i.e., F
is given by
some expression), only the arity A
is returned.
The evaluation throws syntax_error
if Node
does not represent a
well-formed application expression.
See also: analyze_function_name/1.
function_name_expansions(Names::[Name]) -> [{ShortName, Name}]
Name = ShortName | {atom(), Name}
ShortName = atom() | {atom(), integer()}
Creates a mapping from corresponding short names to full
function names. Names are represented by nested tuples of atoms and
integers (cf. analyze_function_name/1
). The result is a
list containing a pair {ShortName, Name}
for each
element Name
in the given list, where the corresponding
ShortName
is the rightmost-innermost part of
Name
. The list thus represents a finite mapping from
unqualified names to the corresponding qualified names.
Note: the resulting list can contain more than one tuple
{ShortName, Name}
for the same ShortName
,
possibly with different values for Name
, depending on
the given list.
See also: analyze_function_name/1.
strip_comments(Tree::syntaxTree()) -> syntaxTree()
Removes all comments from all nodes of a syntax tree. All other attributes (such as position information) remain unchanged. Standalone comments in form lists are removed; any other standalone comments are changed into null-comments (no text, no indentation).
to_comment(Tree) -> syntaxTree()
Equivalent to to_comment(Tree, "% ").
to_comment(Tree::syntaxTree(), Prefix::string()) -> syntaxTree()
Equivalent to to_comment(Tree, Prefix, F)
for a
default formatting function F
. The default
F
simply calls erl_prettypr:format/1
.
See also: to_comment/3, erl_prettypr:format/1.
to_comment(Tree::syntaxTree(), Prefix::string(), F::Printer) -> syntaxTree()
Printer = (syntaxTree()) -> string()
Transforms a syntax tree into an abstract comment. The lines of
the comment contain the text for Node
, as produced by
the given Printer
function. Each line of the comment is
prefixed by the string Prefix
(this does not include the
initial "%
" character of the comment line).
For example, the result of
to_comment(erl_syntax:abstract([a,b,c]))
represents
%% [a,b,c]
(cf. to_comment/1
).
Note: the text returned by the formatting function will be split automatically into separate comment lines at each line break. No extra work is needed.
See also: to_comment/1, to_comment/2.
limit(Tree, Depth) -> syntaxTree()
Equivalent to limit(Tree, Depth, Text)
using the
text "..."
as default replacement.
See also: limit/3, erl_syntax:text/1.
limit(Tree::syntaxTree(), Depth::integer(), Node::syntaxTree()) -> syntaxTree()
Limits a syntax tree to a specified depth. Replaces all non-leaf
subtrees in Tree
at the given Depth
by
Node
. If Depth
is negative, the result is
always Node
, even if Tree
has no subtrees.
When a group of subtrees (as e.g., the argument list of an
application
node) is at the specified depth, and there
are two or more subtrees in the group, these will be collectively
replaced by Node
even if they are leaf nodes. Groups of
subtrees that are above the specified depth will be limited in size,
as if each subsequent tree in the group were one level deeper than
the previous. E.g., if Tree
represents a list of
integers "[1, 2, 3, 4, 5, 6, 7, 8, 9, 10]
", the result
of limit(Tree, 5)
will represent [1, 2, 3, 4,
...]
.
The resulting syntax tree is typically only useful for pretty-printing or similar visual formatting.
See also: limit/2.
- map/2
- map_subtrees/2
- fold/2
- fold_subtrees/2
- foldl_listlist/2
- mapfold/2
- mapfold_subtrees/2
- mapfoldl_listlist/3
- variables/1
- new_variable_name/1
- new_variable_name/2
- new_variable_names/1
- new_variable_names/1-1
- annotate_bindings/1
- annotate_bindings/1-1
- is_fail_expr/1
- analyze_forms/1
- analyze_form/1
- analyze_attribute/1
- analyze_module_attribute/1
- analyze_export_attribute/1
- analyze_function_name/1
- analyze_import_attribute/1
- analyze_wild_attribute/1
- analyze_record_attribute/1
- analyze_record_expr/1
- analyze_record_field/1
- analyze_file_attribute/1
- analyze_function/1
- analyze_rule/1
- analyze_implicit_fun/1
- analyze_application/1
- function_name_expansions/1
- strip_comments/1
- to_comment/1
- to_comment/1-1
- to_comment/1-2
- limit/2
- limit/1