~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/syntax_tools/src/erl_syntax_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% =====================================================================
2
 
%% Support library for abstract Erlang syntax trees.
3
 
%%
4
 
%% Copyright (C) 1997-2002 Richard Carlsson
5
 
%%
6
2
%% This library is free software; you can redistribute it and/or modify
7
3
%% it under the terms of the GNU Lesser General Public License as
8
4
%% published by the Free Software Foundation; either version 2 of the
18
14
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
19
15
%% USA
20
16
%%
21
 
%% Author contact: richardc@csd.uu.se
22
 
%%
23
17
%% $Id$
24
18
%%
 
19
%% @copyright 1997-2006 Richard Carlsson
 
20
%% @author Richard Carlsson <richardc@it.uu.se>
 
21
%% @end
25
22
%% =====================================================================
26
 
%%
 
23
 
27
24
%% @doc Support library for abstract Erlang syntax trees.
28
25
%%
29
 
%% <p> This module contains utility functions for working with the
30
 
%% abstract data type defined in the module <a
31
 
%% href="erl_syntax.html"><code>erl_syntax</code></a>.</p>
 
26
%% This module contains utility functions for working with the
 
27
%% abstract data type defined in the module {@link erl_syntax}.
32
28
%%
33
29
%% @type syntaxTree() = erl_syntax:syntaxTree(). An abstract syntax
34
 
%% tree. See the <code>erl_syntax</code> module for details.
 
30
%% tree. See the {@link erl_syntax} module for details.
35
31
 
36
32
-module(erl_syntax_lib).
37
33
 
102
98
%%          Function = (syntaxTree(), term()) -> term()
103
99
%%
104
100
%% @doc Folds a function over all nodes of a syntax tree. The result is
105
 
%% the value of <code>Function(X1, Function(X2, ... Function(Xn, Start)
106
 
%% ... ))</code>, where <code>[X1, X2, ..., Xn]</code> are the nodes of
107
 
%% <code>Tree</code> in a post-order traversal.
 
101
%% the value of `Function(X1, Function(X2, ... Function(Xn, Start)
 
102
%% ... ))', where `[X1, X2, ..., Xn]' are the nodes of
 
103
%% `Tree' in a post-order traversal.
108
104
%%
109
105
%% @see fold_subtrees/3
110
106
%% @see foldl_listlist/3
135
131
%%          Function = (syntaxTree(), term()) -> term()
136
132
%%
137
133
%% @doc Folds a function over the immediate subtrees of a syntax tree.
138
 
%% This is similar to <code>fold/3</code>, but only on the immediate
139
 
%% subtrees of <code>Tree</code>, in left-to-right order; it does not
140
 
%% include the root node of <code>Tree</code>.
 
134
%% This is similar to `fold/3', but only on the immediate
 
135
%% subtrees of `Tree', in left-to-right order; it does not
 
136
%% include the root node of `Tree'.
141
137
%%
142
138
%% @see fold/3
143
139
 
150
146
%%
151
147
%%          Function = (term(), term()) -> term()
152
148
%%
153
 
%% @doc Like <code>lists:foldl/3</code>, but over a list of lists.
 
149
%% @doc Like `lists:foldl/3', but over a list of lists.
154
150
%%
155
151
%% @see fold/3
156
 
%% @see lists:foldl/3
 
152
%% @see //stdlib/lists:foldl/3
157
153
 
158
154
foldl_listlist(F, S, [L | Ls]) ->
159
155
    foldl_listlist(F, foldl(F, S, L), Ls);
173
169
%%          Function = (syntaxTree(), term()) -> {syntaxTree(), term()}
174
170
%%
175
171
%% @doc Combines map and fold in a single operation. This is similar to
176
 
%% <code>map/2</code>, but also propagates an extra value from each
177
 
%% application of the <code>Function</code> to the next, while doing a
178
 
%% post-order traversal of the tree like <code>fold/3</code>. The value
179
 
%% <code>Start</code> is passed to the first function application, and
 
172
%% `map/2', but also propagates an extra value from each
 
173
%% application of the `Function' to the next, while doing a
 
174
%% post-order traversal of the tree like `fold/3'. The value
 
175
%% `Start' is passed to the first function application, and
180
176
%% the final result is the result of the last application.
181
177
%%
182
178
%% @see map/2
214
210
%%          Function = (syntaxTree(), term()) -> {syntaxTree(), term()}
215
211
%%
216
212
%% @doc Does a mapfold operation over the immediate subtrees of a syntax
217
 
%% tree. This is similar to <code>mapfold/3</code>, but only on the
218
 
%% immediate subtrees of <code>Tree</code>, in left-to-right order; it
219
 
%% does not include the root node of <code>Tree</code>.
 
213
%% tree. This is similar to `mapfold/3', but only on the
 
214
%% immediate subtrees of `Tree', in left-to-right order; it
 
215
%% does not include the root node of `Tree'.
220
216
%%
221
217
%% @see mapfold/3
222
218
 
237
233
%%
238
234
%%          Function = (term(), term()) -> {term(), term()}
239
235
%%
240
 
%% @doc Like <code>lists:mapfoldl/3</code>, but over a list of lists.
 
236
%% @doc Like `lists:mapfoldl/3', but over a list of lists.
241
237
%% The list of lists in the result has the same structure as the given
242
238
%% list of lists.
243
239
 
259
255
%% =====================================================================
260
256
%% @spec variables(syntaxTree()) -> set(atom())
261
257
%%
262
 
%%        set(T) = sets:set(T)
 
258
%%        set(T) = //stdlib/sets:set(T)
263
259
%%
264
260
%% @doc Returns the names of variables occurring in a syntax tree, The
265
261
%% result is a set of variable names represented by atoms. Macro names
266
262
%% are not included.
267
263
%%
268
 
%% @see sets
 
264
%% @see //stdlib/sets
269
265
 
270
266
variables(Tree) ->
271
267
    variables(Tree, sets:new()).
313
309
%% =====================================================================
314
310
%% @spec new_variable_name(Used::set(atom())) -> atom()
315
311
%%
316
 
%% @doc Returns an atom which is not already in the set
317
 
%% <code>Used</code>. This is equivalent to
318
 
%% <code>new_variable_name(Function, Used)</code>, where
319
 
%% <code>Function</code> maps a given integer <code>N</code> to the atom
320
 
%% whose name consists of "<code>V</code>" followed by the numeral for
321
 
%% <code>N</code>.
 
312
%% @doc Returns an atom which is not already in the set `Used'. This is
 
313
%% equivalent to `new_variable_name(Function, Used)', where `Function'
 
314
%% maps a given integer `N' to the atom whose name consists of "`V'"
 
315
%% followed by the numeral for `N'.
322
316
%%
323
317
%% @see new_variable_name/2
324
318
 
331
325
%%          Function = (integer()) -> atom()
332
326
%%
333
327
%% @doc Returns a user-named atom which is not already in the set
334
 
%% <code>Used</code>. The atom is generated by applying the given
335
 
%% <code>Function</code> to a generated integer. Integers are generated
 
328
%% `Used'. The atom is generated by applying the given
 
