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() = term()
Parse tree for Erlang clause.
abstract_expr() = term()
Parse tree for Erlang expression.
abstract_form() = term()
Parse tree for Erlang form.
error_description() = term()
error_info() = {erl_scan:line(), module(), error_description()}
token() = erl_scan:token()
Functions
parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo}
Tokens = [token()]AbsForm = abstract_form()ErrorInfo = error_info()
This function parses  as if it were
          a form. It returns:
{ok, AbsForm }The parsing was successful.  is the
              abstract form of the parsed form.
{error, ErrorInfo }An error occurred.
parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo}
Tokens = [token()]ExprList = [abstract_expr()]ErrorInfo = error_info()
This function parses  as if it were
          a list of expressions. It returns:
{ok, ExprList }The parsing was successful.  is a
              list of the abstract forms of the parsed expressions.
{error, ErrorInfo }An error occurred.
parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo}
Tokens = [token()]Term = term()ErrorInfo = error_info()
This function parses  as if it were
          a term. It returns:
{ok, Term }The parsing was successful.  is
              the Erlang term corresponding to the token list.
{error, ErrorInfo}An error occurred.
format_error(ErrorDescriptor) -> Chars
ErrorDescriptor = error_description()Chars = [char() | 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
AbsTerm = abstract_expr()Tokens = [token()]
tokens(AbsTerm, MoreTokens) -> Tokens
AbsTerm = abstract_expr()MoreTokens = Tokens = [token()]
This function generates a list of tokens representing the abstract
          form  of an expression. Optionally, it
          appends .
normalise(AbsTerm) -> Data
AbsTerm = abstract_expr()Data = term()
Converts the abstract form  of a
          term into a
          conventional Erlang data structure (i.e., the term itself).
          This is the inverse of abstract/1.
abstract(Data) -> AbsTerm
Data = term()AbsTerm = abstract_expr()
Converts the Erlang data structure  into an
          abstract form of type .
          This 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_scan:line()AbsTerm = abstract_expr()
encoding_func() = fun((integer() >= 0) -> boolean())
Converts the Erlang data structure  into an
          abstract form of type .
The  option is the line that will
          be assigned to each node of the abstract form.
The  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.
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)    
  See Also
io(3), erl_scan(3), ERTS User's Guide