erl_syntax
Abstract Erlang syntax trees.
Abstract Erlang syntax trees.
This module defines an abstract data type for representing Erlang
source code as syntax trees, in a way that is backwards compatible
with the data structures created by the Erlang standard library
parser module erl_parse
(often referred to as "parse
trees", which is a bit of a misnomer). This means that all
erl_parse
trees are valid abstract syntax trees, but the
reverse is not true: abstract syntax trees can in general not be used
as input to functions expecting an erl_parse
tree.
However, as long as an abstract syntax tree represents a correct
Erlang program, the function revert/1 should be able to
transform it to the corresponding erl_parse
representation.
A recommended starting point for the first-time user is the documentation of the syntaxTree() data type, and the function type/1.
NOTES:
This module deals with the composition and decomposition of syntactic entities (as opposed to semantic ones); its purpose is to hide all direct references to the data structures used to represent these entities. With few exceptions, the functions in this module perform no semantic interpretation of their inputs, and in general, the user is assumed to pass type-correct arguments - if this is not done, the effects are not defined.
With the exception of the erl_parse() data structures,
the internal representations of abstract syntax trees are subject to
change without notice, and should not be documented outside this
module. Furthermore, we do not give any guarantees on how an abstract
syntax tree may or may not be represented, with the following
exceptions: no syntax tree is represented by a single atom, such
as none
, by a list constructor [X | Y]
, or
by the empty list []
. This can be relied on when writing
functions that operate on syntax trees.
DATA TYPES
encoding() = utf8 | unicode | latin1
erl_parse() = abstract_form() (see module erl_parse) | abstract_expr() (see module erl_parse)
The representation built by the Erlang standard library parser
erl_parse
. This is a subset of the syntaxTree() type.
forms() = syntaxTree() | [syntaxTree()]
guard() = none | syntaxTree() | [syntaxTree()] | [[syntaxTree()]]
padding() = none | integer()
syntaxTree()
An abstract syntax tree. The erl_parse()
"parse tree" representation is a proper subset of the syntaxTree()
representation.
Every abstract syntax tree node has a type, given by the function type/1. Each node also has associated attributes; see get_attrs/1 for details. The functions make_tree/2 and subtrees/1 are generic constructor/decomposition functions for abstract syntax trees. The functions abstract/1 and concrete/1 convert between constant Erlang terms and their syntactic representations. The set of syntax tree nodes is extensible through the tree/2 function.
A syntax tree can be transformed to the erl_parse() representation with the revert/1 function.
syntaxTreeAttributes()
This is an abstract representation of syntax tree node attributes; see the function get_attrs/1.
Functions
type(Tree::syntaxTree()) -> atom()
Returns the type tag of Node
. If Node
does not represent a syntax tree, evaluation fails with reason
badarg
. Node types currently defined by this module are:
application
arity_qualifier
atom
attribute
binary
binary_field
block_expr
case_expr
catch_expr
char
class_qualifier
clause
comment
cond_expr
conjunction
disjunction
eof_marker
error_marker
float
form_list
fun_expr
function
generator
if_expr
implicit_fun
infix_expr
integer
list
list_comp
macro
match_expr
module_qualifier
nil
operator
parentheses
prefix_expr
receive_expr
record_access
record_expr
record_field
record_index_expr
rule
size_qualifier
string
text
try_expr
tuple
underscore
variable
warning_marker
The user may (for special purposes) create additional nodes with other type tags, using the tree/2 function.
Note: The primary constructor functions for a node type should always have the same name as the node type itself.
See also: application/3, arity_qualifier/2, atom/1, attribute/2, binary/1, binary_field/2, block_expr/1, case_expr/2, catch_expr/1, char/1, class_qualifier/2, clause/3, comment/2, cond_expr/1, conjunction/1, disjunction/1, eof_marker/0, error_marker/1, float/1, form_list/1, fun_expr/1, function/2, generator/2, if_expr/1, implicit_fun/2, infix_expr/3, integer/1, list/2, list_comp/2, macro/2, match_expr/2, module_qualifier/2, nil/0, operator/1, parentheses/1, prefix_expr/2, receive_expr/3, record_access/3, record_expr/2, record_field/2, record_index_expr/2, rule/2, size_qualifier/2, string/1, text/1, tree/2, try_expr/3, tuple/1, underscore/0, variable/1, warning_marker/1.
is_leaf(Node::syntaxTree()) -> boolean()
Returns true
if Node
is a leaf node,
otherwise false
. The currently recognised leaf node
types are:
atom
char
comment
eof_marker
error_marker
float
integer
nil
operator
string
text
underscore
variable
warning_marker
A node of type tuple
is a leaf node if and only if its arity is zero.
Note: not all literals are leaf nodes, and vice versa. E.g., tuples with nonzero arity and nonempty lists may be literals, but are not leaf nodes. Variables, on the other hand, are leaf nodes but not literals.
See also: is_literal/1, type/1.
is_form(Node::syntaxTree()) -> boolean()
Returns true
if Node
is a syntax tree
representing a so-called "source code form", otherwise
false
. Forms are the Erlang source code units which,
placed in sequence, constitute an Erlang program. Current form types
are:
attribute
comment
error_marker
eof_marker
form_list
function
rule
warning_marker
text
See also: attribute/2, comment/2, eof_marker/0, error_marker/1, form_list/1, function/2, rule/2, type/1, warning_marker/1.
get_pos(Tree::syntaxTree()) -> term()
Returns the position information associated with
Node
. This is usually a nonnegative integer (indicating
the source code line number), but may be any term. By default, all
new tree nodes have their associated position information set to the
integer zero.
See also: get_attrs/1, set_pos/2.
set_pos(Node::syntaxTree(), Pos::term()) -> syntaxTree()
copy_pos(Source::syntaxTree(), Target::syntaxTree()) -> syntaxTree()
get_precomments(Tree::syntaxTree()) -> [syntaxTree()]
Returns the associated pre-comments of a node. This is a possibly empty list of abstract comments, in top-down textual order. When the code is formatted, pre-comments are typically displayed directly above the node. For example:
% Pre-comment of function foo(X) -> {bar, X}.
If possible, the comment should be moved before any preceding separator characters on the same line. E.g.:
foo([X | Xs]) -> % Pre-comment of 'bar(X)' node [bar(X) | foo(Xs)]; ...
(where the comment is moved before the "[
").
See also: comment/2, get_attrs/1, get_postcomments/1, set_precomments/2.
set_precomments(Node::syntaxTree(), Cs::[syntaxTree()]) -> syntaxTree()
Sets the pre-comments of Node
to
Comments
. Comments
should be a possibly
empty list of abstract comments, in top-down textual order.
See also: add_precomments/2, comment/2, copy_comments/2, get_precomments/1, join_comments/2, remove_comments/1, set_postcomments/2.
add_precomments(Cs::[syntaxTree()], Node::syntaxTree()) -> syntaxTree()
Appends Comments
to the pre-comments of Node
.
Note: This is equivalent to set_precomments(Node,
get_precomments(Node) ++ Comments)
, but potentially more
efficient.
See also: add_postcomments/2, comment/2, get_precomments/1, join_comments/2, set_precomments/2.
get_postcomments(Tree::syntaxTree()) -> [syntaxTree()]
Returns the associated post-comments of a node. This is a possibly empty list of abstract comments, in top-down textual order. When the code is formatted, post-comments are typically displayed to the right of and/or below the node. For example:
{foo, X, Y} % Post-comment of tuple
If possible, the comment should be moved past any following separator characters on the same line, rather than placing the separators on the following line. E.g.:
foo([X | Xs], Y) -> foo(Xs, bar(X)); % Post-comment of 'bar(X)' node ...
(where the comment is moved past the rightmost ")
" and
the ";
").
See also: comment/2, get_attrs/1, get_precomments/1, set_postcomments/2.
set_postcomments(Node::syntaxTree(), Cs::[syntaxTree()]) -> syntaxTree()
Sets the post-comments of Node
to
Comments
. Comments
should be a possibly
empty list of abstract comments, in top-down textual order
See also: add_postcomments/2, comment/2, copy_comments/2, get_postcomments/1, join_comments/2, remove_comments/1, set_precomments/2.
add_postcomments(Cs::[syntaxTree()], Node::syntaxTree()) -> syntaxTree()
Appends Comments
to the post-comments of Node
.
Note: This is equivalent to set_postcomments(Node,
get_postcomments(Node) ++ Comments)
, but potentially more
efficient.
See also: add_precomments/2, comment/2, get_postcomments/1, join_comments/2, set_postcomments/2.
has_comments(Tree::syntaxTree()) -> boolean()
Yields false
if the node has no associated
comments, and true
otherwise.
Note: This is equivalent to (get_precomments(Node) == [])
and (get_postcomments(Node) == [])
, but potentially more
efficient.
See also: get_postcomments/1, get_precomments/1, remove_comments/1.
remove_comments(Node::syntaxTree()) -> syntaxTree()
Clears the associated comments of Node
.
Note: This is equivalent to
set_precomments(set_postcomments(Node, []), [])
, but
potentially more efficient.
See also: set_postcomments/2, set_precomments/2.
copy_comments(Source::syntaxTree(), Target::syntaxTree()) -> syntaxTree()
Copies the pre- and postcomments from Source
to Target
.
Note: This is equivalent to
set_postcomments(set_precomments(Target,
get_precomments(Source)), get_postcomments(Source))
, but
potentially more efficient.
See also: comment/2, get_postcomments/1, get_precomments/1, set_postcomments/2, set_precomments/2.
join_comments(Source::syntaxTree(), Target::syntaxTree()) -> syntaxTree()
Appends the comments of Source
to the current
comments of Target
.
Note: This is equivalent to
add_postcomments(get_postcomments(Source),
add_precomments(get_precomments(Source), Target))
, but
potentially more efficient.
See also: add_postcomments/2, add_precomments/2, comment/2, get_postcomments/1, get_precomments/1.
get_ann(Tree::syntaxTree()) -> [term()]
Returns the list of user annotations associated with a syntax tree node. For a newly created node, this is the empty list. The annotations may be any terms.
See also: get_attrs/1, set_ann/2.
set_ann(Node::syntaxTree(), As::[term()]) -> syntaxTree()
Sets the list of user annotations of Node
to Annotations
.
See also: add_ann/2, copy_ann/2, get_ann/1.
add_ann(A::term(), Node::syntaxTree()) -> syntaxTree()
copy_ann(Source::syntaxTree(), Target::syntaxTree()) -> syntaxTree()
get_attrs(Tree::syntaxTree()) -> syntaxTreeAttributes()
Returns a representation of the attributes associated with a syntax tree node. The attributes are all the extra information that can be attached to a node. Currently, this includes position information, source code comments, and user annotations. The result of this function cannot be inspected directly; only attached to another node (see set_attrs/2).
For accessing individual attributes, see get_pos/1, get_ann/1, get_precomments/1 and get_postcomments/1.
See also: get_ann/1, get_pos/1, get_postcomments/1, get_precomments/1, set_attrs/2.
set_attrs(Node::syntaxTree(), Attr::syntaxTreeAttributes()) -> syntaxTree()
copy_attrs(S::syntaxTree(), T::syntaxTree()) -> syntaxTree()
Copies the attributes from Source
to Target
.
Note: this is equivalent to set_attrs(Target,
get_attrs(Source))
, but potentially more efficient.
See also: get_attrs/1, set_attrs/2.
comment(Strings::[string()]) -> syntaxTree()
Equivalent to comment(none, Strings).
comment(Pad::padding(), Strings::[string()]) -> syntaxTree()
Creates an abstract comment with the given padding and text. If
Strings
is a (possibly empty) list
["Txt1", ..., "TxtN"]
, the result
represents the source code text
%Txt1 ... %TxtN
Padding
states the number of empty character positions
to the left of the comment separating it horizontally from
source code on the same line (if any). If Padding
is
none
, a default positive number is used. If
Padding
is an integer less than 1, there should be no
separating space. Comments are in themselves regarded as source
program forms.
comment_text(Node::syntaxTree()) -> [string()]
comment_padding(Node::syntaxTree()) -> padding()
Returns the amount of padding before the comment, or
none
. The latter means that a default padding may be used.
See also: comment/2.
form_list(Forms::[syntaxTree()]) -> syntaxTree()
Creates an abstract sequence of "source code forms". If
Forms
is [F1, ..., Fn]
, where each
Fi
is a form (see is_form/1, the result
represents
F1 ... Fn
where the Fi
are separated by one or more line breaks. A
node of type form_list
is itself regarded as a source
code form; see flatten_form_list/1.
Note: this is simply a way of grouping source code forms as a single syntax tree, usually in order to form an Erlang module definition.
See also: flatten_form_list/1, form_list_elements/1, is_form/1.
form_list_elements(Node::syntaxTree()) -> [syntaxTree()]
flatten_form_list(Node::syntaxTree()) -> syntaxTree()
Flattens sublists of a form_list
node. Returns
Node
with all subtrees of type form_list
recursively expanded, yielding a single "flat" abstract form
sequence.
See also: form_list/1.
text(String::string()) -> syntaxTree()
Creates an abstract piece of source code text. The result
represents exactly the sequence of characters in String
.
This is useful in cases when one wants full control of the resulting
output, e.g., for the appearance of floating-point numbers or macro
definitions.
See also: text_string/1.
text_string(Node::syntaxTree()) -> string()
variable(Name::atom() | string()) -> syntaxTree()
Creates an abstract variable with the given name.
Name
may be any atom or string that represents a
lexically valid variable name, but not a single underscore
character; see underscore/0.
Note: no checking is done whether the character sequence represents a proper variable name, i.e., whether or not its first character is an uppercase Erlang character, or whether it does not contain control characters, whitespace, etc.
See also: underscore/0, variable_literal/1, variable_name/1.
variable_name(Node::syntaxTree()) -> atom()
variable_literal(Node::syntaxTree()) -> string()
underscore() -> syntaxTree()
Creates an abstract universal pattern ("_
"). The
lexical representation is a single underscore character. Note that
this is not a variable, lexically speaking.
See also: variable/1.
integer(Value::integer()) -> syntaxTree()
Creates an abstract integer literal. The lexical representation
is the canonical decimal numeral of Value
.
See also: integer_literal/1, integer_value/1, is_integer/2.
is_integer(Node::syntaxTree(), Value::integer()) -> boolean()
integer_value(Node::syntaxTree()) -> integer()
integer_literal(Node::syntaxTree()) -> string()
float(Value::float()) -> syntaxTree()
Creates an abstract floating-point literal. The lexical
representation is the decimal floating-point numeral of Value
.
See also: float_literal/1, float_value/1.
float_value(Node::syntaxTree()) -> float()
Returns the value represented by a float
node. Note
that floating-point values should usually not be compared for
equality.
See also: float/1.
float_literal(Node::syntaxTree()) -> string()
char(Char::char()) -> syntaxTree()
Creates an abstract character literal. The result represents
"$Name
", where Name
corresponds to
Value
.
Note: the literal corresponding to a particular character value is
not uniquely defined. E.g., the character "a
" can be
written both as "$a
" and "$\141
", and a Tab
character can be written as "$\11
", "$\011
"
or "$\t
".
See also: char_literal/1, char_literal/2, char_value/1, is_char/2.
is_char(Node::syntaxTree(), Value::char()) -> boolean()
char_value(Node::syntaxTree()) -> char()
char_literal(Node::syntaxTree()) -> nonempty_string()
Returns the literal string represented by a char
node. This includes the leading "$
" character.
Characters beyond 255 will be escaped.
See also: char/1.
char_literal(Node::syntaxTree(), X2::encoding()) -> nonempty_string()
Returns the literal string represented by a char
node. This includes the leading "$
" character.
Depending on the encoding a character beyond 255 will be escaped
('latin1') or copied as is ('utf8').
See also: char/1.
string(String::string()) -> syntaxTree()
Creates an abstract string literal. The result represents
"Text"
(including the surrounding
double-quotes), where Text
corresponds to the sequence
of characters in Value
, but not representing a
specific string literal.
For example, the result of string("x\ny")
represents any and all of
"x\ny"
, "x\12y"
, "x\012y"
and "x\^Jy"
; see char/1.
See also: char/1, is_string/2, string_literal/1, string_literal/2, string_value/1.
is_string(Node::syntaxTree(), Value::string()) -> boolean()
string_value(Node::syntaxTree()) -> string()
string_literal(Node::syntaxTree()) -> nonempty_string()
Returns the literal string represented by a string
node. This includes surrounding double-quote characters.
Characters beyond 255 will be escaped.
See also: string/1.
string_literal(Node::syntaxTree(), X2::encoding()) -> nonempty_string()
Returns the literal string represented by a string
node. This includes surrounding double-quote characters.
Depending on the encoding characters beyond 255 will be escaped
('latin1') or copied as is ('utf8').
See also: string/1.
atom(Name::atom() | string()) -> syntaxTree()
Creates an abstract atom literal. The print name of the atom is
the character sequence represented by Name
.
See also: atom_literal/1, atom_name/1, atom_value/1, is_atom/2.
is_atom(Node::syntaxTree(), Value::atom()) -> boolean()
atom_value(Node::syntaxTree()) -> atom()
atom_name(Node::syntaxTree()) -> string()
atom_literal(Node::syntaxTree()) -> string()
tuple(List::[syntaxTree()]) -> syntaxTree()
Creates an abstract tuple. If Elements
is
[X1, ..., Xn]
, the result represents
"{X1, ..., Xn}
".
Note: The Erlang language has distinct 1-tuples, i.e.,
{X}
is always distinct from X
itself.
See also: tuple_elements/1, tuple_size/1.
tuple_elements(Node::syntaxTree()) -> [syntaxTree()]
tuple_size(Node::syntaxTree()) -> non_neg_integer()
Returns the number of elements of a tuple
node.
Note: this is equivalent to
length(tuple_elements(Node))
, but potentially more
efficient.
See also: tuple/1, tuple_elements/1.
list(List::[syntaxTree()]) -> syntaxTree()
Equivalent to list(List, none).
list(Elements::[syntaxTree()], Tail::none | syntaxTree()) -> syntaxTree()
Constructs an abstract list skeleton. The result has type
list
or nil
. If List
is a
nonempty list [E1, ..., En]
, the result has type
list
and represents either "[E1, ...,
En]
", if Tail
is none
, or
otherwise "[E1, ..., En |
Tail]
". If List
is the empty list,
Tail
must be none
, and in that
case the result has type nil
and represents
"[]
" (see nil/0).
The difference between lists as semantic objects (built up of individual "cons" and "nil" terms) and the various syntactic forms for denoting lists may be bewildering at first. This module provides functions both for exact control of the syntactic representation as well as for the simple composition and deconstruction in terms of cons and head/tail operations.
Note: in list(Elements, none)
, the "nil" list
terminator is implicit and has no associated information (see
get_attrs/1), while in the seemingly equivalent
list(Elements, Tail)
when Tail
has type
nil
, the list terminator subtree Tail
may
have attached attributes such as position, comments, and annotations,
which will be preserved in the result.
See also: compact_list/1, cons/2, get_attrs/1, is_list_skeleton/1, is_proper_list/1, list/1, list_elements/1, list_head/1, list_length/1, list_prefix/1, list_suffix/1, list_tail/1, nil/0, normalize_list/1.
nil() -> syntaxTree()
Creates an abstract empty list. The result represents
"[]
". The empty list is traditionally called "nil".
See also: is_list_skeleton/1, list/2.
list_prefix(Node::syntaxTree()) -> [syntaxTree()]
Returns the prefix element subtrees of a list
node.
If Node
represents "[E1, ...,
En]
" or "[E1, ..., En |
Tail]
", the returned value is [E1, ...,
En]
.
See also: list/2.
list_suffix(Node::syntaxTree()) -> none | syntaxTree()
Returns the suffix subtree of a list
node, if one
exists. If Node
represents "[E1, ...,
En | Tail]
", the returned value is
Tail
, otherwise, i.e., if Node
represents
"[E1, ..., En]
", none
is
returned.
Note that even if this function returns some Tail
that is not none
, the type of Tail
can be
nil
, if the tail has been given explicitly, and the list
skeleton has not been compacted (see compact_list/1).
See also: compact_list/1, list/2, nil/0.
cons(Head::syntaxTree(), Tail::syntaxTree()) -> syntaxTree()
"Optimising" list skeleton cons operation. Creates an abstract
list skeleton whose first element is Head
and whose tail
corresponds to Tail
. This is similar to
list([Head], Tail)
, except that Tail
may
not be none
, and that the result does not necessarily
represent exactly "[Head | Tail]
", but
may depend on the Tail
subtree. E.g., if
Tail
represents [X, Y]
, the result may
represent "[Head, X, Y]
", rather than
"[Head | [X, Y]]
". Annotations on
Tail
itself may be lost if Tail
represents
a list skeleton, but comments on Tail
are propagated to
the result.
See also: list/2, list_head/1, list_tail/1.
list_head(Node::syntaxTree()) -> syntaxTree()
Returns the head element subtree of a list
node. If
Node
represents "[Head ...]
", the
result will represent "Head
".
See also: cons/2, list/2, list_tail/1.
list_tail(Node::syntaxTree()) -> syntaxTree()
Returns the tail of a list
node. If
Node
represents a single-element list
"[E]
", then the result has type
nil
, representing "[]
". If
Node
represents "[E1, E2
...]
", the result will represent "[E2
...]
", and if Node
represents
"[Head | Tail]
", the result will
represent "Tail
".
See also: cons/2, list/2, list_head/1.
is_list_skeleton(Node::syntaxTree()) -> boolean()
is_proper_list(Node::syntaxTree()) -> boolean()
Returns true
if Node
represents a
proper list, and false
otherwise. A proper list is a
list skeleton either on the form "[]
" or
"[E1, ..., En]
", or "[... |
Tail]
" where recursively Tail
also
represents a proper list.
Note: Since Node
is a syntax tree, the actual
run-time values corresponding to its subtrees may often be partially
or completely unknown. Thus, if Node
represents e.g.
"[... | Ns]
" (where Ns
is a variable), then
the function will return false
, because it is not known
whether Ns
will be bound to a list at run-time. If
Node
instead represents e.g. "[1, 2, 3]
" or
"[A | []]
", then the function will return
true
.
See also: list/2.
list_elements(Node::syntaxTree()) -> [syntaxTree()]
Returns the list of element subtrees of a list skeleton.
Node
must represent a proper list. E.g., if
Node
represents "[X1, X2 |
[X3, X4 | []]
", then
list_elements(Node)
yields the list [X1, X2, X3, X4]
.
See also: is_proper_list/1, list/2.
list_length(Node::syntaxTree()) -> non_neg_integer()
Returns the number of element subtrees of a list skeleton.
Node
must represent a proper list. E.g., if
Node
represents "[X1 | [X2, X3 | [X4, X5,
X6]]]
", then list_length(Node)
returns the
integer 6.
Note: this is equivalent to
length(list_elements(Node))
, but potentially more
efficient.
See also: is_proper_list/1, list/2, list_elements/1.
normalize_list(Node::syntaxTree()) -> syntaxTree()
Expands an abstract list skeleton to its most explicit form. If
Node
represents "[E1, ..., En |
Tail]
", the result represents "[E1 |
... [En | Tail1] ... ]
", where
Tail1
is the result of
normalize_list(Tail)
. If Node
represents
"[E1, ..., En]
", the result simply
represents "[E1 | ... [En | []] ...
]
". If Node
does not represent a list skeleton,
Node
itself is returned.
See also: compact_list/1, list/2.
compact_list(Node::syntaxTree()) -> syntaxTree()
Yields the most compact form for an abstract list skeleton. The
result either represents "[E1, ..., En |
Tail]
", where Tail
is not a list
skeleton, or otherwise simply "[E1, ...,
En]
". Annotations on subtrees of Node
that represent list skeletons may be lost, but comments will be
propagated to the result. Returns Node
itself if
Node
does not represent a list skeleton.
See also: list/2, normalize_list/1.
binary(List::[syntaxTree()]) -> syntaxTree()
Creates an abstract binary-object template. If
Fields
is [F1, ..., Fn]
, the result
represents "<<F1, ...,
Fn>>
".
See also: binary_field/2, binary_fields/1.
binary_fields(Node::syntaxTree()) -> [syntaxTree()]
binary_field(Body::syntaxTree()) -> syntaxTree()
Equivalent to binary_field(Body, []).
binary_field(Body::syntaxTree(), Size::none | syntaxTree(), Types::[syntaxTree()]) -> syntaxTree()
Creates an abstract binary template field.
If Size
is none
, this is equivalent to
"binary_field(Body, Types)
", otherwise it is
equivalent to "binary_field(size_qualifier(Body, Size),
Types)
".
(This is a utility function.)
See also: binary/1, binary_field/2, size_qualifier/2.
binary_field(Body::syntaxTree(), Types::[syntaxTree()]) -> syntaxTree()
Creates an abstract binary template field. If
Types
is the empty list, the result simply represents
"Body
", otherwise, if Types
is
[T1, ..., Tn]
, the result represents
"Body/T1-...-Tn
".
See also: binary/1, binary_field/1, binary_field/3, binary_field_body/1, binary_field_size/1, binary_field_types/1.
binary_field_body(Node::syntaxTree()) -> syntaxTree()
binary_field_types(Node::syntaxTree()) -> [syntaxTree()]
Returns the list of type-specifier subtrees of a
binary_field
node. If Node
represents
".../T1, ..., Tn
", the result is
[T1, ..., Tn]
, otherwise the result is the empty list.
See also: binary_field/2.
binary_field_size(Node::syntaxTree()) -> none | syntaxTree()
Returns the size specifier subtree of a
binary_field
node, if any. If Node
represents "Body:Size
" or
"Body:Size/T1, ...,
Tn
", the result is Size
, otherwise
none
is returned.
(This is a utility function.)
See also: binary_field/2, binary_field/3.
size_qualifier(Body::syntaxTree(), Size::syntaxTree()) -> syntaxTree()
Creates an abstract size qualifier. The result represents
"Body:Size
".
See also: size_qualifier_argument/1, size_qualifier_body/1.
size_qualifier_body(Node::syntaxTree()) -> syntaxTree()
size_qualifier_argument(Node::syntaxTree()) -> syntaxTree()
error_marker(Error::term()) -> syntaxTree()
Creates an abstract error marker. The result represents an
occurrence of an error in the source code, with an associated Erlang
I/O ErrorInfo structure given by Error
(see module
io(3) for details). Error markers are regarded as source
code forms, but have no defined lexical form.
Note: this is supported only for backwards compatibility with existing parsers and tools.
See also: eof_marker/0, error_marker_info/1, is_form/1, warning_marker/1.
error_marker_info(Node::syntaxTree()) -> term()
warning_marker(Warning::term()) -> syntaxTree()
Creates an abstract warning marker. The result represents an
occurrence of a possible problem in the source code, with an
associated Erlang I/O ErrorInfo structure given by Error
(see module io(3) for details). Warning markers are
regarded as source code forms, but have no defined lexical form.
Note: this is supported only for backwards compatibility with existing parsers and tools.
See also: eof_marker/0, error_marker/1, is_form/1, warning_marker_info/1.
warning_marker_info(Node::syntaxTree()) -> term()
eof_marker() -> syntaxTree()
Creates an abstract end-of-file marker. This represents the end of input when reading a sequence of source code forms. An end-of-file marker is itself regarded as a source code form (namely, the last in any sequence in which it occurs). It has no defined lexical form.
Note: this is retained only for backwards compatibility with existing parsers and tools.
See also: error_marker/1, is_form/1, warning_marker/1.
attribute(Name::syntaxTree()) -> syntaxTree()
Equivalent to attribute(Name, none).
attribute(Name::syntaxTree(), Args::none | [syntaxTree()]) -> syntaxTree()
Creates an abstract program attribute. If
Arguments
is [A1, ..., An]
, the result
represents "-Name(A1, ...,
An).
". Otherwise, if Arguments
is
none
, the result represents
"-Name.
". The latter form makes it possible
to represent preprocessor directives such as
"-endif.
". Attributes are source code forms.
Note: The preprocessor macro definition directive
"-define(Name, Body).
" has relatively
few requirements on the syntactical form of Body
(viewed
as a sequence of tokens). The text
node type can be used
for a Body
that is not a normal Erlang construct.
See also: attribute/1, attribute_arguments/1, attribute_name/1, is_form/1, text/1.
attribute_name(Node::syntaxTree()) -> syntaxTree()
attribute_arguments(Node::syntaxTree()) -> none | [syntaxTree()]
Returns the list of argument subtrees of an
attribute
node, if any. If Node
represents "-Name.
", the result is
none
. Otherwise, if Node
represents
"-Name(E1, ..., En).
",
[E1, ..., E1]
is returned.
See also: attribute/1.
arity_qualifier(Body::syntaxTree(), Arity::syntaxTree()) -> syntaxTree()
Creates an abstract arity qualifier. The result represents
"Body/Arity
".
See also: arity_qualifier_argument/1, arity_qualifier_body/1.
arity_qualifier_body(Node::syntaxTree()) -> syntaxTree()
arity_qualifier_argument(Node::syntaxTree()) -> syntaxTree()
module_qualifier(Module::syntaxTree(), Body::syntaxTree()) -> syntaxTree()
Creates an abstract module qualifier. The result represents
"Module:Body
".
See also: module_qualifier_argument/1, module_qualifier_body/1.
module_qualifier_argument(Node::syntaxTree()) -> syntaxTree()
module_qualifier_body(Node::syntaxTree()) -> syntaxTree()
function(Name::syntaxTree(), Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract function definition. If Clauses
is [C1, ..., Cn]
, the result represents
"Name C1; ...; Name
Cn.
". More exactly, if each Ci
represents "(Pi1, ..., Pim) Gi ->
Bi
", then the result represents
"Name(P11, ..., P1m) G1 ->
B1; ...; Name(Pn1, ..., Pnm)
Gn -> Bn.
". Function definitions are source
code forms.
See also: function_arity/1, function_clauses/1, function_name/1, is_form/1, rule/2.
function_name(Node::syntaxTree()) -> syntaxTree()
function_clauses(Node::syntaxTree()) -> [syntaxTree()]
function_arity(Node::syntaxTree()) -> arity()
Returns the arity of a function
node. The result
is the number of parameter patterns in the first clause of the
function; subsequent clauses are ignored.
An exception is thrown if function_clauses(Node)
returns an empty list, or if the first element of that list is not
a syntax tree C
of type clause
such that
clause_patterns(C)
is a nonempty list.
See also: clause/3, clause_patterns/1, function/2, function_clauses/1.
clause(Guard::guard(), Body::[syntaxTree()]) -> syntaxTree()
Equivalent to clause([], Guard, Body).
clause(Patterns::[syntaxTree()], Guard::guard(), Body::[syntaxTree()]) -> syntaxTree()
Creates an abstract clause. If Patterns
is
[P1, ..., Pn]
and Body
is [B1, ...,
Bm]
, then if Guard
is none
, the
result represents "(P1, ..., Pn) ->
B1, ..., Bm
", otherwise, unless
Guard
is a list, the result represents
"(P1, ..., Pn) when Guard ->
B1, ..., Bm
".
For simplicity, the Guard
argument may also be any
of the following:
An empty list
[]
. This is equivalent to passingnone
.A nonempty list
[E1, ..., Ej]
of syntax trees. This is equivalent to passingconjunction([E1, ..., Ej])
.A nonempty list of lists of syntax trees
[[E1_1, ..., E1_k1], ..., [Ej_1, ..., Ej_kj]]
, which is equivalent to passingdisjunction([conjunction([E1_1, ..., E1_k1]), ..., conjunction([Ej_1, ..., Ej_kj])])
.
See also: clause/2, clause_body/1, clause_guard/1, clause_patterns/1.
clause_patterns(Node::syntaxTree()) -> [syntaxTree()]
clause_guard(Node::syntaxTree()) -> none | syntaxTree()
Returns the guard subtree of a clause
node, if
any. If Node
represents "(P1, ...,
Pn) when Guard -> B1, ...,
Bm
", Guard
is returned. Otherwise, the
result is none
.
See also: clause/3.
clause_body(Node::syntaxTree()) -> [syntaxTree()]
disjunction(Tests::[syntaxTree()]) -> syntaxTree()
Creates an abstract disjunction. If List
is
[E1, ..., En]
, the result represents
"E1; ...; En
".
See also: conjunction/1, disjunction_body/1.
disjunction_body(Node::syntaxTree()) -> [syntaxTree()]
conjunction(Tests::[syntaxTree()]) -> syntaxTree()
Creates an abstract conjunction. If List
is
[E1, ..., En]
, the result represents
"E1, ..., En
".
See also: conjunction_body/1, disjunction/1.
conjunction_body(Node::syntaxTree()) -> [syntaxTree()]
catch_expr(Expr::syntaxTree()) -> syntaxTree()
Creates an abstract catch-expression. The result represents
"catch Expr
".
See also: catch_expr_body/1.
catch_expr_body(Node::syntaxTree()) -> syntaxTree()
match_expr(Pattern::syntaxTree(), Body::syntaxTree()) -> syntaxTree()
Creates an abstract match-expression. The result represents
"Pattern = Body
".
See also: match_expr_body/1, match_expr_pattern/1.
match_expr_pattern(Node::syntaxTree()) -> syntaxTree()
match_expr_body(Node::syntaxTree()) -> syntaxTree()
operator(Name::atom() | string()) -> syntaxTree()
Creates an abstract operator. The name of the operator is the
character sequence represented by Name
. This is
analogous to the print name of an atom, but an operator is never
written within single-quotes; e.g., the result of
operator(
++')' represents "++
" rather
than "`++''".
See also: atom/1, operator_literal/1, operator_name/1.
operator_name(Node::syntaxTree()) -> atom()
Returns the name of an operator
node. Note that
the name is returned as an atom.
See also: operator/1.
operator_literal(Node::syntaxTree()) -> string()
Returns the literal string represented by an
operator
node. This is simply the operator name as a string.
See also: operator/1.
infix_expr(Left::syntaxTree(), Operator::syntaxTree(), Right::syntaxTree()) -> syntaxTree()
Creates an abstract infix operator expression. The result
represents "Left Operator
Right
".
See also: infix_expr_left/1, infix_expr_operator/1, infix_expr_right/1, prefix_expr/2.
infix_expr_left(Node::syntaxTree()) -> syntaxTree()
infix_expr_operator(Node::syntaxTree()) -> syntaxTree()
infix_expr_right(Node::syntaxTree()) -> syntaxTree()
prefix_expr(Operator::syntaxTree(), Argument::syntaxTree()) -> syntaxTree()
Creates an abstract prefix operator expression. The result
represents "Operator Argument
".
See also: infix_expr/3, prefix_expr_argument/1, prefix_expr_operator/1.
prefix_expr_operator(Node::syntaxTree()) -> syntaxTree()
prefix_expr_argument(Node::syntaxTree()) -> syntaxTree()
record_field(Name::syntaxTree()) -> syntaxTree()
Equivalent to record_field(Name, none).
record_field(Name::syntaxTree(), Value::none | syntaxTree()) -> syntaxTree()
Creates an abstract record field specification. If
Value
is none
, the result represents
simply "Name
", otherwise it represents
"Name = Value
".
See also: record_expr/3, record_field_name/1, record_field_value/1.
record_field_name(Node::syntaxTree()) -> syntaxTree()
record_field_value(Node::syntaxTree()) -> none | syntaxTree()
Returns the value subtree of a record_field
node,
if any. If Node
represents
"Name
", none
is
returned. Otherwise, if Node
represents
"Name = Value
", Value
is returned.
See also: record_field/2.
record_index_expr(Type::syntaxTree(), Field::syntaxTree()) -> syntaxTree()
Creates an abstract record field index expression. The result
represents "#Type.Field
".
(Note: the function name record_index/2
is reserved
by the Erlang compiler, which is why that name could not be used
for this constructor.)
See also: record_expr/3, record_index_expr_field/1, record_index_expr_type/1.
record_index_expr_type(Node::syntaxTree()) -> syntaxTree()
record_index_expr_field(Node::syntaxTree()) -> syntaxTree()
record_access(Argument::syntaxTree(), Field::syntaxTree()) -> syntaxTree()
Equivalent to record_access(Argument, none, Field).
record_access(Argument::syntaxTree(), Type::none | syntaxTree(), Field::syntaxTree()) -> syntaxTree()
Creates an abstract record field access expression. If
Type
is not none
, the result represents
"Argument#Type.Field
".
If Type
is none
, the result represents
"Argument.Field
". This is a special
form only allowed within Mnemosyne queries.
See also: record_access/2, record_access_argument/1, record_access_field/1, record_access_type/1, record_expr/3.
record_access_argument(Node::syntaxTree()) -> syntaxTree()
record_access_type(Node::syntaxTree()) -> none | syntaxTree()
Returns the type subtree of a record_access
node,
if any. If Node
represents
"Argument.Field
", none
is returned, otherwise if Node
represents
"Argument#Type.Field
",
Type
is returned.
See also: record_access/3.
record_access_field(Node::syntaxTree()) -> syntaxTree()
record_expr(Type::syntaxTree(), Fields::[syntaxTree()]) -> syntaxTree()
Equivalent to record_expr(none, Type, Fields).
record_expr(Argument::none | syntaxTree(), Type::syntaxTree(), Fields::[syntaxTree()]) -> syntaxTree()
Creates an abstract record expression. If Fields
is
[F1, ..., Fn]
, then if Argument
is
none
, the result represents
"#Type{F1, ..., Fn}
",
otherwise it represents
"Argument#Type{F1, ...,
Fn}
".
See also: record_access/3, record_expr/2, record_expr_argument/1, record_expr_fields/1, record_expr_type/1, record_field/2, record_index_expr/2.
record_expr_argument(Node::syntaxTree()) -> none | syntaxTree()
Returns the argument subtree of a record_expr
node,
if any. If Node
represents
"#Type{...}
", none
is returned.
Otherwise, if Node
represents
"Argument#Type{...}
",
Argument
is returned.
See also: record_expr/3.
record_expr_type(Node::syntaxTree()) -> syntaxTree()
record_expr_fields(Node::syntaxTree()) -> [syntaxTree()]
application(Module::none | syntaxTree(), Name::syntaxTree(), Arguments::[syntaxTree()]) -> syntaxTree()
Creates an abstract function application expression. If
Module
is none
, this is call is equivalent
to application(Function, Arguments)
, otherwise it is
equivalent to application(module_qualifier(Module, Function),
Arguments)
.
(This is a utility function.)
See also: application/2, module_qualifier/2.
application(Operator::syntaxTree(), Arguments::[syntaxTree()]) -> syntaxTree()
Creates an abstract function application expression. If
Arguments
is [A1, ..., An]
, the result
represents "Operator(A1, ...,
An)
".
See also: application/3, application_arguments/1, application_operator/1.
application_operator(Node::syntaxTree()) -> syntaxTree()
Returns the operator subtree of an application
node.
Note: if Node
represents
"M:F(...)
", then the result is the
subtree representing "M:F
".
See also: application/2, module_qualifier/2.
application_arguments(Node::syntaxTree()) -> [syntaxTree()]
list_comp(Template::syntaxTree(), Body::[syntaxTree()]) -> syntaxTree()
Creates an abstract list comprehension. If Body
is
[E1, ..., En]
, the result represents
"[Template || E1, ..., En]
".
See also: generator/2, list_comp_body/1, list_comp_template/1.
list_comp_template(Node::syntaxTree()) -> syntaxTree()
list_comp_body(Node::syntaxTree()) -> [syntaxTree()]
binary_comp(Template::syntaxTree(), Body::[syntaxTree()]) -> syntaxTree()
Creates an abstract binary comprehension. If Body
is
[E1, ..., En]
, the result represents
"<<Template || E1, ..., En>>
".
See also: binary_comp_body/1, binary_comp_template/1, generator/2.
binary_comp_template(Node::syntaxTree()) -> syntaxTree()
binary_comp_body(Node::syntaxTree()) -> [syntaxTree()]
rule(Name::syntaxTree(), Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract Mnemosyne rule. If Clauses
is
[C1, ..., Cn]
, the results represents
"Name C1; ...; Name
Cn.
". More exactly, if each Ci
represents "(Pi1, ..., Pim) Gi ->
Bi
", then the result represents
"Name(P11, ..., P1m) G1 :-
B1; ...; Name(Pn1, ..., Pnm)
Gn :- Bn.
". Rules are source code forms.
See also: function/2, is_form/1, rule_arity/1, rule_clauses/1, rule_name/1.
rule_name(Node::syntaxTree()) -> syntaxTree()
rule_clauses(Node::syntaxTree()) -> [syntaxTree()]
rule_arity(Node::syntaxTree()) -> arity()
Returns the arity of a rule
node. The result is the
number of parameter patterns in the first clause of the rule;
subsequent clauses are ignored.
An exception is thrown if rule_clauses(Node)
returns
an empty list, or if the first element of that list is not a syntax
tree C
of type clause
such that
clause_patterns(C)
is a nonempty list.
See also: clause/3, clause_patterns/1, rule/2, rule_clauses/1.
generator(Pattern::syntaxTree(), Body::syntaxTree()) -> syntaxTree()
Creates an abstract generator. The result represents
"Pattern <- Body
".
See also: binary_comp/2, generator_body/1, generator_pattern/1, list_comp/2.
generator_pattern(Node::syntaxTree()) -> syntaxTree()
generator_body(Node::syntaxTree()) -> syntaxTree()
binary_generator(Pattern::syntaxTree(), Body::syntaxTree()) -> syntaxTree()
Creates an abstract binary_generator. The result represents
"Pattern <- Body
".
See also: binary_comp/2, binary_generator_body/1, binary_generator_pattern/1, list_comp/2.
binary_generator_pattern(Node::syntaxTree()) -> syntaxTree()
binary_generator_body(Node::syntaxTree()) -> syntaxTree()
block_expr(Body::[syntaxTree()]) -> syntaxTree()
Creates an abstract block expression. If Body
is
[B1, ..., Bn]
, the result represents "begin
B1, ..., Bn end
".
See also: block_expr_body/1.
block_expr_body(Node::syntaxTree()) -> [syntaxTree()]
if_expr(Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract if-expression. If Clauses
is
[C1, ..., Cn]
, the result represents "if
C1; ...; Cn end
". More exactly, if each
Ci
represents "() Gi ->
Bi
", then the result represents "if
G1 -> B1; ...; Gn -> Bn
end
".
See also: case_expr/2, clause/3, if_expr_clauses/1.
if_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
case_expr(Argument::syntaxTree(), Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract case-expression. If Clauses
is
[C1, ..., Cn]
, the result represents "case
Argument of C1; ...; Cn end
". More
exactly, if each Ci
represents "(Pi)
Gi -> Bi
", then the result represents
"case Argument of P1 G1 ->
B1; ...; Pn Gn -> Bn end
".
See also: case_expr_argument/1, case_expr_clauses/1, clause/3, cond_expr/1, if_expr/1.
case_expr_argument(Node::syntaxTree()) -> syntaxTree()
case_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
cond_expr(Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract cond-expression. If Clauses
is
[C1, ..., Cn]
, the result represents "cond
C1; ...; Cn end
". More exactly, if each
Ci
represents "() Ei ->
Bi
", then the result represents "cond
E1 -> B1; ...; En -> Bn
end
".
See also: case_expr/2, clause/3, cond_expr_clauses/1.
cond_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
receive_expr(Clauses::[syntaxTree()]) -> syntaxTree()
Equivalent to receive_expr(Clauses, none, []).
receive_expr(Clauses::[syntaxTree()], Timeout::none | syntaxTree(), Action::[syntaxTree()]) -> syntaxTree()
Creates an abstract receive-expression. If Timeout
is none
, the result represents "receive
C1; ...; Cn end
" (the Action
argument is ignored). Otherwise, if Clauses
is
[C1, ..., Cn]
and Action
is [A1, ...,
Am]
, the result represents "receive C1; ...;
Cn after Timeout -> A1, ..., Am
end
". More exactly, if each Ci
represents
"(Pi) Gi -> Bi
", then the
result represents "receive P1 G1 ->
B1; ...; Pn Gn -> Bn ...
end
".
Note that in Erlang, a receive-expression must have at least one clause if no timeout part is specified.
See also: case_expr/2, clause/3, receive_expr/1, receive_expr_action/1, receive_expr_clauses/1, receive_expr_timeout/1.
receive_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
receive_expr_timeout(Node::syntaxTree()) -> none | syntaxTree()
Returns the timeout subtree of a receive_expr
node,
if any. If Node
represents "receive C1;
...; Cn end
", none
is returned.
Otherwise, if Node
represents "receive
C1; ...; Cn after Timeout -> ... end
",
Timeout
is returned.
See also: receive_expr/3.
receive_expr_action(Node::syntaxTree()) -> [syntaxTree()]
Returns the list of action body subtrees of a
receive_expr
node. If Node
represents
"receive C1; ...; Cn end
", this is the
empty list.
See also: receive_expr/3.
try_expr(Body::[syntaxTree()], Handlers::[syntaxTree()]) -> syntaxTree()
Equivalent to try_expr(Body, [], Handlers).
try_expr(Body::[syntaxTree()], Clauses::[syntaxTree()], Handlers::[syntaxTree()]) -> syntaxTree()
Equivalent to try_expr(Body, Clauses, Handlers, []).
try_after_expr(Body::[syntaxTree()], After::[syntaxTree()]) -> syntaxTree()
Equivalent to try_expr(Body, [], [], After).
try_expr(Body::[syntaxTree()], Clauses::[syntaxTree()], Handlers::[syntaxTree()], After::[syntaxTree()]) -> syntaxTree()
Creates an abstract try-expression. If Body
is
[B1, ..., Bn]
, Clauses
is [C1, ...,
Cj]
, Handlers
is [H1, ..., Hk]
, and
After
is [A1, ..., Am]
, the result
represents "try B1, ..., Bn of C1;
...; Cj catch H1; ...; Hk after
A1, ..., Am end
". More exactly, if each
Ci
represents "(CPi) CGi ->
CBi
", and each Hi
represents
"(HPi) HGi -> HBi
", then the
result represents "try B1, ..., Bn of
CP1 CG1 -> CB1; ...; CPj
CGj -> CBj catch HP1 HG1 ->
HB1; ...; HPk HGk -> HBk after
A1, ..., Am end
"; see
case_expr/2. If Clauses
is the empty list,
the of ...
section is left out. If After
is
the empty list, the after ...
section is left out. If
Handlers
is the empty list, and After
is
nonempty, the catch ...
section is left out.
See also: case_expr/2, class_qualifier/2, clause/3, try_after_expr/2, try_expr/2, try_expr/3, try_expr_after/1, try_expr_body/1, try_expr_clauses/1, try_expr_handlers/1.
try_expr_body(Node::syntaxTree()) -> [syntaxTree()]
try_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
Returns the list of case-clause subtrees of a
try_expr
node. If Node
represents
"try Body catch H1; ...; Hn
end
", the result is the empty list.
See also: try_expr/4.
try_expr_handlers(Node::syntaxTree()) -> [syntaxTree()]
try_expr_after(Node::syntaxTree()) -> [syntaxTree()]
class_qualifier(Class::syntaxTree(), Body::syntaxTree()) -> syntaxTree()
Creates an abstract class qualifier. The result represents
"Class:Body
".
See also: class_qualifier_argument/1, class_qualifier_body/1, try_expr/4.
class_qualifier_argument(Node::syntaxTree()) -> syntaxTree()
class_qualifier_body(Node::syntaxTree()) -> syntaxTree()
implicit_fun(Name::syntaxTree(), Arity::none | syntaxTree()) -> syntaxTree()
Creates an abstract "implicit fun" expression. If
Arity
is none
, this is equivalent to
implicit_fun(Name)
, otherwise it is equivalent to
implicit_fun(arity_qualifier(Name, Arity))
.
(This is a utility function.)
See also: implicit_fun/1, implicit_fun/3.
implicit_fun(Module::none | syntaxTree(), Name::syntaxTree(), Arity::syntaxTree()) -> syntaxTree()
Creates an abstract module-qualified "implicit fun" expression.
If Module
is none
, this is equivalent to
implicit_fun(Name, Arity)
, otherwise it is equivalent to
implicit_fun(module_qualifier(Module, arity_qualifier(Name,
Arity))
.
(This is a utility function.)
See also: implicit_fun/1, implicit_fun/2.
implicit_fun(Name::syntaxTree()) -> syntaxTree()
Creates an abstract "implicit fun" expression. The result
represents "fun Name
". Name
should
represent either F/A
or
M:F/A
See also: arity_qualifier/2, implicit_fun/2, implicit_fun/3, implicit_fun_name/1, module_qualifier/2.
implicit_fun_name(Node::syntaxTree()) -> syntaxTree()
Returns the name subtree of an implicit_fun
node.
Note: if Node
represents "fun
N/A
" or "fun
M:N/A
", then the result is the
subtree representing "N/A
" or
"M:N/A
", respectively.
See also: arity_qualifier/2, implicit_fun/1, module_qualifier/2.
fun_expr(Clauses::[syntaxTree()]) -> syntaxTree()
Creates an abstract fun-expression. If Clauses
is
[C1, ..., Cn]
, the result represents "fun
C1; ...; Cn end
". More exactly, if each
Ci
represents "(Pi1, ..., Pim)
Gi -> Bi
", then the result represents
"fun (P11, ..., P1m) G1 ->
B1; ...; (Pn1, ..., Pnm) Gn ->
Bn end
".
See also: fun_expr_arity/1, fun_expr_clauses/1.
fun_expr_clauses(Node::syntaxTree()) -> [syntaxTree()]
fun_expr_arity(Node::syntaxTree()) -> arity()
Returns the arity of a fun_expr
node. The result is
the number of parameter patterns in the first clause of the
fun-expression; subsequent clauses are ignored.
An exception is thrown if fun_expr_clauses(Node)
returns an empty list, or if the first element of that list is not a
syntax tree C
of type clause
such that
clause_patterns(C)
is a nonempty list.
See also: clause/3, clause_patterns/1, fun_expr/1, fun_expr_clauses/1.
parentheses(Expr::syntaxTree()) -> syntaxTree()
Creates an abstract parenthesised expression. The result
represents "(Body)
", independently of the
context.
See also: parentheses_body/1.
parentheses_body(Node::syntaxTree()) -> syntaxTree()
macro(Name::syntaxTree()) -> syntaxTree()
Equivalent to macro(Name, none).
macro(Name::syntaxTree(), Arguments::none | [syntaxTree()]) -> syntaxTree()
Creates an abstract macro application. If Arguments
is none
, the result represents
"?Name
", otherwise, if Arguments
is [A1, ..., An]
, the result represents
"?Name(A1, ..., An)
".
Notes: if Arguments
is the empty list, the result
will thus represent "?Name()
", including a pair
of matching parentheses.
The only syntactical limitation imposed by the preprocessor on the
arguments to a macro application (viewed as sequences of tokens) is
that they must be balanced with respect to parentheses, brackets,
begin ... end
, case ... end
, etc. The
text
node type can be used to represent arguments which
are not regular Erlang constructs.
See also: macro/1, macro_arguments/1, macro_name/1, text/1.
macro_name(Node::syntaxTree()) -> syntaxTree()
macro_arguments(Node::syntaxTree()) -> none | [syntaxTree()]
Returns the list of argument subtrees of a macro
node, if any. If Node
represents
"?Name
", none
is returned.
Otherwise, if Node
represents
"?Name(A1, ..., An)
",
[A1, ..., An]
is returned.
See also: macro/2.
abstract(T::term()) -> syntaxTree()
Returns the syntax tree corresponding to an Erlang term.
Term
must be a literal term, i.e., one that can be
represented as a source code literal. Thus, it may not contain a
process identifier, port, reference, binary or function value as a
subterm. The function recognises printable strings, in order to get a
compact and readable representation. Evaluation fails with reason
badarg
if Term
is not a literal term.
See also: concrete/1, is_literal/1.
concrete(Node::syntaxTree()) -> term()
Returns the Erlang term represented by a syntax tree. Evaluation
fails with reason badarg
if Node
does not
represent a literal term.
Note: Currently, the set of syntax trees which have a concrete representation is larger than the set of trees which can be built using the function abstract/1. An abstract character will be concretised as an integer, while abstract/1 does not at present yield an abstract character for any input. (Use the char/1 function to explicitly create an abstract character.)
See also: abstract/1, char/1, is_literal/1.
is_literal(T::syntaxTree()) -> boolean()
Returns true
if Node
represents a
literal term, otherwise false
. This function returns
true
if and only if the value of
concrete(Node)
is defined.
See also: abstract/1, concrete/1.
revert(Node::syntaxTree()) -> syntaxTree()
Returns an erl_parse
-compatible representation of a
syntax tree, if possible. If Tree
represents a
well-formed Erlang program or expression, the conversion should work
without problems. Typically, is_tree/1 yields
true
if conversion failed (i.e., the result is still an
abstract syntax tree), and false
otherwise.
The is_tree/1 test is not completely foolproof. For a
few special node types (e.g. arity_qualifier
), if such a
node occurs in a context where it is not expected, it will be left
unchanged as a non-reverted subtree of the result. This can only
happen if Tree
does not actually represent legal Erlang
code.
See also: erl_parse(3), revert_forms/1.
revert_forms(Forms::forms()) -> [erl_parse()]
Reverts a sequence of Erlang source code forms. The sequence can
be given either as a form_list
syntax tree (possibly
nested), or as a list of "program form" syntax trees. If successful,
the corresponding flat list of erl_parse
-compatible
syntax trees is returned (see revert/1). If some program
form could not be reverted, {error, Form}
is thrown.
Standalone comments in the form sequence are discarded.
See also: form_list/1, is_form/1, revert/1.
subtrees(T::syntaxTree()) -> [[syntaxTree()]]
Returns the grouped list of all subtrees of a syntax tree. If
Node
is a leaf node (see is_leaf/1), this
is the empty list, otherwise the result is always a nonempty list,
containing the lists of subtrees of Node
, in
left-to-right order as they occur in the printed program text, and
grouped by category. Often, each group contains only a single
subtree.
Depending on the type of Node
, the size of some
groups may be variable (e.g., the group consisting of all the
elements of a tuple), while others always contain the same number of
elements - usually exactly one (e.g., the group containing the
argument expression of a case-expression). Note, however, that the
exact structure of the returned list (for a given node type) should
in general not be depended upon, since it might be subject to change
without notice.
The function subtrees/1 and the constructor functions make_tree/2 and update_tree/2 can be a great help if one wants to traverse a syntax tree, visiting all its subtrees, but treat nodes of the tree in a uniform way in most or all cases. Using these functions makes this simple, and also assures that your code is not overly sensitive to extensions of the syntax tree data type, because any node types not explicitly handled by your code can be left to a default case.
For example:
postorder(F, Tree) -> F(case subtrees(Tree) of [] -> Tree; List -> update_tree(Tree, [[postorder(F, Subtree) || Subtree <- Group] || Group <- List]) end).
maps the function F
on Tree
and all its
subtrees, doing a post-order traversal of the syntax tree. (Note the
use of update_tree/2 to preserve node attributes.) For a
simple function like:
f(Node) -> case type(Node) of atom -> atom("a_" ++ atom_name(Node)); _ -> Node end.
the call postorder(fun f/1, Tree)
will yield a new
representation of Tree
in which all atom names have been
extended with the prefix "a_", but nothing else (including comments,
annotations and line numbers) has been changed.
See also: copy_attrs/2, is_leaf/1, make_tree/2, type/1.
update_tree(Node::syntaxTree(), Groups::[[syntaxTree()]]) -> syntaxTree()
Creates a syntax tree with the same type and attributes as the
given tree. This is equivalent to copy_attrs(Node,
make_tree(type(Node), Groups))
.
See also: copy_attrs/2, make_tree/2, type/1.
make_tree(X1::atom(), X2::[[syntaxTree()]]) -> syntaxTree()
Creates a syntax tree with the given type and subtrees.
Type
must be a node type name (see type/1)
that does not denote a leaf node type (see is_leaf/1).
Groups
must be a nonempty list of groups of
syntax trees, representing the subtrees of a node of the given type,
in left-to-right order as they would occur in the printed program
text, grouped by category as done by subtrees/1.
The result of copy_attrs(Node, make_tree(type(Node),
subtrees(Node)))
(see update_tree/2) represents
the same source code text as the original Node
, assuming
that subtrees(Node)
yields a nonempty list. However, it
does not necessarily have the same data representation as
Node
.
See also: copy_attrs/2, is_leaf/1, subtrees/1, type/1, update_tree/2.
meta(T::syntaxTree()) -> syntaxTree()
Creates a meta-representation of a syntax tree. The result
represents an Erlang expression "MetaTree
"
which, if evaluated, will yield a new syntax tree representing the
same source code text as Tree
(although the actual data
representation may be different). The expression represented by
MetaTree
is implementation independent with
regard to the data structures used by the abstract syntax tree
implementation. Comments attached to nodes of Tree
will
be preserved, but other attributes are lost.
Any node in Tree
whose node type is
variable
(see type/1), and whose list of
annotations (see get_ann/1) contains the atom
meta_var
, will remain unchanged in the resulting tree,
except that exactly one occurrence of meta_var
is
removed from its annotation list.
The main use of the function meta/1
is to transform a
data structure Tree
, which represents a piece of program
code, into a form that is representation independent when
printed. E.g., suppose Tree
represents a variable
named "V". Then (assuming a function print/1
for
printing syntax trees), evaluating print(abstract(Tree))
- simply using abstract/1 to map the actual data
structure onto a syntax tree representation - would output a string
that might look something like "{tree, variable, ..., "V",
...}
", which is obviously dependent on the implementation of
the abstract syntax trees. This could e.g. be useful for caching a
syntax tree in a file. However, in some situations like in a program
generator generator (with two "generator"), it may be unacceptable.
Using print(meta(Tree))
instead would output a
representation independent syntax tree generating
expression; in the above case, something like
"erl_syntax:variable("V")
".
See also: abstract/1, get_ann/1, type/1.
tree(Type::atom()) -> #tree{}
Equivalent to tree(Type, []).
tree(Type::atom(), Data::term()) -> #tree{}
For special purposes only. Creates an abstract syntax
tree node with type tag Type
and associated data
Data
.
This function and the related is_tree/1 and
data/1 provide a uniform way to extend the set of
erl_parse
node types. The associated data is any term,
whose format may depend on the type tag.
Notes:
Any nodes created outside of this module must have type tags distinct from those currently defined by this module; see type/1 for a complete list.
The type tag of a syntax tree node may also be used as a primary tag by the
erl_parse
representation; in that case, the selector functions for that node type must handle both the abstract syntax tree and theerl_parse
form. The functiontype(T)
should return the correct type tag regardless of the representation ofT
, so that the user sees no difference betweenerl_syntax
anderl_parse
nodes.
is_tree(Tree::syntaxTree()) -> boolean()
For special purposes only. Returns true
if
Tree
is an abstract syntax tree and false
otherwise.
Note: this function yields false
for all
"old-style" erl_parse
-compatible "parse trees".
See also: tree/2.
data(Tree::syntaxTree()) -> term()
For special purposes only. Returns the associated data
of a syntax tree node. Evaluation fails with reason
badarg
if is_tree(Node)
does not yield
true
.
See also: tree/2.
- type/1
- is_leaf/1
- is_form/1
- get_pos/1
- set_pos/1
- copy_pos/1
- get_precomments/1
- set_precomments/1
- add_precomments/1
- get_postcomments/1
- set_postcomments/1
- add_postcomments/1
- has_comments/1
- remove_comments/1
- copy_comments/1
- join_comments/1
- get_ann/1
- set_ann/1
- add_ann/1
- copy_ann/1
- get_attrs/1
- set_attrs/1
- copy_attrs/1
- comment/1
- comment/1-1
- comment_text/1
- comment_padding/1
- form_list/1
- form_list_elements/1
- flatten_form_list/1
- text/1
- text_string/1
- variable/1
- variable_name/1
- variable_literal/1
- underscore/0
- integer/1
- is_integer/1
- integer_value/1
- integer_literal/1
- float/1
- float_value/1
- float_literal/1
- char/1
- is_char/1
- char_value/1
- char_literal/1
- char_literal/1-1
- string/1
- is_string/1
- string_value/1
- string_literal/1
- string_literal/1-1
- atom/1
- is_atom/1
- atom_value/1
- atom_name/1
- atom_literal/1
- tuple/1
- tuple_elements/1
- tuple_size/1
- list/1
- list/1-1
- nil/0
- list_prefix/1
- list_suffix/1
- cons/1
- list_head/1
- list_tail/1
- is_list_skeleton/1
- is_proper_list/1
- list_elements/1
- list_length/1
- normalize_list/1
- compact_list/1
- binary/1
- binary_fields/1
- binary_field/1
- binary_field/1-1
- binary_field/1-2
- binary_field_body/1
- binary_field_types/1
- binary_field_size/1
- size_qualifier/1
- size_qualifier_body/1
- size_qualifier_argument/1
- error_marker/1
- error_marker_info/1
- warning_marker/1
- warning_marker_info/1
- eof_marker/0
- attribute/1
- attribute/1-1
- attribute_name/1
- attribute_arguments/1
- arity_qualifier/1
- arity_qualifier_body/1
- arity_qualifier_argument/1
- module_qualifier/1
- module_qualifier_argument/1
- module_qualifier_body/1
- function/1
- function_name/1
- function_clauses/1
- function_arity/1
- clause/1
- clause/1-1
- clause_patterns/1
- clause_guard/1
- clause_body/1
- disjunction/1
- disjunction_body/1
- conjunction/1
- conjunction_body/1
- catch_expr/1
- catch_expr_body/1
- match_expr/1
- match_expr_pattern/1
- match_expr_body/1
- operator/1
- operator_name/1
- operator_literal/1
- infix_expr/1
- infix_expr_left/1
- infix_expr_operator/1
- infix_expr_right/1
- prefix_expr/1
- prefix_expr_operator/1
- prefix_expr_argument/1
- record_field/1
- record_field/1-1
- record_field_name/1
- record_field_value/1
- record_index_expr/1
- record_index_expr_type/1
- record_index_expr_field/1
- record_access/1
- record_access/1-1
- record_access_argument/1
- record_access_type/1
- record_access_field/1
- record_expr/1
- record_expr/1-1
- record_expr_argument/1
- record_expr_type/1
- record_expr_fields/1
- application/1
- application/1-1
- application_operator/1
- application_arguments/1
- list_comp/1
- list_comp_template/1
- list_comp_body/1
- binary_comp/1
- binary_comp_template/1
- binary_comp_body/1
- rule/1
- rule_name/1
- rule_clauses/1
- rule_arity/1
- generator/1
- generator_pattern/1
- generator_body/1
- binary_generator/1
- binary_generator_pattern/1
- binary_generator_body/1
- block_expr/1
- block_expr_body/1
- if_expr/1
- if_expr_clauses/1
- case_expr/1
- case_expr_argument/1
- case_expr_clauses/1
- cond_expr/1
- cond_expr_clauses/1
- receive_expr/1
- receive_expr/1-1
- receive_expr_clauses/1
- receive_expr_timeout/1
- receive_expr_action/1
- try_expr/1
- try_expr/1-1
- try_after_expr/1
- try_expr/1-2
- try_expr_body/1
- try_expr_clauses/1
- try_expr_handlers/1
- try_expr_after/1
- class_qualifier/1
- class_qualifier_argument/1
- class_qualifier_body/1
- implicit_fun/1
- implicit_fun/1-1
- implicit_fun/1-2
- implicit_fun_name/1
- fun_expr/1
- fun_expr_clauses/1
- fun_expr_arity/1
- parentheses/1
- parentheses_body/1
- macro/1
- macro/1-1
- macro_name/1
- macro_arguments/1
- abstract/1
- concrete/1
- is_literal/1
- revert/1
- revert_forms/1
- subtrees/1
- update_tree/1
- make_tree/1
- meta/1
- tree/1
- tree/1-1
- is_tree/1
- data/1