329
%% `Function' to a generated integer. Integers are generated
336
330
%% using an algorithm which tries to keep the names randomly distributed
337
331
%% within a reasonably small range relative to the number of elements in
338
332
%% the set.
339
333
%%
340
 
%% <p>This function uses the module <code>random</code> to generate new
 
334
%% This function uses the module `random' to generate new
341
335
%% keys. The seed it uses may be initialized by calling
342
 
%% <code>random:seed/0</code> or <code>random:seed/3</code> before this
343
 
%% function is first called.</p>
 
336
%% `random:seed/0' or `random:seed/3' before this
 
337
%% function is first called.
344
338
%%
345
339
%% @see new_variable_name/1
346
 
%% @see sets
347
 
%% @see random
 
340
%% @see //stdlib/sets
 
341
%% @see //stdlib/random
348
342
 
349
343
new_variable_name(F, S) ->
350
344
    R = start_range(S),
389
383
%% =====================================================================
390
384
%% @spec new_variable_names(N::integer(), Used::set(atom())) -> [atom()]
391
385
%%
392
 
%% @doc Like <code>new_variable_name/1</code>, but generates a list of
393
 
%% <code>N</code> new names.
 
386
%% @doc Like `new_variable_name/1', but generates a list of
 
387
%% `N' new names.
394
388
%% 
395
389
%% @see new_variable_name/1
396
390
 
403
397
%%
404
398
%%          Function = (integer()) -> atom()
405
399
%%
406
 
%% @doc Like <code>new_variable_name/2</code>, but generates a list of
407
 
%% <code>N</code> new names.
 
400
%% @doc Like `new_variable_name/2', but generates a list of
 
401
%% `N' new names.
408
402
%% 
409
403
%% @see new_variable_name/2
410
404
 
424
418
%% @spec annotate_bindings(Tree::syntaxTree(),
425
419
%%                         Bindings::ordset(atom())) -> syntaxTree()
426
420
%%
427
 
%%          ordset(T) = ordsets:ordset(T)
 
421
%% @type ordset(T) = //stdlib/ordsets:ordset(T)
428
422
%%
429
423
%% @doc Adds or updates annotations on nodes in a syntax tree.
430
 
%% <code>Bindings</code> specifies the set of bound variables in the
 
424
%% `Bindings' specifies the set of bound variables in the
431
425
%% environment of the top level node. The following annotations are
432
426
%% affected:
433
427
%% <ul>
434
 
%%     <li><code>{env, Vars}</code>, representing the input environment
 
428
%%     <li>`{env, Vars}', representing the input environment
435
429
%%     of the subtree.</li>
436
430
%%
437
 
%%     <li><code>{bound, Vars}</code>, representing the variables that
 
431
%%     <li>`{bound, Vars}', representing the variables that
438
432
%%     are bound in the subtree.</li>
439
433
%%
440
 
%%     <li><code>{free, Vars}</code>, representing the free variables in
 
434
%%     <li>`{free, Vars}', representing the free variables in
441
435
%%     the subtree.</li>
442
436
%% </ul>
443
 
%% <code>Bindings</code> and <code>Vars</code> are ordered-set lists
444
 
%% (cf. module <code>ordsets</code>) of atoms representing variable
 
437
%% `Bindings' and `Vars' are ordered-set lists
 
