erl_parse (stdlib v3.15.2)
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.
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
Link to this section Summary
Types
Abstract form of an Erlang clause.
Abstract form of an Erlang expression.
Abstract form of an Erlang form.
Abstract form of an Erlang type.
Abstract representation of an element of a bitstring.
Abstract representation of a record field.
Abstract representation of a generator or a bitstring generator.
Abstract representation of a remote function call.
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.
Functions
Converts the Erlang data structure Data
into an abstract form of type AbsTerm
. This function is the inverse of normalise/1
.
Converts the Erlang data structure Data
into an abstract form of type AbsTerm
.
Assumes that Term
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 Term
is traversed in a depth-first, left-to-right fashion.
Returns a term where each collection of annotations Anno
of the nodes of the erl_parse
tree Abstr
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.
Updates an accumulator by applying Fun
on each collection of annotations of the erl_parse
tree Abstr
. The first call to Fun
has AccIn
as argument, the returned accumulator AccOut
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).
Modifies the erl_parse
tree Abstr
by applying Fun
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.
Modifies the erl_parse
tree Abstr
by applying Fun
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 Fun
has AccIn
as second argument, the returned accumulator AccOut
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.
Assumes that Term
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 Term
is traversed in a depth-first, left-to-right fashion.
Converts the abstract form AbsTerm
of a term into a conventional Erlang data structure (that is, the term itself). This function is the inverse of abstract/1
.
Parses Tokens
as if it was a list of expressions. Returns one of the following
Parses Tokens
as if it was a form. Returns one of the following
Parses Tokens
as if it was a term. Returns one of the following
Generates a list of tokens representing the abstract form AbsTerm
of an expression. Optionally, MoreTokens
is appended.
Link to this section Types
abstract_clause()
Specs
abstract_clause() :: af_clause().
Abstract form of an Erlang clause.
abstract_expr()
Specs
abstract_expr() :: af_literal() | af_match(abstract_expr()) | af_variable() | af_tuple(abstract_expr()) | af_nil() | af_cons(abstract_expr()) | af_bin(abstract_expr()) | af_binary_op(abstract_expr()) | af_unary_op(abstract_expr()) | af_record_creation(abstract_expr()) | af_record_update(abstract_expr()) | af_record_index() | af_record_field_access(abstract_expr()) | af_map_creation(abstract_expr()) | af_map_update(abstract_expr()) | af_catch() | af_local_call() | af_remote_call() | af_list_comprehension() | af_binary_comprehension() | af_block() | af_if() | af_case() | af_try() | af_receive() | af_local_fun() | af_remote_fun() | af_fun() | af_named_fun().
Abstract form of an Erlang expression.
abstract_form()
Specs
abstract_form() :: af_module() | af_behavior() | af_behaviour() | af_export() | af_import() | af_export_type() | af_compile() | af_file() | af_record_decl() | af_type_decl() | af_function_spec() | af_wild_attribute() | af_function_decl().
Abstract form of an Erlang form.
abstract_type()
Specs
abstract_type() :: af_annotated_type() | af_atom() | af_bitstring_type() | af_empty_list_type() | af_fun_type() | af_integer_range_type() | af_map_type() | af_predefined_type() | af_record_type() | af_remote_type() | af_singleton_integer_type() | af_tuple_type() | af_type_union() | af_type_variable() | af_user_defined_type().
Abstract form of an Erlang type.
af_binelement(_)
Specs
af_binelement(T) :: {bin_element, anno(), T, af_binelement_size(), type_specifier_list()}.
Abstract representation of an element of a bitstring.
af_field_decl()
Specs
af_field_decl() :: af_typed_field() | af_field().
Abstract representation of a record field.
af_generator()
Specs
af_generator() :: {generate, anno(), af_pattern(), abstract_expr()} | {b_generate, anno(), af_pattern(), abstract_expr()}.
Abstract representation of a generator or a bitstring generator.
af_remote_function()>
Specs
af_remote_function() :: {remote, anno(), abstract_expr(), abstract_expr()}.
Abstract representation of a remote function call.
-type erl_parse_tree() :: term().
Specs
erl_parse_tree() :: abstract_clause() | abstract_expr() | abstract_form() | abstract_type().
-type error_description() :: term().
Specs
error_description() :: term().
-type error_info() :: term().
Specs
error_info() :: {erl_anno:location(), module(), error_description()}.
-type form_info() :: term().
Specs
form_info() :: {eof, erl_anno:location()} | {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.
-type token() :: term().
Specs
token() :: erl_scan:token().
Link to this section Functions
abstract/1
Specs
abstract(Data) -> AbsTerm when Data :: term(), AbsTerm :: abstract_expr().
Converts the Erlang data structure Data
into an abstract form of type AbsTerm
. This function is the inverse of normalise/1
.
erl_parse:abstract(T)
is equivalent to erl_parse:abstract(T, 0)
.
Specs
abstract(Data, Options) -> AbsTerm when Data :: term(), Options :: Location | [Option], Option :: {encoding, Encoding} | {line, Line} | {location, Location}, Encoding :: latin1 | unicode | utf8 | none | encoding_func(), Line :: erl_anno:line(), Location :: erl_anno:location(), AbsTerm :: abstract_expr().
Converts the Erlang data structure Data
into an abstract form of type AbsTerm
.
Each node of AbsTerm
is assigned an annotation, see erl_anno(3)
. The annotation contains the location given by option location
or by option line
. Option location
overrides option line
. If neither option location
nor option line
is given, 0
is used as location.
Option Encoding
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.
Specs
anno_from_term(Term) -> erl_parse_tree() | form_info() when Term :: term().
Assumes that Term
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 Term
is traversed in a depth-first, left-to-right fashion.
Specs
anno_to_term(Abstr) -> term() when Abstr :: erl_parse_tree() | form_info().
Returns a term where each collection of annotations Anno
of the nodes of the erl_parse
tree Abstr
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.
Specs
fold_anno(Fun, Acc0, Abstr) -> Acc1 when Fun :: fun((Anno, AccIn) -> AccOut), Anno :: erl_anno:anno(), Acc0 :: term(), Acc1 :: term(), AccIn :: term(), AccOut :: term(), Abstr :: erl_parse_tree() | form_info().
Updates an accumulator by applying Fun
on each collection of annotations of the erl_parse
tree Abstr
. The first call to Fun
has AccIn
as argument, the returned accumulator AccOut
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.
format_error(ErrorDescriptor) -> Chars
Specs
format_error(any()) -> [char() | list()].
- 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).
Specs
map_anno(Fun, Abstr) -> NewAbstr when Fun :: fun((Anno) -> NewAnno), Anno :: erl_anno:anno(), NewAnno :: erl_anno:anno(), Abstr :: erl_parse_tree() | form_info(), NewAbstr :: erl_parse_tree() | form_info().
Modifies the erl_parse
tree Abstr
by applying Fun
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.
Specs
mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1} when Fun :: fun((Anno, AccIn) -> {NewAnno, AccOut}), Anno :: erl_anno:anno(), NewAnno :: erl_anno:anno(), Acc0 :: term(), Acc1 :: term(), AccIn :: term(), AccOut :: term(), Abstr :: erl_parse_tree() | form_info(), NewAbstr :: erl_parse_tree() | form_info().
Modifies the erl_parse
tree Abstr
by applying Fun
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 Fun
has AccIn
as second argument, the returned accumulator AccOut
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.
Specs
new_anno(Term) -> Abstr when Term :: term(), Abstr :: erl_parse_tree() | form_info().
Assumes that Term
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 Term
is traversed in a depth-first, left-to-right fashion.
normalise/1
Specs
normalise(AbsTerm) -> Data when AbsTerm :: abstract_expr(), Data :: term().
Converts the abstract form AbsTerm
of a term into a conventional Erlang data structure (that is, the term itself). This function is the inverse of abstract/1
.
parse_exprs/1
Specs
parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo} when Tokens :: [token()], ExprList :: [abstract_expr()], ErrorInfo :: error_info().
Parses Tokens
as if it was a list of expressions. Returns one of the following:
{ok, ExprList}
The parsing was successful.
ExprList
is a list of the abstract forms of the parsed expressions.{error, ErrorInfo}
An error occurred.
parse_form/1
Specs
parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo} when Tokens :: [token()], AbsForm :: abstract_form(), ErrorInfo :: error_info().
Parses Tokens
as if it was a form. Returns one of the following:
{ok, AbsForm}
The parsing was successful.
AbsForm
is the abstract form of the parsed form.{error, ErrorInfo}
An error occurred.
parse_term/1
Specs
parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo} when Tokens :: [token()], Term :: term(), ErrorInfo :: error_info().
Parses Tokens
as if it was a term. Returns one of the following:
{ok, Term}
The parsing was successful.
Term
is the Erlang term corresponding to the token list.{error, ErrorInfo}
An error occurred.
tokens/1
Specs
tokens(AbsTerm) -> Tokens when AbsTerm :: abstract_expr(), Tokens :: [token()].
Generates a list of tokens representing the abstract form AbsTerm
of an expression. Optionally, MoreTokens
is appended.
tokens/2
Specs
tokens(AbsTerm, MoreTokens) -> Tokens when AbsTerm :: abstract_expr(), MoreTokens :: [token()], Tokens :: [token()].