~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/erl_parse.xml

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
4
4
<erlref>
5
5
  <header>
6
6
    <copyright>
7
 
      <year>1996</year><year>2010</year>
 
7
      <year>1996</year><year>2011</year>
8
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
9
9
    </copyright>
10
10
    <legalnotice>
36
36
  <description>
37
37
    <p>This module is the basic Erlang parser which converts tokens into
38
38
      the abstract form of either forms (i.e., top-level constructs),
39
 
      expressions, or terms. The Abstract Format is described in the ERTS
40
 
      User's Guide.
 
39
      expressions, or terms. The Abstract Format is described in the
 
40
      <seealso marker="erts:absform">ERTS User's Guide</seealso>.
41
41
      Note that a token list must end with the <em>dot</em> token in order
42
42
      to be acceptable to the parse functions (see <seealso marker="erl_scan">erl_scan(3)</seealso>).</p>
43
43
  </description>
 
44
  <datatypes>
 
45
    <datatype>
 
46
      <name name="abstract_clause"></name>
 
47
      <desc><p>Parse tree for Erlang clause.</p>
 
48
      </desc>
 
49
    </datatype>
 
50
    <datatype>
 
51
      <name name="abstract_expr"></name>
 
52
      <desc><p>Parse tree for Erlang expression.</p>
 
53
      </desc>
 
54
    </datatype>
 
55
    <datatype>
 
56
      <name name="abstract_form"></name>
 
57
      <desc><p>Parse tree for Erlang form.</p>
 
58
      </desc>
 
59
    </datatype>
 
60
    <datatype>
 
61
      <name name="error_description"></name>
 
62
    </datatype>
 
63
    <datatype>
 
64
      <name name="error_info"></name>
 
65
    </datatype>
 
66
    <datatype>
 
67
      <name name="token"></name>
 
68
    </datatype>
 
69
  </datatypes>
44
70
  <funcs>
45
71
    <func>
46
 
      <name>parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo}</name>
 
72
      <name name="parse_form" arity="1"/>
47
73
      <fsummary>Parse an Erlang form</fsummary>
48
 
      <type>
49
 
        <v>Tokens = [Token]</v>
50
 
        <v>Token = {Tag,Line} | {Tag,Line,term()}</v>
51
 
        <v>Tag = atom()</v>
52
 
        <v>AbsForm = term()</v>
53
 
        <v>ErrorInfo = see section Error Information below.</v>
54
 
      </type>
55
74
      <desc>
56
 
        <p>This function parses <c>Tokens</c> as if it were a form. It returns:</p>
 
75
        <p>This function parses <c><anno>Tokens</anno></c> as if it were
 
76
          a form. It returns:</p>
57
77
        <taglist>
58
 
          <tag><c>{ok, AbsForm}</c></tag>
 
78
          <tag><c>{ok, <anno>AbsForm</anno>}</c></tag>
59
79
          <item>
60
 
            <p>The parsing was successful. <c>AbsForm</c> is the
 
80
            <p>The parsing was successful. <c><anno>AbsForm</anno></c> is the
61
81
              abstract form of the parsed form.</p>
62
82
          </item>
63
 
          <tag><c>{error, ErrorInfo}</c></tag>
 
83
          <tag><c>{error, <anno>ErrorInfo</anno>}</c></tag>
64
84
          <item>
65
85
            <p>An error occurred.</p>
66
86
          </item>
68
88
      </desc>
69
89
    </func>
70
90
    <func>
71
 
      <name>parse_exprs(Tokens) -> {ok, Expr_list} | {error, ErrorInfo}</name>
 
91
      <name name="parse_exprs" arity="1"/>
72
92
      <fsummary>Parse Erlang expressions</fsummary>
73
 
      <type>
74
 
        <v>Tokens = [Token]</v>
75
 
        <v>Token = {Tag,Line} | {Tag,Line,term()}</v>
76
 
        <v>Tag = atom()</v>
77
 
        <v>Expr_list = [AbsExpr]</v>
78
 
        <v>AbsExpr = term()</v>
79
 
        <v>ErrorInfo = see section Error Information below.</v>
80
 
      </type>
81
93
      <desc>
82
 
        <p>This function parses <c>Tokens</c> as if it were a list of expressions. It returns:</p>
 
94
        <p>This function parses <c><anno>Tokens</anno></c> as if it were
 
95
          a list of expressions. It returns:</p>
83
96
        <taglist>
84
 
          <tag><c>{ok, Expr_list}</c></tag>
 
97
          <tag><c>{ok, <anno>ExprList</anno>}</c></tag>
85
98
          <item>
86
 
            <p>The parsing was successful. <c>Expr_list</c> is a
 
99
            <p>The parsing was successful. <c><anno>ExprList</anno></c> is a
87
100
              list of the abstract forms of the parsed expressions.</p>
88
101
          </item>