438
%% (cf. module `ordsets') of atoms representing variable
445
439
%% names.
446
440
%%
447
441
%% @see annotate_bindings/1
448
 
%% @see ordsets
 
442
%% @see //stdlib/ordsets
449
443
 
450
444
annotate_bindings(Tree, Env) ->
451
445
    {Tree1, _, _} = vann(Tree, Env),
455
449
%% @spec annotate_bindings(Tree::syntaxTree()) -> syntaxTree()
456
450
%%
457
451
%% @doc Adds or updates annotations on nodes in a syntax tree.
458
 
%% Equivalent to <code>annotate_bindings(Tree, Bindings)</code> where
459
 
%% the top-level environment <code>Bindings</code> is taken from the
460
 
%% annotation <code>{env, Bindings}</code> on the root node of
461
 
%% <code>Tree</code>. An exception is thrown if no such annotation
 
452
%% Equivalent to `annotate_bindings(Tree, Bindings)' where
 
453
%% the top-level environment `Bindings' is taken from the
 
454
%% annotation `{env, Bindings}' on the root node of
 
455
%% `Tree'. An exception is thrown if no such annotation
462
456
%% should exist.
463
457
%%
464
458
%% @see annotate_bindings/2
791
785
%% =====================================================================
792
786
%% @spec is_fail_expr(Tree::syntaxTree()) -> bool()
793
787
%%
794
 
%% @doc Returns <code>true</code> if <code>Tree</code> represents an
 
788
%% @doc Returns `true' if `Tree' represents an
795
789
%% expression which never terminates normally. Note that the reverse
796
790
%% does not apply. Currently, the detected cases are calls to
797
 
%% <code>exit/1</code>, <code>throw/1</code>,
798
 
%% <code>erlang:fault/1</code> and <code>erlang:fault/2</code>.
 
791
%% `exit/1', `throw/1',
 
792
%% `erlang:fault/1' and `erlang:fault/2'.
799
793
%%
800
 
%% @see erlang:exit/1
801
 
%% @see erlang:throw/1
802
 
%% @see erlang:fault/1
803
 
%% @see erlang:fault/2
 
794
%% @see //kernel/erlang:exit/1
 
795
%% @see //kernel/erlang:throw/1
 
796
%% @see //kernel/erlang:fault/1
 
797
%% @see //kernel/erlang:fault/2
804
798
 
805
799
is_fail_expr(E) ->          
806
800
    case erl_syntax:type(E) of
810
804
            case catch {ok, analyze_function_name(F)} of
811
805
                syntax_error ->
812
806
                    false;
813
 
                {ok, exit} when N == 1 ->
814
 
                    true;
815
 
                {ok, throw} when N == 1 ->
816
 
                    true;
817
 
                {ok, {erlang, exit}} when N == 1 ->
818
 
                    true;
819
 
                {ok, {erlang, throw}} when N == 1 ->
820
 
                    true;
821
 
                {ok, {erlang, error}} when N == 1 ->
822
 
                    true;
823
 
                {ok, {erlang, error}} when N == 2 ->
824
 
                    true;
825
 
                {ok, {erlang, fault}} when N == 1 ->
826
 
                    true;
827
 
                {ok, {erlang, fault}} when N == 2 ->
 
807
                {ok, exit} when N =:= 1 ->
 
808
                    true;
 
809
                {ok, throw} when N =:= 1 ->
 
810
                    true;
 
811
                {ok, {erlang, exit}} when N =:= 1 ->
 
812
                    true;
 
813
                {ok, {erlang, throw}} when N =:= 1 ->
 
814
                    true;
 
815
                {ok, {erlang, error}} when N =:= 1 ->
 
816
                    true;
 
817
                {ok, {erlang, error}} when N =:= 2 ->
 
818
                    true;
 
819
                {ok, {erlang, fault}} when N =:= 1 ->
 
820
                    true;
 
821
                {ok, {erlang, fault}} when N =:= 2 ->
828
822
                    true;
829
823
                _ ->
830
824
                    false
842
836
%%                | module | records | rules | warnings
843
837
%%
844
838
%% @doc Analyzes a sequence of "program forms". The given
845
 
%% <code>Forms</code> may be a single syntax tree of type
846
 
%% <code>form_list</code>, or a list of "program form" syntax trees. The
847
 
%% returned value is a list of pairs <code>{Key, Info}</code>, where
848
 
%% each value of <code>Key</code> occurs at most once in the list; the
 
839
%% `Forms' may be a single syntax tree of type
 
840
%% `form_list', or a list of "program form" syntax trees. The
 
841
%% returned value is a list of pairs `{Key, Info}', where
 
842
%% each value of `Key' occurs at most once in the list; the
849
843
%% absence of a particular key indicates that there is no well-defined
850
844
%% value for that key.
851
845
%%
852
 
%% <p>Each entry in the resulting list contains the following
 
846
%% Each entry in the resulting list contains the following
853
847
%% corresponding information about the program forms:
854
848
%% <dl>
855
 
%%     <dt><code>{attributes, Attributes}</code></dt>
 
849
%%     <dt>`{attributes, Attributes}'</dt>
856
850
%%       <dd><ul>
857
 
%%         <li><code>Attributes = [{atom(), term()}]</code></li>
 
851
%%         <li>`Attributes = [{atom(), term()}]'</li>
858
852
%%       </ul>
859
 
%%       <code>Attributes</code> is a list of pairs representing the
 
853
%%       `Attributes' is a list of pairs representing the
860
854
%%       names and corresponding values of all so-called "wild"
861
 
%%       attributes (as e.g. "<code>-compile(...)</code>") occurring in
862
 
%%       <code>Forms</code> (cf. <code>analyze_wild_attribute/1</code>).
 
855
%%       attributes (as e.g. "`-compile(...)'") occurring in
 
856
%%       `Forms' (cf. `analyze_wild_attribute/1').
863
857
%%       We do not guarantee that each name occurs at most once in the
864
858
%%       list. The order of listing is not defined.</dd>
865
859
%%
866
 
%%     <dt><code>{errors, Errors}</code></dt>
 
860
%%     <dt>`{errors, Errors}'</dt>
867
861
%%       <dd><ul>
868
 
%%         <li><code>Errors = [term()]</code></li>
 
862
%%         <li>`Errors = [term()]'</li>
869
863
%%       </ul>
870
 
%%       <code>Errors</code> is the list of error descriptors of all
871
 
%%       <code>error_marker</code> nodes that occur in
872
 
%%       <code>Forms</code>. The order of listing is not defined.</dd>
 
864
%%       `Errors' is the list of error descriptors of all
 
865
%%       `error_marker' nodes that occur in
 
866
%%       `Forms'. The order of listing is not defined.</dd>
873
867
%%
874
 
%%     <dt><code>{exports, Exports}</code></dt>
 
868
%%     <dt>`{exports, Exports}'</dt>
875
869
%%       <dd><ul>
876
 
%%          <li><code>Exports = [FunctionName]</code></li>
877
 
%%          <li><code>FunctionName = atom()
 
870
%%          <li>`Exports = [FunctionName]'</li>
 
871
%%          <li>`FunctionName = atom()
878
872
%%                    | {atom(), integer()}
879
 
%%                    | {ModuleName, FunctionName}</code></li>
880
 
%%          <li><code>ModuleName = atom()</code></li>
 
873
%%                    | {ModuleName, FunctionName}'</li>
 
874
%%          <li>`ModuleName = atom()'</li>
881
875
%%       </ul>
882
 
%%       <code>Exports</code> is a list of representations of those
 
876
%%       `Exports' is a list of representations of those
883
877
%%       function names that are listed by export declaration attributes
884
 
%%       in <code>Forms</code> (cf.
885
 
%%       <code>analyze_export_attribute/1</code>). We do not guarantee
 
878
%%       in `Forms' (cf.
 
879
%%       `analyze_export_attribute/1'). We do not guarantee
886
880
%%       that each name occurs at most once in the list. The order of
887
881
%%       listing is not defined.</dd>
888
882
%%
889
 
%%     <dt><code>{functions, Functions}</code></dt>
 
883
%%     <dt>`{functions, Functions}'</dt>
890
884
%%       <dd><ul>
891
 
%%          <li><code>Functions = [{atom(), integer()}]</code></li>
 
885
%%          <li>`Functions = [{atom(), integer()}]'</li>
892
886
%%       </ul>
893
 
%%       <code>Functions</code> is a list of the names of the functions
894
 
%%       that are defined in <code>Forms</code> (cf.
895
 
%%       <code>analyze_function/1</code>). We do not guarantee that each
 
887
%%       `Functions' is a list of the names of the functions
 
888
%%       that are defined in `Forms' (cf.
 
889
%%       `analyze_function/1'). We do not guarantee that each
896
890
%%       name occurs at most once in the list. The order of listing is
897
891
%%       not defined.</dd>
898
892
%%
899
 
%%     <dt><code>{imports, Imports}</code></dt>
 
893
%%     <dt>`{imports, Imports}'</dt>
900
894
%%       <dd><ul>
901
 
%%          <li><code>Imports = [{Module, Names}]</code></li>
902
 
%%          <li><code>Module = atom()</code></li>
903
 
%%          <li><code>Names = [FunctionName]</code></li>
904
 
%%          <li><code>FunctionName = atom()
 
895
%%          <li>`Imports = [{Module, Names}]'</li>
 
896
%%          <li>`Module = atom()'</li>
 
897
%%          <li>`Names = [FunctionName]'</li>
 
898
%%          <li>`FunctionName = atom()
905
899
%%                    | {atom(), integer()}
906
 
%%                    | {ModuleName, FunctionName}</code></li>
907
 
%%          <li><code>ModuleName = atom()</code></li>
 
900
%%                    | {ModuleName, FunctionName}'</li>
 
901
%%          <li>`ModuleName = atom()'</li>
908
902
%%       </ul>
909
 
%%       <code>Imports</code> is a list of pairs representing those
 
903
%%       `Imports' is a list of pairs representing those
910
904
%%       module names and corresponding function names that are listed
911
 
%%       by import declaration attributes in <code>Forms</code> (cf.
912
 
%%       <code>analyze_import_attribute/1</code>), where each
913
 
%%       <code>Module</code> occurs at most once in
914
 
%%       <code>Imports</code>. We do not guarantee that each name occurs
 
905
%%       by import declaration attributes in `Forms' (cf.
 
906
%%       `analyze_import_attribute/1'), where each
 
907
%%       `Module' occurs at most once in
 
908
%%       `Imports'. We do not guarantee that each name occurs
915
909
%%       at most once in the lists of function names. The order of
916
910
%%       listing is not defined.</dd>
917
911
%%
918
 
%%     <dt><code>{module, ModuleName}</code></dt>
 
912
%%     <dt>`{module, ModuleName}'</dt>
919
913
%%       <dd><ul>
920
 
%%          <li><code>ModuleName = atom()</code></li>
 
914
%%          <li>`ModuleName = atom()'</li>
921
915
%%       </ul>
922
 
%%       <code>ModuleName</code> is the name declared by a module
923
 
%%       attribute in <code>Forms</code>. If no module name is defined
924
 
%%       in <code>Forms</code>, the result will contain no entry for the
925
 
%%       <code>module</code> key. If multiple module name declarations
 
916
%%       `ModuleName' is the name declared by a module
 
917
%%       attribute in `Forms'. If no module name is defined
 
918
%%       in `Forms', the result will contain no entry for the
 
919
%%       `module' key. If multiple module name declarations
926
920
%%       should occur, all but the first will be ignored.</dd>
927
921
%%
928
 
%%     <dt><code>{records, Records}</code></dt>
 
922
%%     <dt>`{records, Records}'</dt>
929
923
%%       <dd><ul>
930
 
%%          <li><code>Records = [{atom(), Fields}]</code></li>
931
 
%%          <li><code>Fields = [{atom(), Default}]</code></li>
932
 
%%          <li><code>Default = none | syntaxTree()</code></li>
 
924
%%          <li>`Records = [{atom(), Fields}]'</li>
 
925
%%          <li>`Fields = [{atom(), Default}]'</li>
 
926
%%          <li>`Default = none | syntaxTree()'</li>
933
927
%%       </ul>
934
 
%%       <code>Records</code> is a list of pairs representing the names
 
928
%%       `Records' is a list of pairs representing the names
935
929
%%       and corresponding field declarations of all record declaration
936
 
%%       attributes occurring in <code>Forms</code>. For fields declared
 
930
%%       attributes occurring in `Forms'. For fields declared
937
931
%%       without a default value, the corresponding value for
938
 
%%       <code>Default</code> is the atom <code>none</code> (cf.
939
 
%%       <code>analyze_record_attribute/1</code>). We do not guarantee
 
932
%%       `Default' is the atom `none' (cf.
 
933
%%       `analyze_record_attribute/1'). We do not guarantee
940
934
%%       that each record name occurs at most once in the list. The
941
935
%%       order of listing is not defined.</dd>
942
936
%%
943
 
%%     <dt><code>{rules, Rules}</code></dt>
 
937
%%     <dt>`{rules, Rules}'</dt>
944
938
%%       <dd><ul>
945
 
%%          <li><code>Rules = [{atom(), integer()}]</code></li>
 
939
%%          <li>`Rules = [{atom(), integer()}]'</li>
946
940
%%       </ul>
947
 
%%       <code>Rules</code> is a list of the names of the rules that are
948
 
%%       defined in <code>Forms</code> (cf.
949
 
%%       <code>analyze_rule/1</code>). We do not guarantee that each
 
941
%%       `Rules' is a list of the names of the rules that are
 
942
%%       defined in `Forms' (cf.
 
943
%%       `analyze_rule/1'). We do not guarantee that each
950
944
%%       name occurs at most once in the list. The order of listing is
951
945
%%       not defined.</dd>
952
946
%%
953
 
%%     <dt><code>{warnings, Warnings}</code></dt>
 
947
%%     <dt>`{warnings, Warnings}'</dt>
954
948
%%       <dd><ul>
955
 
%%          <li><code>Warnings = [term()]</code></li>
 
949
%%          <li>`Warnings = [term()]'</li>
956
950
%%       </ul>
957
 
%%       <code>Warnings</code> is the list of error descriptors of all
958
 
%%       <code>warning_marker</code> nodes that occur in
959
 
%%       <code>Forms</code>. The order of listing is not defined.</dd>
960
 
%% </dl></p>
 
951
%%       `Warnings' is the list of error descriptors of all
 
952
%%       `warning_marker' nodes that occur in
 
953
%%       `Forms'. The order of listing is not defined.</dd>
 
954
%% </dl>
961
955
%%
962
 
%% <p>The evaluation throws <code>syntax_error</code> if an ill-formed
963
 
%% Erlang construct is encountered.</p>
 
956
%% The evaluation throws `syntax_error' if an ill-formed
 
957
%% Erlang construct is encountered.
964
958
%%
965
959
%% @see analyze_wild_attribute/1
966
960
%% @see analyze_export_attribute/1
1095
1089
%% =====================================================================
1096
1090
%% @spec analyze_form(Node::syntaxTree()) -> {atom(), term()} | atom()
1097
1091
%%
1098
 
%% @doc Analyzes a "source code form" node. If <code>Node</code> is a
1099
 
%% "form" type (cf. <code>erl_syntax:is_form/1</code>), the returned
1100
 
%% value is a tuple <code>{Type, Info}</code> where <code>Type</code> is
1101
 
%% the node type and <code>Info</code> depends on <code>Type</code>, as
 
1092
%% @doc Analyzes a "source code form" node. If `Node' is a
 
1093
%% "form" type (cf. `erl_syntax:is_form/1'), the returned
 
1094
%% value is a tuple `{Type, Info}' where `Type' is
 
1095
%% the node type and `Info' depends on `Type', as
1102
1096
%% follows:
1103
1097
%% <dl>
1104
 
%%   <dt><code>{attribute, Info}</code></dt>
1105
 
%%
1106
 
%%      <dd>where <code>Info = analyze_attribute(Node)</code>.</dd>
1107
 
%%
1108
 
%%   <dt><code>{error_marker, Info}</code></dt>
1109
 
%%
1110
 
%%      <dd>where <code>Info =
1111
 
%%      erl_syntax:error_marker_info(Node)</code>.</dd>
1112
 
%%
1113
 
%%   <dt><code>{function, Info}</code></dt>
1114
 
%%
1115
 
%%          <dd>where <code>Info = analyze_function(Node)</code>.</dd>
1116
 
%%
1117
 
%%   <dt><code>{rule, Info}</code></dt>
1118
 
%%
1119
 
%%          <dd>where <code>Info = analyze_rule(Node)</code>.</dd>
1120
 
%%
1121
 
%%   <dt><code>{warning_marker, Info}</code></dt>
1122
 
%%
1123
 
%%          <dd>where <code>Info =
1124
 
%%          erl_syntax:warning_marker_info(Node)</code>.</dd>
 
1098
%%   <dt>`{attribute, Info}'</dt>
 
1099
%%
 
1100
%%      <dd>where `Info = analyze_attribute(Node)'.</dd>
 
1101
%%
 
1102
%%   <dt>`{error_marker, Info}'</dt>
 
1103
%%
 
1104
%%      <dd>where `Info =
 
1105
%%      erl_syntax:error_marker_info(Node)'.</dd>
 
1106
%%
 
1107
%%   <dt>`{function, Info}'</dt>
 
1108
%%
 
1109
%%          <dd>where `Info = analyze_function(Node)'.</dd>
 
1110
%%
 
1111
%%   <dt>`{rule, Info}'</dt>
 
1112
%%
 
1113
%%          <dd>where `Info = analyze_rule(Node)'.</dd>
 
1114
%%
 
1115
%%   <dt>`{warning_marker, Info}'</dt>
 
1116
%%
 
1117
%%          <dd>where `Info =
 
1118
%%          erl_syntax:warning_marker_info(Node)'.</dd>
1125
1119
%% </dl>
1126
1120
%% For other types of forms, only the node type is returned.
1127
1121
%%
1128
 
%% <p>The evaluation throws <code>syntax_error</code> if
1129
 
%% <code>Node</code> is not well-formed.</p>
 
1122
%% The evaluation throws `syntax_error' if
 
1123
%% `Node' is not well-formed.
1130
1124
%%
1131
1125
%% @see analyze_attribute/1
1132
1126
%% @see analyze_function/1
1160
1154
%% @spec analyze_attribute(Node::syntaxTree()) ->
1161
1155
%%           preprocessor | {atom(), atom()}
1162
1156
%%
1163
 
%% @doc Analyzes an attribute node. If <code>Node</code> represents a
1164
 
%% preprocessor directive, the atom <code>preprocessor</code> is
1165
 
%% returned. Otherwise, if <code>Node</code> represents a module
1166
 
%% attribute "<code>-<em>Name</em>...</code>", a tuple <code>{Name,
1167
 
%% Info}</code> is returned, where <code>Info</code> depends on
1168
 
%% <code>Name</code>, as follows:
 
1157
%% @doc Analyzes an attribute node. If `Node' represents a
 
1158
%% preprocessor directive, the atom `preprocessor' is
 
1159
%% returned. Otherwise, if `Node' represents a module
 
1160
%% attribute "`-<em>Name</em>...'", a tuple `{Name,
 
1161
%% Info}' is returned, where `Info' depends on
 
