1erl_syntax_lib(3)          Erlang Module Definition          erl_syntax_lib(3)
2
3
4

NAME

6       erl_syntax_lib - Support library for abstract Erlang syntax trees.
7

DESCRIPTION

9       Support library for abstract Erlang syntax trees.
10
11       This  module  contains  utility functions for working with the abstract
12       data type defined in the module erl_syntax.
13

DATA TYPES

15         appFunName() = {atom(), arity()} | {atom(), {atom(), arity()}}:
16
17
18         field() = {atom(), {field_default(), field_type()}}:
19
20
21         field_default() = none | erl_syntax:syntaxTree():
22
23
24         field_type() = none | erl_syntax:syntaxTree():
25
26
27         fields() = [field()]:
28
29
30         functionN() = atom() | {atom(), arity()}:
31
32
33         functionName() = functionN() | {atom(), functionN()}:
34
35
36         info() = {atom(),  [{atom(),  erl_syntax:syntaxTree()}]}  |  {atom(),
37         atom()} | atom():
38
39
40         info_pair() = {key(), term()}:
41
42
43         key()  = attributes | errors | exports | functions | imports | module
44         | records | warnings:
45
46
47         name() = shortname() | {atom(), shortname()}:
48
49
50         ordset(T) = ordsets:ordset(T):
51
52
53         set(T) = sets:set(T):
54
55
56         shortname() = atom() | {atom(), arity()}:
57
58
59         syntaxTree() = erl_syntax:syntaxTree():
60
61
62           An abstract syntax tree. See the erl_syntax module for details.
63
64         typeName() = atom() | {module(), {atom(), arity()}}  |  {atom(),  ar‐
65         ity()}:
66
67

EXPORTS