89
 
          <tag><c>{error, ErrorInfo}</c></tag>
 
102
          <tag><c>{error, <anno>ErrorInfo</anno>}</c></tag>
90
103
          <item>
91
104
            <p>An error occurred.</p>
92
105
          </item>
94
107
      </desc>
95
108
    </func>
96
109
    <func>
97
 
      <name>parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo}</name>
 
110
      <name name="parse_term" arity="1"/>
98
111
      <fsummary>Parse an Erlang term</fsummary>
99
 
      <type>
100
 
        <v>Tokens = [Token]</v>
101
 
        <v>Token = {Tag,Line} | {Tag,Line,term()}</v>
102
 
        <v>Tag = atom()</v>
103
 
        <v>Term = term()</v>
104
 
        <v>ErrorInfo = see section Error Information below.</v>
105
 
      </type>
106
112
      <desc>
107
 
        <p>This function parses <c>Tokens</c> as if it were a term. It returns:</p>
 
113
        <p>This function parses <c><anno>Tokens</anno></c> as if it were
 
114
          a term. It returns:</p>
108
115
        <taglist>
109
 
          <tag><c>{ok, Term}</c></tag>
 
116
          <tag><c>{ok, <anno>Term</anno>}</c></tag>
110
117
          <item>
111
 
            <p>The parsing was successful. <c>Term</c> is
 
118
            <p>The parsing was successful. <c><anno>Term</anno></c> is
112
119
              the Erlang term corresponding to the token list.</p>
113
120
          </item>
114
121
          <tag><c>{error, ErrorInfo}</c></tag>
122
129
      <name>format_error(ErrorDescriptor) -> Chars</name>
123
130
      <fsummary>Format an error descriptor</fsummary>
124
131
      <type>
125
 
        <v>ErrorDescriptor = errordesc()</v>
 
132
        <v>ErrorDescriptor = <seealso
 
133
          marker="#type-error_info">error_description()</seealso></v>
126
134
        <v>Chars = [char() | Chars]</v>
127
135
      </type>
128
136
      <desc>
133
141
      </desc>
134
142
    </func>
135
143
    <func>
136
 
      <name>tokens(AbsTerm) -> Tokens</name>
137
 
      <name>tokens(AbsTerm, MoreTokens) -> Tokens</name>
 
144
      <name name="tokens" arity="1"/>
 
145
      <name name="tokens" arity="2"/>
138
146
      <fsummary>Generate a list of tokens for an expression</fsummary>
139
 
      <type>
140
 
        <v>Tokens = MoreTokens = [Token]</v>
141
 
        <v>Token = {Tag,Line} | {Tag,Line,term()}</v>
142
 
        <v>Tag = atom()</v>
143
 
        <v>AbsTerm = term()</v>
144
 
        <v>ErrorInfo = see section Error Information below.</v>
145
 
      </type>
146
147
      <desc>
147
148
        <p>This function generates a list of tokens representing the abstract
148
 
          form <c>AbsTerm</c> of an expression. Optionally, it appends
149
 
          <c>Moretokens</c>.</p>
 
149
          form <c><anno>AbsTerm</anno></c> of an expression. Optionally, it
 
150
          appends <c><anno>MoreTokens</anno></c>.</p>
150
151
      </desc>
151
152
    </func>
152
153
    <func>
153
 
      <name>normalise(AbsTerm) -> Data</name>
 
154
      <name name="normalise" arity="1"/>
154
155
      <fsummary>Convert abstract form to an Erlang term</fsummary>
155
 
      <type>
156
 
        <v>AbsTerm = Data = term()</v>
157
 
      </type>
158
156
      <desc>
159
 
        <p>Converts the abstract form <c>AbsTerm</c> of a term into a
 
157
        <p>Converts the abstract form <c><anno>AbsTerm</anno></c> of a
 
158
          term into a
160
159
          conventional Erlang data structure (i.e., the term itself).
161
160
          This is the inverse of <c>abstract/1</c>.</p>
162
161
      </desc>
163
162
    </func>
164
163
    <func>
165
 
      <name>abstract(Data) -> AbsTerm</name>
 
164
      <name name="abstract" arity="1"/>
166
165
      <fsummary>Convert an Erlang term into an abstract form</fsummary>
167
 
      <type>
168
 
        <v>Data = AbsTerm = term()</v>
169
 
      </type>
170
166
      <desc>
171
 
        <p>Converts the Erlang data structure <c>Data</c> into an
172
 
          abstract form of type <c>AbsTerm</c>. This is the inverse of
173
 
          <c>normalise/1</c>.</p>
 
167
        <p>Converts the Erlang data structure <c><anno>Data</anno></c> into an
 
168
          abstract form of type <c><anno>AbsTerm</anno></c>.
 
169
          This is the inverse of <c>normalise/1</c>.</p>
174
170
      </desc>
175
171
    </func>
176
172
  </funcs>