1162
%% `Name', as follows:
1169
1163
%% <dl>
1170
 
%%     <dt><code>{module, Info}</code></dt>
1171
 
%%
1172
 
%%          <dd>where <code>Info =
1173
 
%%          analyze_module_attribute(Node)</code>.</dd>
1174
 
%%
1175
 
%%     <dt><code>{export, Info}</code></dt>
1176
 
%%
1177
 
%%          <dd>where <code>Info =
1178
 
%%          analyze_export_attribute(Node)</code>.</dd>
1179
 
%%
1180
 
%%     <dt><code>{import, Info}</code></dt>
1181
 
%%
1182
 
%%          <dd>where <code>Info =
1183
 
%%          analyze_import_attribute(Node)</code>.</dd>
1184
 
%%
1185
 
%%     <dt><code>{file, Info}</code></dt>
1186
 
%%
1187
 
%%          <dd>where <code>Info =
1188
 
%%          analyze_file_attribute(Node)</code>.</dd>
1189
 
%%
1190
 
%%     <dt><code>{record, Info}</code></dt>
1191
 
%%
1192
 
%%          <dd>where <code>Info =
1193
 
%%          analyze_record_attribute(Node)</code>.</dd>
1194
 
%%
1195
 
%%     <dt><code>{Name, Info}</code></dt>
1196
 
%%
1197
 
%%          <dd>where <code>{Name, Info} =
1198
 
%%          analyze_wild_attribute(Node)</code>.</dd>
 
1164
%%     <dt>`{module, Info}'</dt>
 
