erl_parse

The Erlang Parser

This module is the basic Erlang parser which converts tokens into the abstract form of either forms (i.e., top-level constructs), expressions, or terms. The Abstract Format is described in the ERTS User's Guide. Note that a token list must end with the dot token in order to be acceptable to the parse functions (see erl_scan(3)).

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()}

token() = erl_scan:token()

Functions


parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo}

This function parses Tokens as if it were a form. It returns:

{ok, AbsForm}

The parsing was successful. AbsForm is the abstract form of the parsed form.

{error, ErrorInfo}

An error occurred.

parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo}

This function parses Tokens as if it were a list of expressions. It returns:

{ok, ExprList}

The parsing was successful. ExprList is a list of the abstract forms of the parsed expressions.

{error, ErrorInfo}

An error occurred.

parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo}

This function parses Tokens as if it were a term. It returns:

{ok, Term}

The parsing was successful. Term is the Erlang term corresponding to the token list.

{error, ErrorInfo}

An error occurred.

format_error(ErrorDescriptor) -> Chars

Uses an ErrorDescriptor and returns a string which describes the error. This function is usually called implicitly when an ErrorInfo structure is processed (see below).

tokens(AbsTerm) -> Tokens

tokens(AbsTerm, MoreTokens) -> Tokens

This function generates a list of tokens representing the abstract form AbsTerm of an expression. Optionally, it appends MoreTokens.

normalise(AbsTerm) -> Data

Converts the abstract form AbsTerm of a term into a conventional Erlang data structure (i.e., the term itself). This is the inverse of abstract/1.

abstract(Data) -> AbsTerm

Converts the Erlang data structure Data into an abstract form of type AbsTerm. This is the inverse of normalise/1.

erl_parse:abstract(T) is equivalent to erl_parse:abstract(T, 0).

abstract(Data, Options) -> AbsTerm

  • encoding_func() = fun((integer() >= 0) -> boolean())

Converts the Erlang data structure Data into an abstract form of type AbsTerm.

The Line option is the line that will be assigned to each node of AbsTerm.

The Encoding option is used for selecting which integer lists will be considered as strings. The default is to use the encoding returned by epp:default_encoding/0. The value none means that no integer lists will be considered as strings. The encoding_func() will be called with one integer of a list at a time, and if it returns true for every integer the list will be considered a string.

map_anno(Fun, Abstr) -> NewAbstr

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.

fold_anno(Fun, Acc0, Abstr) -> NewAbstr

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, and 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.

mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1}

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, and the returned accumulator AccOut is passed to the next call, and so on. The modified erl_parse tree as well as the 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

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 has been replaced by the value returned by erl_anno:new(L). The term Term is traversed in a depth-first, left-to-right, fashion.

anno_from_term(Term) -> erl_parse_tree()

  • Term = term()

Assumes that Term is a term with the same structure as a erl_parse tree, but with terms, T say, where a erl_parse tree has collections of annotations. Returns a erl_parse tree where each term T has been replaced by the value returned by erl_anno:from_term(T). The term Term is traversed in a depth-first, left-to-right, fashion.

anno_to_term(Abstr) -> term()

Returns a term where each collection of annotations Anno of the nodes of the erl_parse tree Abstr has been 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.

Error Information

The ErrorInfo mentioned above is the standard ErrorInfo structure which is returned from all IO modules. It has the format:

    {ErrorLine, Module, ErrorDescriptor}    

A string which describes the error is obtained with the following call:

    Module:format_error(ErrorDescriptor)