The Erlang parser.
This module is the basic Erlang parser that converts tokens into
the abstract form of either forms (that is, top-level constructs),
expressions, or terms. The Abstract Format is described in the
ERTS User's Guide.
Notice that a token list must end with the dot token to be
acceptable to the parse functions (see the
erl_scan(3)
) module.
Types
abstract_clause()
Abstract form of an Erlang clause.
abstract_expr()
Abstract form of an Erlang expression.
abstract_form()
Abstract form of an Erlang form.
abstract_type()
Abstract form of an Erlang type.
erl_parse_tree() =
abstract_clause() |
abstract_expr() |
abstract_form() |
abstract_type()
error_description() = term()
error_info() = {erl_anno:line(), module(), error_description()}
form_info() =
{eof, erl_anno:line()} |
{error, erl_scan:error_info() | error_info()} |
{warning, erl_scan:error_info() | error_info()}
Tuples {error, error_info()}
and {warning,
error_info()}
, denoting syntactically incorrect forms and
warnings, and {eof, line()}
, denoting an end-of-stream
encountered before a complete form had been parsed.
token() = erl_scan:token()
Functions
abstract(Data) -> AbsTerm
Data = term()
AbsTerm = abstract_expr()
Converts the Erlang data structure
into an
abstract form of type
.
This function is the inverse of
normalise/1
.
erl_parse:abstract(T)
is equivalent to
erl_parse:abstract(T, 0)
.
abstract(Data, Options) -> AbsTerm
Data = term()
Options = Line | [Option]
Option = {line, Line} | {encoding, Encoding}
Encoding = latin1 | unicode | utf8 | none | encoding_func()
Line = erl_anno:line()
AbsTerm = abstract_expr()
encoding_func() = fun((integer() >= 0) -> boolean())
Converts the Erlang data structure
into an
abstract form of type
.
Option
is the line to be
assigned to each node of
.
Option
is used for
selecting which integer lists to be considered
as strings. The default is to use the encoding returned by
function
epp:default_encoding/0
.
Value none
means that no integer lists are
considered as strings. encoding_func()
is
called with one integer of a list at a time; if it
returns true
for every integer, the list is
considered a string.
anno_from_term(Term) -> erl_parse_tree() | form_info()
Term = term()
Assumes that
is a term with the same
structure as a erl_parse
tree, but with terms,
say T
, where a erl_parse
tree has collections
of annotations. Returns a erl_parse
tree where each
term T
is replaced by the value returned by
erl_anno:from_term(T)
. The term
is traversed in a depth-first,
left-to-right fashion.
anno_to_term(Abstr) -> term()
Abstr = erl_parse_tree() | form_info()
Returns a term where each collection of annotations
Anno
of the nodes of the erl_parse
tree
is replaced by the term
returned by
erl_anno:to_term(Anno)
. The
erl_parse
tree is traversed in a depth-first,
left-to-right fashion.
fold_anno(Fun, Acc0, Abstr) -> Acc1
Fun = fun((Anno, AccIn) -> AccOut)
Anno = erl_anno:anno()
Acc0 = Acc1 = AccIn = AccOut = term()
Abstr = erl_parse_tree() | form_info()
Updates an accumulator by applying
on
each collection of annotations of the erl_parse
tree
. The first call to
has
as
argument, the returned accumulator
is passed to the next call, and
so on. The final value of the accumulator is returned. The
erl_parse
tree is traversed in a depth-first, left-to-right
fashion.
ErrorDescriptor = error_description()
Chars = [char() | Chars]
Uses an ErrorDescriptor
and returns a string
that describes the error. This function is usually called
implicitly when an ErrorInfo
structure is processed
(see section
Error Information).
map_anno(Fun, Abstr) -> NewAbstr
Fun = fun((Anno) -> NewAnno)
Anno = NewAnno = erl_anno:anno()
Abstr = NewAbstr = erl_parse_tree() | form_info()
Modifies the erl_parse
tree
by applying
on each collection of
annotations of the nodes of the erl_parse
tree. The
erl_parse
tree is traversed in a depth-first,
left-to-right fashion.
mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1}
Fun = fun((Anno, AccIn) -> {NewAnno, AccOut})
Anno = NewAnno = erl_anno:anno()
Acc0 = Acc1 = AccIn = AccOut = term()
Abstr = NewAbstr = erl_parse_tree() | form_info()
Modifies the erl_parse
tree
by applying
on each collection of
annotations of the nodes of the erl_parse
tree, while
at the same time updating an accumulator. The first call to
has
as
second argument, the returned accumulator
is passed to the next call, and
so on. The modified erl_parse
tree and the
final value of the accumulator are returned. The
erl_parse
tree is traversed in a depth-first,
left-to-right fashion.
new_anno(Term) -> Abstr
Term = term()
Abstr = erl_parse_tree() | form_info()
Assumes that
is a term with the same
structure as a erl_parse
tree, but with locations where a
erl_parse
tree has collections of annotations.
Returns a erl_parse
tree where each location L
is replaced by the value returned by erl_anno:new(L)
.
The term
is traversed in a
depth-first, left-to-right fashion.
normalise(AbsTerm) -> Data
AbsTerm = abstract_expr()
Data = term()
Converts the abstract form
of a
term into a conventional Erlang data structure (that is, the
term itself). This function is the inverse of
abstract/1
.
parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo}
Tokens = [token()]
ExprList = [abstract_expr()]
ErrorInfo = error_info()
Parses
as if it was a list of expressions.
Returns one of the following:
{ok, ExprList }
The parsing was successful.
is a
list of the abstract forms of the parsed expressions.
{error, ErrorInfo }
An error occurred.
parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo}
Tokens = [token()]
AbsForm = abstract_form()
ErrorInfo = error_info()
Parses
as if it was a form. Returns one
of the following:
{ok, AbsForm }
The parsing was successful.
is the
abstract form of the parsed form.
{error, ErrorInfo }
An error occurred.
parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo}
Tokens = [token()]
Term = term()
ErrorInfo = error_info()
Parses
as if it was a term. Returns
one of the following:
{ok, Term }
The parsing was successful.
is
the Erlang term corresponding to the token list.
{error, ErrorInfo }
An error occurred.
tokens(AbsTerm) -> Tokens
AbsTerm = abstract_expr()
Tokens = [token()]
tokens(AbsTerm, MoreTokens) -> Tokens
AbsTerm = abstract_expr()
MoreTokens = Tokens = [token()]
Generates a list of tokens representing the abstract
form
of an expression. Optionally,
is appended.
Error Information
ErrorInfo
is the standard ErrorInfo
structure that is
returned from all I/O modules. The format is as follows:
{ErrorLine, Module, ErrorDescriptor}
A string describing the error is obtained with the following call:
Module:format_error(ErrorDescriptor)
See Also
erl_anno(3)
,
erl_scan(3)
,
io(3)
,
section The Abstract Format
in the ERTS User's Guide