1165
%%
 
1166
%%          <dd>where `Info =
 
1167
%%          analyze_module_attribute(Node)'.</dd>
 
1168
%%
 
1169
%%     <dt>`{export, Info}'</dt>
 
1170
%%
 
1171
%%          <dd>where `Info =
 
1172
%%          analyze_export_attribute(Node)'.</dd>
 
1173
%%
 
1174
%%     <dt>`{import, Info}'</dt>
 
1175
%%
 
1176
%%          <dd>where `Info =
 
1177
%%          analyze_import_attribute(Node)'.</dd>
 
1178
%%
 
1179
%%     <dt>`{file, Info}'</dt>
 
1180
%%
 
1181
%%          <dd>where `Info =
 
1182
%%          analyze_file_attribute(Node)'.</dd>
 
1183
%%
 
1184
%%     <dt>`{record, Info}'</dt>
 
1185
%%
 
1186
%%          <dd>where `Info =
 
1187
%%          analyze_record_attribute(Node)'.</dd>
 
1188
%%
 
1189
%%     <dt>`{Name, Info}'</dt>
 
1190
%%
 
1191
%%          <dd>where `{Name, Info} =
 
1192
%%          analyze_wild_attribute(Node)'.</dd>
1199
1193
%% </dl>
1200
 
%% The evaluation throws <code>syntax_error</code> if <code>Node</code>
 
1194
%% The evaluation throws `syntax_error' if `Node'
1201
1195
%% does not represent a well-formed module attribute.
1202
1196
%%
1203
1197
%% @see analyze_module_attribute/1
1249
1243
%%
1250
1244
%% @doc Returns the module name declared by a module attribute.
1251
1245
%%
1252
 
%% <p>The evaluation throws <code>syntax_error</code> if
1253
 
%% <code>Node</code> does not represent a well-formed module
1254
 
%% attribute.</p>
 
1246
%% The evaluation throws `syntax_error' if
 
1247
%% `Node' does not represent a well-formed module
 
1248
%% attribute.
1255
1249
%%
1256
1250
%% @see analyze_attribute/1
1257
1251
 
1293
1287
%% attribute. We do not guarantee that each name occurs at most once in
1294
1288
%% the list. The order of listing is not defined.
1295
1289
%%
1296
 
%% <p>The evaluation throws <code>syntax_error</code> if
1297
 
%% <code>Node</code> does not represent a well-formed export
1298
 
%% attribute.</p>
 
1290
%% The evaluation throws `syntax_error' if
 
1291
%% `Node' does not represent a well-formed export
 
1292
%% attribute.
1299
1293
%%
1300
1294
%% @see analyze_attribute/1
1301
1295
 
1330
1324
%%          ModuleName = atom()
1331
1325
%%
1332
1326
%% @doc Returns the function name represented by a syntax tree. If
1333
 
%% <code>Node</code> represents a function name, such as
1334
 
%% "<code>foo/1</code>" or "<code>bloggs:fred/2</code>", a uniform
 
1327
%% `Node' represents a function name, such as
 
1328
%% "`foo/1'" or "`bloggs:fred/2'", a uniform
1335
1329
%% representation of that name is returned. Different nestings of arity
1336
1330
%% and module name qualifiers in the syntax tree does not affect the
1337
1331
%% result.
1338
1332
%%
1339
 
%% <p>The evaluation throws <code>syntax_error</code> if
1340
 
%% <code>Node</code> does not represent a well-formed function name.</p>
 
1333
%% The evaluation throws `syntax_error' if
 
1334
%% `Node' does not represent a well-formed function name.
1341
1335
 
1342
1336
analyze_function_name(Node) ->
1343
1337
    case erl_syntax:type(Node) of
1387
1381
%%
1388
1382
%% @doc Returns the module name and (if present) list of function names
1389
1383
%% declared by an import attribute. The returned value is an atom
1390
 
%% <code>Module</code> or a pair <code>{Module, Names}</code>, where
1391
 
%% <code>Names</code> is a list of function names declared as imported
1392
 
%% from the module named by <code>Module</code>. We do not guarantee
1393
 
%% that each name occurs at most once in <code>Names</code>. The order
 
1384
%% `Module' or a pair `{Module, Names}', where
 