69       analyze_application(Node::erl_syntax:syntaxTree())  ->  appFunName()  |
70       arity()
71
72              Returns the name of a called function. The result is a represen‐
73              tation  of  the name of the applied function F/A, if Node repre‐
74              sents a function application "F(X_1, ..., X_A)". If the function
75              is  not  explicitly named (i.e., F is given by some expression),
76              only the arity A is returned.
77
78              The evaluation throws syntax_error if Node does not represent  a
79              well-formed application expression.
80
81              See also: analyze_function_name/1.
82
83       analyze_attribute(Node::erl_syntax:syntaxTree())   ->   preprocessor  |
84       {atom(), term()}
85
86              Analyzes an attribute node. If Node  represents  a  preprocessor
87              directive, the atom preprocessor is returned. Otherwise, if Node
88              represents a module attribute "-Name...", a tuple  {Name,  Info}
89              is returned, where Info depends on Name, as follows:
90
91                {module, Info}:
92                  where Info = analyze_module_attribute(Node).
93
94                {export, Info}:
95                  where Info = analyze_export_attribute(Node).
96
97                {import, Info}:
98                  where Info = analyze_import_attribute(Node).
99
100                {file, Info}:
101                  where Info = analyze_file_attribute(Node).
102
103                {record, Info}:
104                  where Info = analyze_record_attribute(Node).
105
106                {Name, Info}:
107                  where {Name, Info} = analyze_wild_attribute(Node).
108
109              The  evaluation throws syntax_error if Node does not represent a
110              well-formed module attribute.
111
112              See also: analyze_export_attribute/1,  analyze_file_attribute/1,
113              analyze_import_attribute/1,   analyze_module_attribute/1,   ana‐
114              lyze_record_attribute/1, analyze_wild_attribute/1.
115
116       analyze_export_attribute(Node::erl_syntax:syntaxTree())  ->  [function‐
117       Name()]
118
119              Returns  the list of function names declared by an export attri‐
120              bute. We do not guarantee that each name occurs at most once  in
121              the list. The order of listing is not defined.
122
123              The  evaluation throws syntax_error if Node does not represent a
124              well-formed export attribute.
125
126              See also: analyze_attribute/1.
127
128       analyze_file_attribute(Node::erl_syntax:syntaxTree()) -> {string(), in‐
129       teger()}
130
131              Returns  the  file name and line number of a file attribute. The
132              result is the pair {File, Line} if Node represents  "-file(File,
133              Line).".
134
135              The  evaluation throws syntax_error if Node does not represent a
136              well-formed file attribute.
137
138              See also: analyze_attribute/1.
139
140       analyze_form(Node::erl_syntax:syntaxTree())  ->  {atom(),   term()}   |
141       atom()
142
143              Analyzes  a  "source  code  form" node. If Node is a "form" type
144              (cf. erl_syntax:is_form/1), the returned value is a tuple {Type,
145              Info}  where  Type is the node type and Info depends on Type, as
146              follows:
147
148                {attribute, Info}:
149                  where Info = analyze_attribute(Node).
150
151                {error_marker, Info}:
152                  where Info = erl_syntax:error_marker_info(Node).
153
154                {function, Info}:
155                  where Info = analyze_function(Node).
156
157                {warning_marker, Info}:
158                  where Info = erl_syntax:warning_marker_info(Node).
159
160              For other types of forms, only the node type is returned.
161
162              The evaluation throws syntax_error if Node is not well-formed.
163
164              See  also:  analyze_attribute/1,  analyze_function/1,   erl_syn‐
165              tax:error_marker_info/1,  erl_syntax:is_form/1, erl_syntax:warn‐
166              ing_marker_info/1.
167
168       analyze_forms(Forms::erl_syntax:forms()) -> [info_pair()]
169
170              Analyzes a sequence of "program forms". The given Forms may be a
171              single  syntax  tree  of  type  form_list, or a list of "program
172              form" syntax trees. The returned value is a list of pairs  {Key,
173              Info},  where each value of Key occurs at most once in the list;
174              the absence of a particular key indicates that there is no well-
175              defined value for that key.
176
177              Each  entry  in the resulting list contains the following corre‐
178              sponding information about the program forms:
179
180                {attributes, Attributes}:
181
182
183                  * Attributes = [{atom(), term()}]
184
185                  Attributes is a list of pairs  representing  the  names  and
186                  corresponding  values of all so-called "wild" attributes (as
187                  e.g.  "-compile(...)")  occurring   in   Forms   (cf.   ana‐
188                  lyze_wild_attribute/1).  We  do not guarantee that each name
189                  occurs at most once in the list. The order of listing is not
190                  defined.
191
192                {errors, Errors}:
193
194
195                  * Errors = [term()]
196
197                  Errors  is the list of error descriptors of all error_marker
198                  nodes that occur in Forms. The order of listing is  not  de‐
199                  fined.
200
201                {exports, Exports}:
202
203
204                  * Exports = [FunctionName]
205
206                  * FunctionName = atom() | {atom(), integer()} | {ModuleName,
207                    FunctionName}
208
209                  * ModuleName = atom()
210
211                  Exports is a list of representations of those function names
212                  that  are  listed  by export declaration attributes in Forms
213                  (cf. analyze_export_attribute/1). We do not  guarantee  that
214                  each  name  occurs  at  most  once in the list. The order of
215                  listing is not defined.
216
217                {functions, Functions}:
218
219
220                  * Functions = [{atom(), integer()}]
221
222                  Functions is a list of the names of the functions  that  are
223                  defined in Forms (cf. analyze_function/1). We do not guaran‐
224                  tee that each name occurs at most once in the list. The  or‐
225                  der of listing is not defined.
226
227                {imports, Imports}:
228
229
230                  * Imports = [{Module, Names}]
231
232                  * Module = atom()
233
234                  * Names = [FunctionName]
235
236                  * FunctionName = atom() | {atom(), integer()} | {ModuleName,
237                    FunctionName}
238
239                  * ModuleName = atom()
240
241                  Imports is a list of pairs representing those  module  names
242                  and  corresponding  function names that are listed by import
243                  declaration attributes in Forms  (cf.  analyze_import_attri‐
244                  bute/1),  where  each Module occurs at most once in Imports.
245                  We do not guarantee that each name occurs at  most  once  in
246                  the lists of function names. The order of listing is not de‐
247                  fined.
248
249                {module, ModuleName}:
250
251
252                  * ModuleName = atom()
253
254                  ModuleName is the name declared by  a  module  attribute  in
255                  Forms.  If  no  module  name is defined in Forms, the result
256                  will contain no entry for the module key. If multiple module
257                  name  declarations  should  occur, all but the first will be
258                  ignored.
259
260                {records, Records}:
261
262
263                  * Records = [{atom(), Fields}]
264
265                  * Fields = [{atom(), {Default, Type}}]
266
267                  * Default = none | syntaxTree()
268
269                  * Type = none | syntaxTree()
270
271                  Records is a list of pairs representing the names and corre‐
272                  sponding  field  declarations  of all record declaration at‐
273                  tributes occurring in Forms. For fields declared  without  a
274                  default  value,  the  corresponding value for Default is the
275                  atom none. Similarly, for fields declared  without  a  type,
276                  the  corresponding value for Type is the atom none (cf. ana‐
277                  lyze_record_attribute/1). We  do  not  guarantee  that  each
278                  record  name  occurs  at most once in the list. The order of
279                  listing is not defined.
280
281                {warnings, Warnings}:
282
283
284                  * Warnings = [term()]
285
286                  Warnings is the list  of  error  descriptors  of  all  warn‐
287                  ing_marker  nodes  that occur in Forms. The order of listing
288                  is not defined.
289
290              The evaluation throws syntax_error if an ill-formed Erlang  con‐
291              struct is encountered.
292
293              See  also:  analyze_export_attribute/1, analyze_function/1, ana‐
294              lyze_import_attribute/1,    analyze_record_attribute/1,     ana‐
295              lyze_wild_attribute/1,  erl_syntax:error_marker_info/1, erl_syn‐
296              tax:warning_marker_info/1.
297
298       analyze_function(Node::erl_syntax:syntaxTree()) -> {atom(), arity()}
299
300              Returns the name and arity of a function definition. The  result
301              is  a  pair  {Name,  A} if Node represents a function definition
302              "Name(P_1, ..., P_A) -> ...".
303
304              The evaluation throws syntax_error if Node does not represent  a
305              well-formed function definition.
306
307       analyze_function_name(Node::erl_syntax:syntaxTree()) -> functionName()
308
309              Returns  the function name represented by a syntax tree. If Node
310              represents a function name, such as "foo/1" or  "bloggs:fred/2",
311              a  uniform  representation  of  that name is returned. Different
312              nestings of arity and module name qualifiers in the syntax  tree
313              does not affect the result.
314
315              The  evaluation throws syntax_error if Node does not represent a
316              well-formed function name.
317
318       analyze_implicit_fun(Node::erl_syntax:syntaxTree()) -> functionName()
319
320              Returns the name of an implicit fun expression "fun F". The  re‐
321              sult  is  a  representation  of  the  function name F. (Cf. ana‐
322              lyze_function_name/1.)
323
324              The evaluation throws syntax_error if Node does not represent  a
325              well-formed implicit fun.
326
327              See also: analyze_function_name/1.
328
329       analyze_import_attribute(Node::erl_syntax:syntaxTree())   ->   {atom(),
330       [functionName()]} | atom()
331
332              Returns the module name and (if present) list of function  names
333              declared  by  an import attribute. The returned value is an atom
334              Module or a pair {Module, Names}, where Names is a list of func‐
335              tion names declared as imported from the module named by Module.
336              We do not guarantee that each name occurs at most once in Names.
337              The order of listing is not defined.
338
339              The  evaluation throws syntax_error if Node does not represent a
340              well-formed import attribute.
341
342              See also: analyze_attribute/1.
343
344       analyze_module_attribute(Node::erl_syntax:syntaxTree())  ->  atom()   |
345       {atom(), [atom()]}
346
347              Returns  the  module  name and possible parameters declared by a
348              module attribute. If the attribute is a plain module declaration
349              such as -module(name), the result is the module name. If the at‐
350              tribute is a parameterized module declaration, the result  is  a
351              tuple  containing  the  module  name and a list of the parameter
352              variable names.
353
354              The evaluation throws syntax_error if Node does not represent  a
355              well-formed module attribute.
356
357              See also: analyze_attribute/1.
358
359       analyze_record_attribute(Node::erl_syntax:syntaxTree())   ->   {atom(),
360       fields()}
361
362              Returns the name and the list of fields of a record  declaration
363              attribute.  The  result is a pair {Name, Fields}, if Node repre‐
364              sents "-record(Name, {...}).", where Fields is a list  of  pairs
365              {Label,  {Default,  Type}}  for each field "Label", "Label = De‐
366              fault", "Label :: Type", or "Label = Default  ::  Type"  in  the
367              declaration,  listed in left-to-right order. If the field has no
368              default-value declaration, the value for  Default  will  be  the
369              atom  none.  If the field has no type declaration, the value for
370              Type will be the atom none. We do not guarantee that each  label
371              occurs at most once in the list.
372
373              The  evaluation throws syntax_error if Node does not represent a
374              well-formed record declaration attribute.
375
376              See also: analyze_attribute/1, analyze_record_field/1.
377
378       analyze_record_expr(Node::erl_syntax:syntaxTree()) -> {atom(),  info()}
379       | atom()
380
381              Returns the record name and field name/names of a record expres‐
382              sion.  If  Node  has  type  record_expr,  record_index_expr   or
383              record_access,  a  pair  {Type,  Info} is returned, otherwise an
384              atom Type is returned. Type is the node type of Node,  and  Info
385              depends on Type, as follows:
386
387                record_expr::
388                  {atom(), [{atom(), Value}]}
389
390                record_access::
391                  {atom(), atom()}
392
393                record_index_expr::
394                  {atom(), atom()}
395
396              For  a record_expr node, Info represents the record name and the
397              list of descriptors for the involved fields, listed in the order
398              they  appear.  A  field  descriptor is a pair {Label, Value}, if
399              Node represents "Label = Value". For a record_access node,  Info
400              represents  the record name and the field name. For a record_in‐
401              dex_expr node, Info represents the  record  name  and  the  name
402              field name.
403
404              The  evaluation  throws syntax_error if Node represents a record
405              expression that is not well-formed.
406
407              See also: analyze_record_attribute/1, analyze_record_field/1.
408
409       analyze_record_field(Node::erl_syntax:syntaxTree()) -> field()
410
411              Returns the label, value-expression, and type of a record  field
412              specifier.  The  result  is  a pair {Label, {Default, Type}}, if
413              Node represents "Label", "Label = Default", "Label :: Type",  or
414              "Label = Default :: Type". If the field has no value-expression,
415              the value for Default will be the atom none. If the field has no
416              type, the value for Type will be the atom none.
417
418              The  evaluation throws syntax_error if Node does not represent a
419              well-formed record field specifier.
420
421              See also: analyze_record_attribute/1, analyze_record_expr/1.
422
423       analyze_type_application(Node::erl_syntax:syntaxTree()) -> typeName()
424
425              Returns the name of a used type. The result is a  representation
426              of  the  name of the used pre-defined or local type N/A, if Node
427              represents a local (user) type application "N(T_1,  ...,  T_A)",
428              or a representation of the name of the used remote type M:N/A if
429              Node represents a remote user type  application  "M:N(T_1,  ...,
430              T_A)".
431
432              The  evaluation throws syntax_error if Node does not represent a
433              well-formed (user) type application expression.
434
435              See also: analyze_type_name/1.
436
437       analyze_type_name(Node::erl_syntax:syntaxTree()) -> typeName()
438
439              Returns the type name represented by a syntax tree. If Node rep‐
440              resents  a type name, such as "foo/1" or "bloggs:fred/2", a uni‐
441              form representation of that name is returned.
442
443              The evaluation throws syntax_error if Node does not represent  a
444              well-formed type name.
445
446       analyze_wild_attribute(Node::erl_syntax:syntaxTree())    ->    {atom(),
447       term()}
448
449              Returns the name and value of a "wild" attribute. The result  is
450              the pair {Name, Value}, if Node represents "-Name(Value)".
451
452              Note  that no checking is done whether Name is a reserved attri‐
453              bute name such as module or export: it is assumed that  the  at‐
454              tribute is "wild".
455
456              The  evaluation throws syntax_error if Node does not represent a
457              well-formed wild attribute.
458
459              See also: analyze_attribute/1.
460
461       annotate_bindings(Tree::erl_syntax:syntaxTree()) ->  erl_syntax:syntax‐
462       Tree()
463
464              Adds  or  updates annotations on nodes in a syntax tree. Equiva‐
465              lent to annotate_bindings(Tree, Bindings)  where  the  top-level
466              environment  Bindings  is  taken from the annotation {env, Bind‐
467              ings} on the root node of Tree. An exception  is  thrown  if  no
468              such annotation should exist.
469
470              See also: annotate_bindings/2.
471
472       annotate_bindings(Tree::erl_syntax:syntaxTree(),      Env::ordsets:ord‐
473       set(atom())) -> erl_syntax:syntaxTree()
474
475              Adds or updates annotations on nodes in a syntax tree.  Bindings
476              specifies  the  set of bound variables in the environment of the
477              top level node. The following annotations are affected:
478
479                * {env, Vars}, representing the input environment of the  sub‐
480                  tree.
481
482                * {bound,  Vars}, representing the variables that are bound in
483                  the subtree.
484
485                * {free, Vars}, representing the free variables  in  the  sub‐
486                  tree.
487
488              Bindings  and Vars are ordered-set lists (cf. module ordsets) of
489              atoms representing variable names.
490
491              See also: ordsets(3), annotate_bindings/1.
492
493       fold(F::(erl_syntax:syntaxTree(),   term())   ->   term(),   S::term(),
494       Tree::erl_syntax:syntaxTree()) -> term()
495
496              Folds  a function over all nodes of a syntax tree. The result is
497              the value of Function(X1, Function(X2, ...  Function(Xn,  Start)
498              ... )), where [X1, X2, ..., Xn] are the nodes of Tree in a post-
499              order traversal.
500
501              See also: fold_subtrees/3, foldl_listlist/3.
502
503       fold_subtrees(F::(erl_syntax:syntaxTree(),    term())    ->     term(),
504       S::term(), Tree::erl_syntax:syntaxTree()) -> term()
505
506              Folds  a  function over the immediate subtrees of a syntax tree.
507              This is similar to fold/3, but only on the immediate subtrees of
508              Tree,  in left-to-right order; it does not include the root node
509              of Tree.
510
511              See also: fold/3.
512
513       foldl_listlist(F::(term(),    term())     ->     term(),     S::term(),
514       Ls::[[term()]]) -> term()
515
516              Like lists:foldl/3, but over a list of lists.
517
518              See also: lists:foldl/3, fold/3.
519
520       function_name_expansions(Fs::[name()]) -> [{shortname(), name()}]
521
522              Creates  a  mapping from corresponding short names to full func‐
523              tion names. Names are represented by nested tuples of atoms  and
524              integers  (cf.  analyze_function_name/1).  The  result is a list
525              containing a pair {ShortName, Name} for each element Name in the
526              given  list, where the corresponding ShortName is the rightmost-
527              innermost part of Name. The list thus represents a  finite  map‐
528              ping  from  unqualified  names  to  the  corresponding qualified
529              names.
530
531              Note: the resulting list can contain more than one tuple {Short‐
532              Name, Name} for the same ShortName, possibly with different val‐
533              ues for Name, depending on the given list.
534
535              See also: analyze_function_name/1.
536
537       is_fail_expr(E::erl_syntax:syntaxTree()) -> boolean()
538
539              Returns true if Tree represents an expression which never termi‐
540              nates normally. Note that the reverse does not apply. Currently,
541              the detected cases are calls to exit/1, throw/1,  erlang:error/1
542              and erlang:error/2.
543
544              See  also:  erlang:error/1,  erlang:error/2,  erlang:exit/1, er‐
545              lang:throw/1.
546
547       limit(Tree::erl_syntax:syntaxTree(),  Depth::integer())   ->   erl_syn‐
548       tax:syntaxTree()
549
550              Equivalent  to  limit(Tree, Depth, Text) using the text "..." as
551              default replacement.
552
553              See also: limit/3, erl_syntax:text/1.
554
555       limit(Tree::erl_syntax:syntaxTree(),  Depth::integer(),  Node::erl_syn‐
556       tax:syntaxTree()) -> erl_syntax:syntaxTree()
557
558              Limits a syntax tree to a specified depth. Replaces all non-leaf
559              subtrees in Tree at the given Depth by Node. If Depth  is  nega‐
560              tive, the result is always Node, even if Tree has no subtrees.
561
562              When  a  group of subtrees (as e.g., the argument list of an ap‐
563              plication node) is at the specified depth, and there are two  or
564              more  subtrees in the group, these will be collectively replaced
565              by Node even if they are leaf nodes. Groups of subtrees that are
566              above  the  specified  depth will be limited in size, as if each
567              subsequent tree in the group were one level deeper than the pre‐
568              vious. E.g., if Tree represents a list of integers "[1, 2, 3, 4,
569              5, 6, 7, 8, 9, 10]", the result of limit(Tree, 5) will represent
570              [1, 2, 3, 4, ...].
571
572              The  resulting  syntax tree is typically only useful for pretty-
573              printing or similar visual formatting.
574
575              See also: limit/2.
576
577       map(F::(erl_syntax:syntaxTree())      ->       erl_syntax:syntaxTree(),
578       Tree::erl_syntax:syntaxTree()) -> erl_syntax:syntaxTree()
579
580              Applies  a function to each node of a syntax tree. The result of
581              each application replaces the corresponding original  node.  The
582              order of traversal is bottom-up.
583
584              See also: map_subtrees/2.
585
586       map_subtrees(F::(erl_syntax:syntaxTree())  ->  erl_syntax:syntaxTree(),
587       Tree::erl_syntax:syntaxTree()) -> erl_syntax:syntaxTree()
588
589              Applies a function to each immediate subtree of a  syntax  tree.
590              The result of each application replaces the corresponding origi‐
591              nal node.
592
593              See also: map/2.
594
595       mapfold(F::(erl_syntax:syntaxTree(),  term())  ->   {erl_syntax:syntax‐
596       Tree(), term()}, S::term(), Tree::erl_syntax:syntaxTree()) -> {erl_syn‐
597       tax:syntaxTree(), term()}
598
599              Combines map and fold in a single operation. This is similar  to
600              map/2,  but also propagates an extra value from each application
601              of the Function to the next, while doing a post-order  traversal
602              of  the tree like fold/3. The value Start is passed to the first
603              function application, and the final result is the result of  the
604              last application.
605
606              See also: fold/3, map/2.
607
608       mapfold_subtrees(F::(erl_syntax:syntaxTree(),   term())   ->  {erl_syn‐
609       tax:syntaxTree(), term()}, S::term(), Tree::erl_syntax:syntaxTree()) ->
610       {erl_syntax:syntaxTree(), term()}
611
612              Does a mapfold operation over the immediate subtrees of a syntax
613              tree. This is similar to mapfold/3, but only  on  the  immediate
614              subtrees  of  Tree,  in left-to-right order; it does not include
615              the root node of Tree.
616
617              See also: mapfold/3.
618
619       mapfoldl_listlist(F::(term(), term()) -> {term(),  term()},  S::term(),
620       Ls::[[term()]]) -> {[[term()]], term()}
621
622              Like  lists:mapfoldl/3,  but  over  a list of lists. The list of
623              lists in the result has the same structure as the given list  of
624              lists.
625
626       new_variable_name(S::sets:set(atom())) -> atom()
627
628              Returns  an  atom  which is not already in the set Used. This is
629              equivalent to new_variable_name(Function, Used), where  Function
630              maps  a  given  integer N to the atom whose name consists of "V"
631              followed by the numeral for N.
632
633              See also: new_variable_name/2.
634
635       new_variable_name(F::(integer())  ->  atom(),  S::sets:set(atom()))  ->
636       atom()
637
638              Returns  a user-named atom which is not already in the set Used.
639              The atom is generated by applying the given Function to a gener‐
640              ated  integer.  Integers  are generated using an algorithm which
641              tries to keep the names randomly distributed within a reasonably
642              small range relative to the number of elements in the set.
643
644              This  function  uses  the  module rand to generate new keys. The
645              seed it uses  may  be  initialized  by  calling  rand:seed/1  or
646              rand:seed/2 before this function is first called.
647
648              See also: random(3), sets(3), new_variable_name/1.
649
650       new_variable_names(N::integer(), S::sets:set(atom())) -> [atom()]
651
652              Like new_variable_name/1, but generates a list of N new names.
653
654              See also: new_variable_name/1.
655
656       new_variable_names(N::integer(),      F::(integer())     ->     atom(),
657       S::sets:set(atom())) -> [atom()]
658
659              Like new_variable_name/2, but generates a list of N new names.
660
661              See also: new_variable_name/2.
662
663       strip_comments(Tree::erl_syntax:syntaxTree())   ->   erl_syntax:syntax‐
664       Tree()
665
666              Removes  all comments from all nodes of a syntax tree. All other
667              attributes (such  as  position  information)  remain  unchanged.
668              Standalone  comments in form lists are removed; any other stand‐
669              alone comments are changed into null-comments (no text,  no  in‐
670              dentation).
671
672       to_comment(Tree::erl_syntax:syntaxTree()) -> erl_syntax:syntaxTree()
673
674              Equivalent to to_comment(Tree, "% ").
675
676       to_comment(Tree::erl_syntax:syntaxTree(), Prefix::string()) -> erl_syn‐
677       tax:syntaxTree()
678
679              Equivalent to to_comment(Tree, Prefix, F) for a default  format‐
680              ting  function  F.  The default F simply calls erl_prettypr:for‐
681              mat/1.
682
683              See also: to_comment/3, erl_prettypr:format/1.
684
685       to_comment(Tree::erl_syntax:syntaxTree(),             Prefix::string(),
686       F::(erl_syntax:syntaxTree()) -> string()) -> erl_syntax:syntaxTree()
687
688              Transforms  a syntax tree into an abstract comment. The lines of
689              the comment contain the text for Node, as produced by the  given
690              Printer  function.  Each  line of the comment is prefixed by the
691              string Prefix (this does not include the initial  "%"  character
692              of the comment line).
693
694              For    example,    the   result   of   to_comment(erl_syntax:ab‐
695              stract([a,b,c])) represents
696
697                        %% [a,b,c]
698
699              (cf. to_comment/1).
700
701              Note: the text returned by the formatting function will be split
702              automatically into separate comment lines at each line break. No
703              extra work is needed.
704
705              See also: to_comment/1, to_comment/2.
706
707       variables(Tree::erl_syntax:syntaxTree()) -> sets:set(atom())
708
709              Returns the names of variables occurring in a syntax  tree,  The
710              result  is  a  set of variable names represented by atoms. Macro
711              names are not included.
712
713              See also: sets(3).
714

AUTHORS

716       Richard Carlsson <carlsson.richard@gmail.com>
717
718
719
720                              syntax_tools 3.0.1             erl_syntax_lib(3)
Impressum