From 68d53c01b0b8e9a007a6a30158c19e34b2d2a34e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Wed, 18 May 2016 15:53:35 +0200 Subject: Update STDLIB documentation MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Language cleaned up by the technical writers xsipewe and tmanevik from Combitech. Proofreading and corrections by Björn Gustavsson and Hans Bolinder. --- lib/stdlib/doc/src/erl_parse.xml | 373 ++++++++++++++++++++------------------- 1 file changed, 187 insertions(+), 186 deletions(-) (limited to 'lib/stdlib/doc/src/erl_parse.xml') diff --git a/lib/stdlib/doc/src/erl_parse.xml b/lib/stdlib/doc/src/erl_parse.xml index 771ccc2dc6..647f36883c 100644 --- a/lib/stdlib/doc/src/erl_parse.xml +++ b/lib/stdlib/doc/src/erl_parse.xml @@ -28,20 +28,22 @@ 1 Bjarne Däcker - 97-01-24 + 1997-01-24 B - erl_parse.sgml + erl_parse.xml erl_parse - The Erlang Parser + 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), +

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. - Note that a token list must end with the dot token in order - to be acceptable to the parse functions (see erl_scan(3)).

+ Notice that a token list must end with the dot token to be + acceptable to the parse functions (see the + erl_scan(3)) module.

+ abstract_clause() @@ -84,258 +86,257 @@ + - - - Parse an Erlang form - -

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 Erlang expressions - -

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 an Erlang term - -

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 - Format an error descriptor - - 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).

-
-
- - - - Generate a list of tokens for an expression - -

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

-
-
- - - Convert abstract form to an Erlang term - -

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.

-
-
- Convert an Erlang term into an abstract form + Convert an Erlang term into an abstract form.

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

+ This function is the inverse of + normalise/1.

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

+ - Convert an Erlang term into an abstract form + Convert an Erlang term into an abstract form.

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 +

Option Line is the line to be + assigned to each node of AbsTerm.

+

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. - 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 + 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.

+ - - - Map a function over the annotations of a erl_parse tree - + + Return annotations as terms. -

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

+

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.

+
+
+ + + + Return the representation of annotations. + +

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.

+ - - Fold a function over the annotations of a erl_parse tree + Fold a function over the annotations of an erl_parse tree.

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 + 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. -

+ erl_parse tree is traversed in a depth-first, left-to-right + fashion.

+ - - - Map and fold a function over the annotations of a - erl_parse tree + format_error(ErrorDescriptor) -> Chars + Format an error descriptor. + + 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 a function over the annotations of an erl_parse tree.

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

+ 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.

+
+
+ + + + Map and fold a function over the annotations of an + erl_parse tree. + +

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.

+ - - Create new annotations - + Create new annotations.

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

+ depth-first, left-to-right fashion.

+ - - - Return annotations as terms - + + Convert abstract form to an Erlang 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. -

+

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.

+ - - - Return the representation of annotations - + + Parse Erlang expressions. -

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

+

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 an Erlang form. + +

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 an Erlang term. + +

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.

+
+
+
+
+ + + + + Generate a list of tokens for an expression. + +

Generates a list of tokens representing the abstract + form AbsTerm of an expression. Optionally, + MoreTokens is appended.

+ Error Information -

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

+

ErrorInfo is the standard ErrorInfo structure that is + returned from all I/O modules. The format is as follows:

- {ErrorLine, Module, ErrorDescriptor} -

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

+{ErrorLine, Module, ErrorDescriptor} +

A string describing the error is obtained with the following call:

- Module:format_error(ErrorDescriptor) +Module:format_error(ErrorDescriptor)
See Also -

io(3), - erl_anno(3), - erl_scan(3), - ERTS User's Guide

+

erl_anno(3), + erl_scan(3), + io(3), + section The Abstract Format + in the ERTS User's Guide

-- cgit v1.2.3