1385
%% `Names' is a list of function names declared as imported
 
1386
%% from the module named by `Module'. We do not guarantee
 
1387
%% that each name occurs at most once in `Names'. The order
1394
1388
%% of listing is not defined.
1395
1389
%%
1396
 
%% <p>The evaluation throws <code>syntax_error</code> if
1397
 
%% <code>Node</code> does not represent a well-formed import
1398
 
%% attribute.</p>
 
1390
%% The evaluation throws `syntax_error' if
 
1391
%% `Node' does not represent a well-formed import
 
1392
%% attribute.
1399
1393
%%
1400
1394
%% @see analyze_attribute/1
1401
1395
 
1421
1415
%% @spec analyze_wild_attribute(Node::syntaxTree()) -> {atom(), term()}
1422
1416
%%
1423
1417
%% @doc Returns the name and value of a "wild" attribute. The result is
1424
 
%% the pair <code>{Name, Value}</code>, if <code>Node</code> represents
1425
 
%% "<code>-Name(Value)</code>".
1426
 
%%
1427
 
%% <p>Note that no checking is done whether <code>Name</code> is a
1428
 
%% reserved attribute name such as <code>module</code> or
1429
 
%% <code>export</code>: it is assumed that the attribute is "wild".</p>
1430
 
%%
1431
 
%% <p>The evaluation throws <code>syntax_error</code> if
1432
 
%% <code>Node</code> does not represent a well-formed wild
1433
 
%% attribute.</p>
 
1418
%% the pair `{Name, Value}', if `Node' represents
 
1419
%% "`-Name(Value)'".
 
1420
%%
 
1421
%% Note that no checking is done whether `Name' is a
 
1422
%% reserved attribute name such as `module' or
 
1423
%% `export': it is assumed that the attribute is "wild".
 
1424
%%
 
1425
%% The evaluation throws `syntax_error' if
 
1426
%% `Node' does not represent a well-formed wild
 
1427
%% attribute.
1434
1428
%%
1435
1429
%% @see analyze_attribute/1
1436
1430
 
1462
1456
%%          Fields = [{atom(), none | syntaxTree()}]
1463
1457
%%
1464
1458
%% @doc Returns the name and the list of fields of a record declaration
1465
 
%% attribute. The result is a pair <code>{Name, Fields}</code>, if
1466
 
%% <code>Node</code> represents "<code>-record(Name, {...}).</code>",
1467
 
%% where <code>Fields</code> is a list of pairs <code>{Label,
1468
 
%% Default}</code> for each field "<code>Label</code>" or "<code>Label =
1469
 
%% <em>Default</em></code>" in the declaration, listed in left-to-right
 
1459
%% attribute. The result is a pair `{Name, Fields}', if
 
1460
%% `Node' represents "`-record(Name, {...}).'",
 
1461
%% where `Fields' is a list of pairs `{Label,
 
1462
%% Default}' for each field "`Label'" or "`Label =
 
1463
%% <em>Default</em>'" in the declaration, listed in left-to-right
1470
1464
%% order. If the field has no default-value declaration, the value for
1471
 
%% <code>Default</code> will be the atom <code>none</code>. We do not
 
1465
%% `Default' will be the atom `none'. We do not
1472
1466
%% guarantee that each label occurs at most one in the list.
1473
1467
%%
1474
 
%% <p>The evaluation throws <code>syntax_error</code> if
1475
 
%% <code>Node</code> does not represent a well-formed record declaration
1476
 
%% attribute.</p>
 
1468
%% The evaluation throws `syntax_error' if
 
1469
%% `Node' does not represent a well-formed record declaration
 
1470
%% attribute.
1477
1471
%%
1478
1472
%% @see analyze_attribute/1
1479
1473
%% @see analyze_record_field/1
1515
1509
%%    Value = none | syntaxTree()
1516
1510
%%
1517
1511
%% @doc Returns the record name and field name/names of a record
1518
 
%% expression. If <code>Node</code> has type <code>record_expr</code>,
1519
 
%% <code>record_index_expr</code> or <code>record_access</code>, a pair
1520
 
%% <code>{Type, Info}</code> is returned, otherwise an atom
1521
 
%% <code>Type</code> is returned. <code>Type</code> is the node type of
1522
 
%% <code>Node</code>, and <code>Info</code> depends on
1523
 
%% <code>Type</code>, as follows:
 
1512
%% expression. If `Node' has type `record_expr',
 
1513
%% `record_index_expr' or `record_access', a pair
 
1514
%% `{Type, Info}' is returned, otherwise an atom
 
1515
%% `Type' is returned. `Type' is the node type of
 
1516
%% `Node', and `Info' depends on
 
1517
%% `Type', as follows:
1524
1518
%% <dl>
1525
 
%%   <dt><code>record_expr</code>:</dt>
1526
 
%%     <dd><code>{atom(), [{atom(), Value}]}</code></dd>
1527
 
%%   <dt><code>record_access</code>:</dt>
1528
 
%%     <dd><code>{atom(), atom()} | atom()</code></dd>
1529
 
%%   <dt><code>record_index_expr</code>:</dt>
1530
 
%%     <dd><code>{atom(), atom()}</code></dd>
 
1519
%%   <dt>`record_expr':</dt>
 
1520
%%     <dd>`{atom(), [{atom(), Value}]}'</dd>
 
1521
%%   <dt>`record_access':</dt>
 
1522
%%     <dd>`{atom(), atom()} | atom()'</dd>
 
1523
%%   <dt>`record_index_expr':</dt>
 
1524
%%     <dd>`{atom(), atom()}'</dd>
1531
1525
%% </dl>
1532
1526
%%
1533
 
%% <p>For a <code>record_expr</code> node, <code>Info</code> represents
 
1527
%% For a `record_expr' node, `Info' represents
1534
1528
%% the record name and the list of descriptors for the involved fields,
1535
1529
%% listed in the order they appear. (See
1536
 
%% <code>analyze_record_field/1</code> for details on the field
1537
 
%% descriptors). For a <code>record_access</code> node,
1538
 
%% <code>Info</code> represents the record name and the field name (or
 
1530
%% `analyze_record_field/1' for details on the field
 
1531
%% descriptors). For a `record_access' node,
 
1532
%% `Info' represents the record name and the field name (or
1539
1533
%% if the record name is not included, only the field name; this is
1540
1534
%% allowed only in Mnemosyne-query syntax). For a
1541
 
%% <code>record_index_expr</code> node, <code>Info</code> represents the
1542
 
%% record name and the name field name.</p>
 
1535
%% `record_index_expr' node, `Info' represents the
 
1536
%% record name and the name field name.
1543
1537
%%
1544
 
%% <p>The evaluation throws <code>syntax_error</code> if
1545
 
%% <code>Node</code> represents a record expression that is not
1546
 
%% well-formed.</p>
 
1538
%% The evaluation throws `syntax_error' if
 
1539
%% `Node' represents a record expression that is not
 
1540
%% well-formed.
1547
1541
%%
1548
1542
%% @see analyze_record_attribute/1
1549
1543
%% @see analyze_record_field/1
1606
1600
%%          Value = none | syntaxTree()
1607
1601
%%
1608
1602
%% @doc Returns the label and value-expression of a record field
1609
 
%% specifier. The result is a pair <code>{Label, Value}</code>, if
1610
 
%% <code>Node</code> represents "<code>Label = <em>Value</em></code>" or
1611
 
%% "<code>Label</code>", where in the first case, <code>Value</code> is
1612
 
%% a syntax tree, and in the second case <code>Value</code> is
1613
 
%% <code>none</code>.
 
1603
%% specifier. The result is a pair `{Label, Value}', if
 
1604
%% `Node' represents "`Label = <em>Value</em>'" or
 
1605
%% "`Label'", where in the first case, `Value' is
 
1606
%% a syntax tree, and in the second case `Value' is
 
1607
%% `none'.
1614
1608
%%
1615
 
%% <p>The evaluation throws <code>syntax_error</code> if
1616
 
%% <code>Node</code> does not represent a well-formed record field
1617
 
%% specifier.</p>
 
1609
%% The evaluation throws `syntax_error' if
 
1610
%% `Node' does not represent a well-formed record field
 
1611
%% specifier.
1618
1612
%%
1619
1613
%% @see analyze_record_attribute/1
1620
1614
%% @see analyze_record_expr/1
1639
1633
%% @spec analyze_file_attribute(Node::syntaxTree()) ->
1640
1634
%%           {string(), integer()}
1641
1635
%%
1642
 
%% @doc Returns the file name and line number of a <code>file</code>
1643
 
%% attribute. The result is the pair <code>{File, Line}</code> if
1644
 
%% <code>Node</code> represents "<code>-file(File, Line).</code>".
 
1636
%% @doc Returns the file name and line number of a `file'
 
1637
%% attribute. The result is the pair `{File, Line}' if
 
1638
%% `Node' represents "`-file(File, Line).'".
1645
1639
%%
1646
 
%% <p>The evaluation throws <code>syntax_error</code> if
1647
 
%% <code>Node</code> does not represent a well-formed <code>file</code>
1648
 
%% attribute.</p>
 
1640
%% The evaluation throws `syntax_error' if
 
1641
%% `Node' does not represent a well-formed `file'
 
1642
%% attribute.
1649
1643
%%
1650
1644
%% @see analyze_attribute/1
1651
1645
 
1654
1648
        attribute ->
1655
1649
            case erl_syntax:attribute_arguments(Node) of
1656
1650
                [F, N] ->
1657
 
                    case (erl_syntax:type(F) == string)
1658
 
                        and (erl_syntax:type(N) == integer) of
 
1651
                    case (erl_syntax:type(F) =:= string)
 
1652
                        and (erl_syntax:type(N) =:= integer) of
1659
1653
                        true ->
1660
1654
                            {erl_syntax:string_value(F),
1661
1655
                             erl_syntax:integer_value(N)};
1674
1668
%% @spec analyze_function(Node::syntaxTree()) -> {atom(), integer()}
1675
1669
%%
1676
1670
%% @doc Returns the name and arity of a function definition. The result
1677
 
%% is a pair <code>{Name, A}</code> if <code>Node</code> represents a
1678
 
%% function definition "<code>Name(<em>P_1</em>, ..., <em>P_A</em>) ->
1679
 
%% ...</code>".
 
1671
%% is a pair `{Name, A}' if `Node' represents a
 
1672
%% function definition "`Name(<em>P_1</em>, ..., <em>P_A</em>) ->
 
1673
%% ...'".
1680
1674
%%
1681
 
%% <p>The evaluation throws <code>syntax_error</code> if
1682
 
%% <code>Node</code> does not represent a well-formed function
1683
 
%% definition.</p>
 
1675
%% The evaluation throws `syntax_error' if
 
1676
%% `Node' does not represent a well-formed function
 
1677
%% definition.
1684
1678
%%
1685
1679
%% @see analyze_rule/1
1686
1680
 
1704
1698
%% @spec analyze_rule(Node::syntaxTree()) -> {atom(), integer()}
1705
1699
%%
1706
1700
%% @doc Returns the name and arity of a Mnemosyne rule. The result is a
1707
 
%% pair <code>{Name, A}</code> if <code>Node</code> represents a rule
1708
 
%% "<code>Name(<em>P_1</em>, ..., <em>P_A</em>) :- ...</code>".
 
1701
%% pair `{Name, A}' if `Node' represents a rule
 
1702
%% "`Name(<em>P_1</em>, ..., <em>P_A</em>) :- ...'".
1709
1703
%%
1710
 
%% <p>The evaluation throws <code>syntax_error</code> if
1711
 
%% <code>Node</code> does not represent a well-formed Mnemosyne
1712
 
%% rule.</p>
 
1704
%% The evaluation throws `syntax_error' if
 
1705
%% `Node' does not represent a well-formed Mnemosyne
 
1706
%% rule.
1713
1707
%%
1714
1708
%% @see analyze_function/1
1715
1709
 
1736
1730
%%                       | {ModuleName, FunctionName}
1737
1731
%%          ModuleName = atom()
1738
1732
%%      
1739
 
%% @doc Returns the name of an implicit fun expression "<code>fun
1740
 
%% <em>F</em></code>". The result is a representation of the function
1741
 
%% name <code>F</code>. (Cf. <code>analyze_function_name/1</code>.)
 
1733
%% @doc Returns the name of an implicit fun expression "`fun
 
1734
%% <em>F</em>'". The result is a representation of the function
 
1735
%% name `F'. (Cf. `analyze_function_name/1'.)
1742
1736
%%
1743
 
%% <p>The evaluation throws <code>syntax_error</code> if
1744
 
%% <code>Node</code> does not represent a well-formed implicit fun.</p>
 
1737
%% The evaluation throws `syntax_error' if
 
1738
%% `Node' does not represent a well-formed implicit fun.
1745
1739
%%
1746
1740
%% @see analyze_function_name/1
1747
1741
 
1764
1758
%%          ModuleName = atom()
1765
1759
%%
1766
1760
%% @doc Returns the name of a called function. The result is a
1767
 
%% representation of the name of the applied function <code>F/A</code>,
1768
 
%% if <code>Node</code> represents a function application
1769
 
%% "<code><em>F</em>(<em>X_1</em>, ..., <em>X_A</em>)</code>". If the
1770
 
%% function is not explicitly named (i.e., <code>F</code> is given by
1771
 
%% some expression), only the arity <code>A</code> is returned.
 
1761
%% representation of the name of the applied function `F/A',
 
1762
%% if `Node' represents a function application
 
1763
%% "`<em>F</em>(<em>X_1</em>, ..., <em>X_A</em>)'". If the
 
1764
%% function is not explicitly named (i.e., `F' is given by
 
1765
%% some expression), only the arity `A' is returned.
1772
1766
%%
1773
 
%% <p>The evaluation throws <code>syntax_error</code> if
1774
 
%% <code>Node</code> does not represent a well-formed application
1775
 
%% expression.</p>
 
1767
%% The evaluation throws `syntax_error' if
 
1768
%% `Node' does not represent a well-formed application
 
1769
%% expression.
1776
1770
%%
1777
1771
%% @see analyze_function_name/1
1778
1772
 
1802
1796
%%
1803
1797
%% @doc Creates a mapping from corresponding short names to full
1804
1798
%% function names. Names are represented by nested tuples of atoms and
1805
 
%% integers (cf. <code>analyze_function_name/1</code>). The result is a
1806
 
%% list containing a pair <code>{ShortName, Name}</code> for each
1807
 
%% element <code>Name</code> in the given list, where the corresponding
1808
 
%% <code>ShortName</code> is the rightmost-innermost part of
1809
 
%% <code>Name</code>. The list thus represents a finite mapping from
 
1799
%% integers (cf. `analyze_function_name/1'). The result is a
 
1800
%% list containing a pair `{ShortName, Name}' for each
 
1801
%% element `Name' in the given list, where the corresponding
 
1802
%% `ShortName' is the rightmost-innermost part of
 
1803
%% `Name'. The list thus represents a finite mapping from
1810
1804
%% unqualified names to the corresponding qualified names.
1811
1805
%%
1812
 
%% <p>Note: the resulting list can contain more than one tuple
1813
 
%% <code>{ShortName, Name}</code> for the same <code>ShortName</code>,
1814
 
%% possibly with different values for <code>Name</code>, depending on
1815
 
%% the given list.</p>
 
1806
%% Note: the resulting list can contain more than one tuple
 
1807
%% `{ShortName, Name}' for the same `ShortName',
 
1808
%% possibly with different values for `Name', depending on
 
1809
%% the given list.
1816
1810
%%
1817
1811
%% @see analyze_function_name/1
1818
1812
 
1868
1862
%% @spec to_comment(Tree::syntaxTree(), Prefix::string()) ->
1869
1863
%%           syntaxTree()
1870
1864
%%
1871
 
%% @doc Equivalent to <code>to_comment(Tree, Prefix, F)</code> for a
1872
 
%% default formatting function <code>F</code>. The default
1873
 
%% <code>F</code> simply calls <code>erl_prettypr:format/1</code>.
 
1865
%% @doc Equivalent to `to_comment(Tree, Prefix, F)' for a
 
1866
%% default formatting function `F'. The default
 
1867
%% `F' simply calls `erl_prettypr:format/1'.
1874
1868
%%
1875
1869
%% @see to_comment/3
1876
1870
%% @see erl_prettypr:format/1
1886
1880
%%          Printer = (syntaxTree()) -> string()
1887
1881
%%
1888
1882
%% @doc Transforms a syntax tree into an abstract comment. The lines of
1889
 
%% the comment contain the text for <code>Node</code>, as produced by
1890
 
%% the given <code>Printer</code> function. Each line of the comment is
1891
 
%% prefixed by the string <code>Prefix</code> (this does not include the
1892
 
%% initial "<code>%</code>" character of the comment line).
 
1883
%% the comment contain the text for `Node', as produced by
 
1884
%% the given `Printer' function. Each line of the comment is
 
1885
%% prefixed by the string `Prefix' (this does not include the
 
1886
%% initial "`%'" character of the comment line).
1893
1887
%%
1894
 
%% <p>For example, the result of
1895
 
%% <code>to_comment(erl_syntax:abstract([a,b,c]))</code> represents
 
1888
%% For example, the result of
 
1889
%% `to_comment(erl_syntax:abstract([a,b,c]))' represents
1896
1890
%% <pre>
1897
1891
%%         %% [a,b,c]</pre>
1898
 
%% (cf. <code>to_comment/1</code>).</p>
 
1892
%% (cf. `to_comment/1').
1899
1893
%%
1900
 
%% <p>Note: the text returned by the formatting function will be split
 
1894
%% Note: the text returned by the formatting function will be split
1901
1895
%% automatically into separate comment lines at each line break. No
1902
 
%% extra work is needed.</p>
 
1896
%% extra work is needed.
1903
1897
%%
1904
1898
%% @see to_comment/1
1905
1899
%% @see to_comment/2
1911
1905
%% =====================================================================
1912
1906
%% @spec limit(Tree, Depth) -> syntaxTree()
1913
1907
%%
1914
 
%% @doc Equivalent to <code>limit(Tree, Depth, Text)</code> using the
1915
 
%% text <code>"..."</code> as default replacement.
 
1908
%% @doc Equivalent to `limit(Tree, Depth, Text)' using the
 
1909
%% text `"..."' as default replacement.
1916
1910
%%
1917
1911
%% @see limit/3
1918
1912
%% @see erl_syntax:text/1
1925
1919
%%             Node::syntaxTree()) -> syntaxTree()
1926
1920
%%
1927
1921
%% @doc Limits a syntax tree to a specified depth. Replaces all non-leaf
1928
 
%% subtrees in <code>Tree</code> at the given <code>Depth</code> by
1929
 
%% <code>Node</code>. If <code>Depth</code> is negative, the result is
1930
 
%% always <code>Node</code>, even if <code>Tree</code> has no subtrees.
 
1922
%% subtrees in `Tree' at the given `Depth' by
 
1923
%% `Node'. If `Depth' is negative, the result is
 
1924
%% always `Node', even if `Tree' has no subtrees.
1931
1925
%%
1932
 
%% <p>When a group of subtrees (as e.g., the argument list of an
1933
 
%% <code>application</code> node) is at the specified depth, and there
 
1926
%% When a group of subtrees (as e.g., the argument list of an
 
1927
%% `application' node) is at the specified depth, and there
1934
1928
%% are two or more subtrees in the group, these will be collectively
1935
 
%% replaced by <code>Node</code> even if they are leaf nodes. Groups of
 
1929
%% replaced by `Node' even if they are leaf nodes. Groups of
1936
1930
%% subtrees that are above the specified depth will be limited in size,
1937
1931
%% as if each subsequent tree in the group were one level deeper than
1938
 
%% the previous. E.g., if <code>Tree</code> represents a list of
1939
 
%% integers "<code>[1, 2, 3, 4, 5, 6, 7, 8, 9, 10]</code>", the result
1940
 
%% of <code>limit(Tree, 5)</code> will represent <code>[1, 2, 3, 4,
1941
 
%% ...]</code>.</p>
 
1932
%% the previous. E.g., if `Tree' represents a list of
 
1933
%% integers "`[1, 2, 3, 4, 5, 6, 7, 8, 9, 10]'", the result
 
1934
%% of `limit(Tree, 5)' will represent `[1, 2, 3, 4,
 
1935
%% ...]'.
1942
1936
%%
1943
 
%% <p>The resulting syntax tree is typically only useful for
1944
 
%% pretty-printing or similar visual formatting.</p>
 
1937
%% The resulting syntax tree is typically only useful for
 
1938
%% pretty-printing or similar visual formatting.
1945
1939
%%
1946
1940
%% @see limit/2
1947
1941
 
1972
1966
                    rewrite(Tree,
1973
1967
                            erl_syntax:make_tree(erl_syntax:type(Tree),
1974
1968
                                                 Gs1));
1975
 
               Depth == 0 ->
 
1969
               Depth =:= 0 ->
1976
1970
                    %% Depth is zero, and this is not a leaf node
1977
1971
                    %% so we always replace it.
1978
1972
                    Node;