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

NAME

6       cerl - Core Erlang abstract syntax trees.
7

DESCRIPTION

9       Core Erlang abstract syntax trees.
10
11       This  module defines an abstract data type for representing Core Erlang
12       source code as syntax trees.
13
14       A recommended starting point for the first-time user is the  documenta‐
15       tion of the function type/1.
16
17       NOTES:
18
19       This  module  deals with the composition and decomposition of syntactic
20       entities (as opposed to semantic ones); its purpose is to hide all  di‐
21       rect  references  to  the data structures used to represent these enti‐
22       ties. With few exceptions, the functions in this module perform no  se‐
23       mantic  interpretation of their inputs, and in general, the user is as‐
24       sumed to pass type-correct arguments - if this is not done, the effects
25       are not defined.
26
27       Currently,  the internal data structure used is the same as the record-
28       based data structures used traditionally in the Beam compiler.
29
30       The internal representations of abstract syntax trees  are  subject  to
31       change  without  notice, and should not be documented outside this mod‐
32       ule. Furthermore, we do not give any guarantees on how an abstract syn‐
33       tax  tree may or may not be represented, with the following exceptions:
34       no syntax tree is represented by a single atom, such as none, by a list
35       constructor  [X  |  Y],  or by the empty list []. This can be relied on
36       when writing functions that operate on syntax trees.
37

DATA TYPES

39         c_alias() = #c_alias{}:
40
41
42         c_apply() = #c_apply{}:
43
44
45         c_binary() = #c_binary{}:
46
47
48         c_bitstr() = #c_bitstr{}:
49
50
51         c_call() = #c_call{}:
52
53
54         c_case() = #c_case{}:
55
56
57         c_catch() = #c_catch{}:
58
59
60         c_clause() = #c_clause{}:
61
62
63         c_cons() = #c_cons{}:
64
65
66         c_fun() = #c_fun{}:
67
68
69         c_lct() = c_literal() | c_cons() | c_tuple():
70
71
72         c_let() = #c_let{}:
73
74
75         c_letrec() = #c_letrec{}:
76
77
78         c_literal() = #c_literal{}:
79
80
81         c_map() = #c_map{}:
82
83
84         c_map_pair() = #c_map_pair{}:
85
86
87         c_module() = #c_module{}:
88
89
90         c_primop() = #c_primop{}:
91
92
93         c_receive() = #c_receive{}:
94
95
96         c_seq() = #c_seq{}:
97
98
99         c_try() = #c_try{}:
100
101
102         c_tuple() = #c_tuple{}:
103
104
105         c_values() = #c_values{}:
106
107
108         c_var() = #c_var{}:
109
110
111         cerl() = c_alias() | c_apply() | c_binary() | c_bitstr() | c_call() |
112         c_case()  |  c_catch()  | c_clause() | c_cons() | c_fun() | c_let() |
113         c_letrec() | c_literal() | c_map()  |  c_map_pair()  |  c_module()  |
114         c_primop() | c_receive() | c_seq() | c_try() | c_tuple() | c_values()
115         | c_var():
116
117
118         ctype() = alias | apply | binary | bitstr | call |  case  |  catch  |
119         clause  | cons | fun | let | letrec | literal | map | map_pair | mod‐
120         ule | primop | receive | seq | try | tuple | values | var:
121
122
123         dtype() = cons | tuple | {atomic, value()}:
124
125
126         map_op() = #c_literal{val=assoc} | #c_literal{val=exact}:
127
128
129         value() = integer() | float() | atom() | []:
130
131
132         var_name() = integer() | atom() | {atom(), integer()}:
133
134

EXPORTS

136       abstract(T::term()) -> c_literal()
137
138              Creates a syntax tree corresponding to an Erlang term. Term must
139              be a literal term, i.e., one that can be represented as a source
140              code literal. Thus, it may not  contain  a  process  identifier,
141              port, reference, binary or function value as a subterm.
142
143              Note: This is a constant time operation.
144
145              See  also:  ann_abstract/2,  concrete/1,  is_literal/1,  is_lit‐
146              eral_term/1.
147
148       add_ann(Terms::[term()], Node::cerl()) -> cerl()
149
150              Appends Annotations to the list of user annotations of Node.
151
152              Note:  this  is  equivalent  to  set_ann(Node,  Annotations   ++
153              get_ann(Node)), but potentially more efficient.
154
155              See also: get_ann/1, set_ann/2.
156
157       alias_pat(Node::c_alias()) -> cerl()
158
159              Returns the pattern subtree of an abstract pattern alias.
160
161              See also: c_alias/2.
162
163       alias_var(Node::c_alias()) -> c_var()
164
165              Returns the variable subtree of an abstract pattern alias.
166
167              See also: c_alias/2.
168
169       ann_abstract(As::[term()], T::term()) -> c_literal()
170
171              See also: abstract/1.
172
173       ann_c_alias(As::[term()], Var::c_var(), Pattern::cerl()) -> c_alias()
174
175              See also: c_alias/2.
176
177       ann_c_apply(As::[term()],   Operator::cerl(),  Arguments::[cerl()])  ->
178       c_apply()
179
180              See also: c_apply/2.
181
182       ann_c_atom(As::[term()], Name::atom() | string()) -> c_literal()
183
184              See also: c_atom/1.
185
186       ann_c_binary(As::[term()], Segments::[cerl()]) -> c_binary()
187
188              See also: c_binary/1.
189
190       ann_c_bitstr(As::[term()], Value::cerl(),  Size::cerl(),  Type::cerl(),
191       Flags::cerl()) -> c_bitstr()
192
193              Equivalent  to  ann_c_bitstr(As, Value, Size, abstract(1), Type,
194              Flags).
195
196       ann_c_bitstr(As::[term()],  Val::cerl(),  Size::cerl(),   Unit::cerl(),
197       Type::cerl(), Flags::cerl()) -> c_bitstr()
198
199              See also: ann_c_bitstr/5, c_bitstr/5.
200
201       ann_c_call(As::[term()],     Module::cerl(),     Name::cerl(),    Argu‐
202       ments::[cerl()]) -> c_call()
203
204              See also: c_call/3.
205
206       ann_c_case(As::[term()], Expr::cerl(), Clauses::[cerl()]) -> c_case()
207
208              See also: c_case/2.
209
210       ann_c_catch(As::[term()], Body::cerl()) -> c_catch()
211
212              See also: c_catch/1.
213
214       ann_c_char(As::[term()], Value::char()) -> c_literal()
215
216              See also: c_char/1.
217
218       ann_c_clause(As::[term()],   Patterns::[cerl()],    Body::cerl())    ->
219       c_clause()
220
221              Equivalent to ann_c_clause(As, Patterns, c_atom(true), Body).
222
223              See also: c_clause/3.
224
225       ann_c_clause(As::[term()],      Patterns::[cerl()],      Guard::cerl(),
226       Body::cerl()) -> c_clause()
227
228              See also: ann_c_clause/3, c_clause/3.
229
230       ann_c_cons(As::[term()],  C_literal::cerl(),  Tail::cerl())  ->  c_lit‐
231       eral() | c_cons()
232
233              See also: c_cons/2.
234
235       ann_c_cons_skel(As::[term()], Head::cerl(), Tail::cerl()) -> c_cons()
236
237              See also: c_cons_skel/2.
238
239       ann_c_float(As::[term()], Value::float()) -> c_literal()
240
241              See also: c_float/1.
242
243       ann_c_fname(As::[term()], Atom::atom(), Arity::arity()) -> c_var()
244
245              Equivalent to ann_c_var(As, {Atom, Arity}).
246
247              See also: c_fname/2.
248
249       ann_c_fun(As::[term()], Variables::[cerl()], Body::cerl()) -> c_fun()
250
251              See also: c_fun/2.
252
253       ann_c_int(As::[term()], Value::integer()) -> c_literal()
254
255              See also: c_int/1.
256
257       ann_c_let(As::[term()],      Variables::[cerl()],     Argument::cerl(),
258       Body::cerl()) -> c_let()
259
260              See also: c_let/3.
261
262       ann_c_letrec(As::[term()], Defs::[{cerl(), cerl()}],  Body::cerl())  ->
263       c_letrec()
264
265              See also: c_letrec/2.
266
267       ann_c_map(As::[term()], Es::[c_map_pair()]) -> c_map() | c_literal()
268
269       ann_c_map(As::[term()],      C_literal::c_map()      |     c_literal(),
270       Es::[c_map_pair()]) -> c_map() | c_literal()
271
272       ann_c_map_pair(As::[term()],  Op::cerl(),  K::cerl(),   V::cerl())   ->
273       c_map_pair()
274
275       ann_c_map_pattern(As::[term()], Pairs::[c_map_pair()]) -> c_map()
276
277       ann_c_module(As::[term()],       Name::cerl(),       Exports::[cerl()],
278       Es::[{cerl(), cerl()}]) -> c_module()
279
280              See also: ann_c_module/5, c_module/3.
281
282       ann_c_module(As::[term()],   Name::cerl(),    Exports::[cerl()],    At‐
283       trs::[{cerl(), cerl()}], Es::[{cerl(), cerl()}]) -> c_module()
284
285              See also: ann_c_module/4, c_module/4.
286
287       ann_c_nil(As::[term()]) -> c_literal()
288
289              See also: c_nil/0.
290
291       ann_c_primop(As::[term()], Name::cerl(), Arguments::[cerl()]) -> c_pri‐
292       mop()
293
294              See also: c_primop/2.
295
296       ann_c_receive(As::[term()], Clauses::[cerl()]) -> c_receive()
297
298              Equivalent  to  ann_c_receive(As,   Clauses,   c_atom(infinity),
299              c_atom(true)).
300
301              See also: c_atom/1, c_receive/3.
302
303       ann_c_receive(As::[term()],   Clauses::[cerl()],  Timeout::cerl(),  Ac‐
304       tion::cerl()) -> c_receive()
305
306              See also: ann_c_receive/2, c_receive/3.
307
308       ann_c_seq(As::[term()], Argument::cerl(), Body::cerl()) -> c_seq()
309
310              See also: c_seq/2.
311
312       ann_c_string(As::[term()], Value::string()) -> c_literal()
313
314              See also: c_string/1.
315
316       ann_c_try(As::[term()],   Expr::cerl(),   Vs::[cerl()],   Body::cerl(),
317       Evs::[cerl()], Handler::cerl()) -> c_try()
318
319              See also: c_try/5.
320
321       ann_c_tuple(As::[term()], Es::[cerl()]) -> c_tuple() | c_literal()
322
323              See also: c_tuple/1.
324
325       ann_c_tuple_skel(As::[term()], Es::[cerl()]) -> c_tuple()
326
327              See also: c_tuple_skel/1.
328
329       ann_c_values(As::[term()], Es::[cerl()]) -> c_values()
330
331              See also: c_values/1.
332
333       ann_c_var(As::[term()], Name::var_name()) -> c_var()
334
335              See also: c_var/1.
336
337       ann_make_data(As::[term()], X2::dtype(), Es::[cerl()]) -> c_lct()
338
339              See also: make_data/2.
340
341       ann_make_data_skel(As::[term()], X2::dtype(), Es::[cerl()]) -> c_lct()
342
343              See also: make_data_skel/2.
344
345       ann_make_list(As::[term()], List::[cerl()]) -> cerl()
346
347              Equivalent to ann_make_list(As, List, none).
348
349       ann_make_list(As::[term()], T::[cerl()], Tail::cerl() | none) -> cerl()
350
351              See also: ann_make_list/2, make_list/2.
352
353       ann_make_tree(As::[term()], X2::ctype(), X3::[[cerl()], ...]) -> cerl()
354
355              Creates  a syntax tree with the given annotations, type and sub‐
356              trees. See make_tree/2 for details.
357
358              See also: make_tree/2.
359
360       apply_args(Node::c_apply()) -> [cerl()]
361
362              Returns the list of argument subtrees of  an  abstract  function
363              application.
364
365              See also: apply_arity/1, c_apply/2.
366
367       apply_arity(Node::c_apply()) -> arity()
368
369              Returns  the number of argument subtrees of an abstract function
370              application.
371
372              Note: this is equivalent to length(apply_args(Node)), but poten‐
373              tially more efficient.
374
375              See also: apply_args/1, c_apply/2.
376
377       apply_op(Node::c_apply()) -> cerl()
378
379              Returns  the  operator  subtree of an abstract function applica‐
380              tion.
381
382              See also: c_apply/2.
383
384       atom_lit(Node::cerl()) -> nonempty_string()
385
386              Returns the literal string represented by an abstract atom. This
387              always includes surrounding single-quote characters.
388
389              Note  that an abstract atom may have several literal representa‐
390              tions, and that the representation yielded by this  function  is
391              not  fixed;  e.g.,  atom_lit(c_atom("a\012b"))  could  yield the
392              string "\'a\\nb\'".
393
394              See also: c_atom/1.
395
396       atom_name(Node::c_literal()) -> string()
397
398              Returns the printname of an abstract atom.
399
400              See also: c_atom/1.
401
402       atom_val(Node::c_literal()) -> atom()
403
404              Returns the value represented by an abstract atom.
405
406              See also: c_atom/1.
407
408       binary_segments(Node::c_binary()) -> [cerl()]
409
410              Returns the list of segment subtrees of an abstract  binary-tem‐
411              plate.
412
413              See also: c_binary/1, c_bitstr/5.
414
415       bitstr_bitsize(Node::c_bitstr()) -> all | any | utf | non_neg_integer()
416
417              Returns  the  total  size in bits of an abstract bit-string tem‐
418              plate. If the size field is an integer literal,  the  result  is
419              the  product  of  the size and unit values; if the size field is
420              the atom literal all, the atom all is returned. If the  size  is
421              not a literal, the atom any is returned.
422
423              See also: c_bitstr/5.
424
425       bitstr_flags(Node::c_bitstr()) -> cerl()
426
427              Returns the flags subtree of an abstract bit-string template.
428
429              See also: c_bitstr/5.
430
431       bitstr_size(Node::c_bitstr()) -> cerl()
432
433              Returns the size subtree of an abstract bit-string template.
434
435              See also: c_bitstr/5.
436
437       bitstr_type(Node::c_bitstr()) -> cerl()
438
439              Returns the type subtree of an abstract bit-string template.
440
441              See also: c_bitstr/5.
442
443       bitstr_unit(Node::c_bitstr()) -> cerl()
444
445              Returns the unit subtree of an abstract bit-string template.
446
447              See also: c_bitstr/5.
448
449       bitstr_val(Node::c_bitstr()) -> cerl()
450
451              Returns the value subtree of an abstract bit-string template.
452
453              See also: c_bitstr/5.
454
455       c_alias(Var::c_var(), Pattern::cerl()) -> c_alias()
456
457              Creates  an abstract pattern alias. The result represents "Vari‐
458              able = Pattern".
459
460              See also: alias_pat/1, alias_var/1,  ann_c_alias/3,  c_clause/3,
461              is_c_alias/1, update_c_alias/3.
462
463       c_apply(Operator::cerl(), Arguments::[cerl()]) -> c_apply()
464
465              Creates  an  abstract function application. If Arguments is [A1,
466              ..., An], the result represents "apply Operator(A1, ..., An)".
467
468              See  also:  ann_c_apply/3,  apply_args/1,   apply_arity/1,   ap‐
469              ply_op/1, c_call/3, c_primop/2, is_c_apply/1, update_c_apply/3.
470
471       c_atom(Name::atom() | string()) -> c_literal()
472
473              Creates  an abstract atom literal. The print name of the atom is
474              the character sequence represented by Name.
475
476              Note: passing a string as argument to  this  function  causes  a
477              corresponding  atom  to  be created for the internal representa‐
478              tion.
479
480              See also:  ann_c_atom/2,  atom_lit/1,  atom_name/1,  atom_val/1,
481              is_c_atom/1.
482
483       c_binary(Segments::[cerl()]) -> c_binary()
484
485              Creates  an abstract binary-template. A binary object is in this
486              context a sequence of an arbitrary number of bits.  (The  number
487              of  bits  used to be evenly divisible by 8, but after the intro‐
488              duction of bit strings in the Erlang language,  the  choice  was
489              made  to  use  the  binary  template for all bit strings.) It is
490              specified by zero or more bit-string template segments of  arbi‐
491              trary lengths (in number of bits). If Segments is [S1, ..., Sn],
492              the result represents "#{S1, ..., Sn}#". All the  Si  must  have
493              type bitstr.
494
495              See   also:   ann_c_binary/2,   binary_segments/1,   c_bitstr/5,
496              is_c_binary/1, update_c_binary/2.
497
498       c_bitstr(Val::cerl(), Type::cerl(), Flags::cerl()) -> c_bitstr()
499
500              Equivalent to c_bitstr(Value, abstract(all), abstract(1),  Type,
501              Flags).
502
503       c_bitstr(Val::cerl(),  Size::cerl(),  Type::cerl(),  Flags::cerl())  ->
504       c_bitstr()
505
506              Equivalent to c_bitstr(Value, Size, abstract(1), Type, Flags).
507
508       c_bitstr(Val::cerl(),   Size::cerl(),    Unit::cerl(),    Type::cerl(),
509       Flags::cerl()) -> c_bitstr()
510
511              Creates an abstract bit-string template. These can only occur as
512              components of an abstract binary-template (see c_binary/1).  The
513              result  represents  "#<Value>(Size,  Unit,  Type, Flags)", where
514              Unit must represent a positive integer constant, Type must  rep‐
515              resent a constant atom (one of 'integer', 'float', or 'binary'),
516              and Flags must represent a constant list "[F1, ...,  Fn]"  where
517              all the Fi are atoms.
518
519              See  also:  ann_c_bitstr/6,  bitstr_flags/1, bitstr_size/1, bit‐
520              str_type/1, bitstr_unit/1, bitstr_val/1,  c_binary/1,  is_c_bit‐
521              str/1, update_c_bitstr/6.
522
523       c_call(Module::cerl(), Name::cerl(), Arguments::[cerl()]) -> c_call()
524
525              Creates an abstract inter-module call. If Arguments is [A1, ...,
526              An], the result represents "call Module:Name(A1, ..., An)".
527
528              See  also:  ann_c_call/4,  c_apply/2,  c_primop/2,  call_args/1,
529              call_arity/1,   call_module/1,   call_name/1,  is_c_call/1,  up‐
530              date_c_call/4.
531
532       c_case(Expr::cerl(), Clauses::[cerl()]) -> c_case()
533
534              Creates an abstract case-expression. If  Clauses  is  [C1,  ...,
535              Cn],  the  result  represents  "case Argument of C1 ... Cn end".
536              Clauses must not be empty.
537
538              See also: ann_c_case/3,  c_clause/3,  case_arg/1,  case_arity/1,
539              case_clauses/1, is_c_case/1, update_c_case/3.
540
541       c_catch(Body::cerl()) -> c_catch()
542
543              Creates  an  abstract  catch-expression.  The  result represents
544              "catch Body".
545
546              Note: catch-expressions can be rewritten as try-expressions, and
547              will eventually be removed from Core Erlang.
548
549              See  also:  ann_c_catch/2,  c_try/5, catch_body/1, is_c_catch/1,
550              update_c_catch/2.
551
552       c_char(Value::non_neg_integer()) -> c_literal()
553
554              Creates an abstract character literal. If the local  implementa‐
555              tion  of  Erlang  defines  char() as a subset of integer(), this
556              function is equivalent to c_int/1. Otherwise, if the given value
557              is  an  integer,  it will be converted to the character with the
558              corresponding code. The lexical representation of a character is
559              "$Char",  where Char is a single printing character or an escape
560              sequence.
561
562              See  also:  ann_c_char/2,   c_int/1,   c_string/1,   char_lit/1,
563              char_val/1, is_c_char/1, is_print_char/1.
564
565       c_clause(Patterns::[cerl()], Body::cerl()) -> c_clause()
566
567              Equivalent to c_clause(Patterns, c_atom(true), Body).
568
569              See also: c_atom/1.
570
571       c_clause(Patterns::[cerl()], Guard::cerl(), Body::cerl()) -> c_clause()
572
573              Creates an an abstract clause. If Patterns is [P1, ..., Pn], the
574              result represents "<P1, ..., Pn> when Guard -> Body".
575
576              See also:  ann_c_clause/4,  c_case/2,  c_clause/2,  c_receive/3,
577              clause_arity/1,  clause_body/1,  clause_guard/1,  clause_pats/1,
578              clause_vars/1, is_c_clause/1, update_c_clause/4.
579
580       c_cons(C_literal::cerl(), Tail::cerl()) -> c_literal() | c_cons()
581
582              Creates an abstract  list  constructor.  The  result  represents
583              "[Head  | Tail]". Note that if both Head and Tail have type lit‐
584              eral, then the result will also have type literal,  and  annota‐
585              tions on Head and Tail are lost.
586
587              Recall that in Erlang, the tail element of a list constructor is
588              not necessarily a list.
589
590              See  also:  ann_c_cons/3,  c_cons_skel/2,  c_nil/0,   cons_hd/1,
591              cons_tl/1,     is_c_cons/1,     is_c_list/1,    list_elements/1,
592              list_length/1, make_list/2, update_c_cons/3.
593
594       c_cons_skel(Head::cerl(), Tail::cerl()) -> c_cons()
595
596              Creates an abstract list constructor  skeleton.  Does  not  fold
597              constant literals, i.e., the result always has type cons, repre‐
598              senting "[Head | Tail]".
599
600              This function is occasionally useful when  it  is  necessary  to
601              have  annotations  on  the  subnodes of a list constructor node,
602              even when the subnodes are constant literals. Note however  that
603              is_literal/1 will yield false and concrete/1 will fail if passed
604              the result from this function.
605
606              fold_literal/1 can be used to revert a node to  the  normal-form
607              representation.
608
609              See  also:  ann_c_cons_skel/3,  c_cons/2,  c_nil/0,  concrete/1,
610              fold_literal/1,  is_c_cons/1,  is_c_list/1,  is_literal/1,   up‐
611              date_c_cons_skel/3.
612
613       c_float(Value::float()) -> c_literal()
614
615              Creates  an  abstract floating-point literal. The lexical repre‐
616              sentation is the decimal floating-point numeral of Value.
617
618              See also: ann_c_float/2, float_lit/1, float_val/1, is_c_float/1.
619
620       c_fname(Atom::atom(), Arity::arity()) -> c_var()
621
622              Equivalent to c_var({Name, Arity}).
623
624              See    also:    ann_c_fname/3,    fname_arity/1,     fname_id/1,
625              is_c_fname/1, update_c_fname/3.
626
627       c_fun(Variables::[cerl()], Body::cerl()) -> c_fun()
628
629              Creates  an  abstract  fun-expression. If Variables is [V1, ...,
630              Vn], the result represents "fun (V1, ..., Vn) -> Body". All  the
631              Vi must have type var.
632
633              See  also:  ann_c_fun/3,  fun_arity/1,  fun_body/1,  fun_vars/1,
634              is_c_fun/1, update_c_fun/3.
635
636       c_int(Value::integer()) -> c_literal()
637
638              Creates an abstract integer literal. The lexical  representation
639              is the canonical decimal numeral of Value.
640
641              See   also:   ann_c_int/2,   c_char/1,   int_lit/1,   int_val/1,
642              is_c_int/1.
643
644       c_let(Variables::[cerl()], Argument::cerl(), Body::cerl()) -> c_let()
645
646              Creates an abstract let-expression. If Variables  is  [V1,  ...,
647              Vn],  the  result  represents  "let  <V1, ..., Vn> = Argument in
648              Body". All the Vi must have type var.
649
650              See  also:  ann_c_let/4,  is_c_let/1,  let_arg/1,   let_arity/1,
651              let_body/1, let_vars/1, update_c_let/4.
652
653       c_letrec(Defs::[{cerl(), cerl()}], Body::cerl()) -> c_letrec()
654
655              Creates  an  abstract letrec-expression. If Definitions is [{V1,
656              F1}, ..., {Vn, Fn}], the result represents "letrec V1 =  F1  ...
657              Vn  =  Fn  in  Body. All the Vi must have type var and represent
658              function names. All the Fi must have type 'fun'.
659
660              See  also:  ann_c_letrec/3,  is_c_letrec/1,  letrec_body/1,  le‐
661              trec_defs/1, letrec_vars/1, update_c_letrec/3.
662
663       c_map(Pairs::[c_map_pair()]) -> c_map()
664
665       c_map_pair(Key::cerl(), Val::cerl()) -> c_map_pair()
666
667       c_map_pair_exact(Key::cerl(), Val::cerl()) -> c_map_pair()
668
669       c_map_pattern(Pairs::[c_map_pair()]) -> c_map()
670
671       c_module(Name::cerl(),  Exports::[cerl()],  Es::[{cerl(),  cerl()}]) ->
672       c_module()
673
674              Equivalent to c_module(Name, Exports, [], Definitions).
675
676       c_module(Name::cerl(),  Exports::[cerl()],  Attrs::[{cerl(),  cerl()}],
677       Es::[{cerl(), cerl()}]) -> c_module()
678
679              Creates an abstract module definition. The result represents
680
681                  module Name [E1, ..., Ek]
682                    attributes [K1 = T1, ...,
683                                Km = Tm]
684                    V1 = F1
685                    ...
686                    Vn = Fn
687                  end
688
689              if  Exports  =  [E1, ..., Ek], Attributes = [{K1, T1}, ..., {Km,
690              Tm}], and Definitions = [{V1, F1}, ..., {Vn, Fn}].
691
692              Name and all the Ki must be atom literals, and all the  Ti  must
693              be  constant  literals. All the Vi and Ei must have type var and
694              represent function names. All the Fi must have type 'fun'.
695
696              See also:  ann_c_module/4,  ann_c_module/5,  c_atom/1,  c_fun/2,
697              c_module/3,    c_var/1,   is_literal/1,   module_attrs/1,   mod‐
698              ule_defs/1, module_exports/1, module_name/1, module_vars/1,  up‐
699              date_c_module/5.
700
701       c_nil() -> c_literal()
702
703              Creates  an abstract empty list. The result represents "[]". The
704              empty list is traditionally called "nil".
705
706              See also: ann_c_nil/1, c_cons/2, is_c_list/1.
707
708       c_primop(Name::cerl(), Arguments::[cerl()]) -> c_primop()
709
710              Creates an abstract primitive operation call.  If  Arguments  is
711              [A1, ..., An], the result represents "primop Name(A1, ..., An)".
712              Name must be an atom literal.
713
714              See also: ann_c_primop/3,  c_apply/2,  c_call/3,  is_c_primop/1,
715              primop_args/1, primop_arity/1, primop_name/1, update_c_primop/3.
716
717       c_receive(Clauses::[cerl()]) -> c_receive()
718
719              Equivalent      to      c_receive(Clauses,     c_atom(infinity),
720              c_atom(true)).
721
722              See also: c_atom/1.
723
724       c_receive(Clauses::[cerl()], Timeout::cerl(), Action::cerl()) ->  c_re‐
725       ceive()
726
727              Creates  an abstract receive-expression. If Clauses is [C1, ...,
728              Cn], the result represents "receive C1 ... Cn after  Timeout  ->
729              Action end".
730
731              See  also:  ann_c_receive/4,  c_receive/1,  is_c_receive/1,  re‐
732              ceive_action/1,   receive_clauses/1,   receive_timeout/1,    up‐
733              date_c_receive/4.
734
735       c_seq(Argument::cerl(), Body::cerl()) -> c_seq()
736
737              Creates an abstract sequencing expression. The result represents
738              "do Argument Body".
739
740              See also: ann_c_seq/3, is_c_seq/1,  seq_arg/1,  seq_body/1,  up‐
741              date_c_seq/3.
742
743       c_string(Value::string()) -> c_literal()
744
745              Creates  an  abstract  string literal. Equivalent to creating an
746              abstract list  of  the  corresponding  character  literals  (cf.
747              is_c_string/1),  but  is  typically  more efficient. The lexical
748              representation of a string is ""Chars"", where Chars  is  a  se‐
749              quence of printing characters or spaces.
750
751              See     also:     ann_c_string/2,    c_char/1,    is_c_string/1,
752              is_print_string/1, string_lit/1, string_val/1.
753
754       c_try(Expr::cerl(),  Vs::[cerl()],  Body::cerl(),  Evs::[cerl()],  Han‐
755       dler::cerl()) -> c_try()
756
757              Creates  an  abstract  try-expression. If Variables is [V1, ...,
758              Vn] and ExceptionVars is [X1, ..., Xm],  the  result  represents
759              "try  Argument  of  <V1, ..., Vn> -> Body catch <X1, ..., Xm> ->
760              Handler". All the Vi and Xi must have type var.
761
762              See  also:  ann_c_try/6,   c_catch/1,   is_c_try/1,   try_arg/1,
763              try_body/1, try_vars/1, update_c_try/6.
764
765       c_tuple(Es::[cerl()]) -> c_tuple() | c_literal()
766
767              Creates an abstract tuple. If Elements is [E1, ..., En], the re‐
768              sult represents "{E1, ..., En}". Note that if all nodes in  Ele‐
769              ments  have  type literal, or if Elements is empty, then the re‐
770              sult will also have type literal and annotations on nodes in El‐
771              ements are lost.
772
773              Recall  that  Erlang  has distinct 1-tuples, i.e., {X} is always
774              distinct from X itself.
775
776              See also: ann_c_tuple/2, c_tuple_skel/1, is_c_tuple/1, tuple_ar‐
777              ity/1, tuple_es/1, update_c_tuple/2.
778
779       c_tuple_skel(Es::[cerl()]) -> c_tuple()
780
781              Creates  an abstract tuple skeleton. Does not fold constant lit‐
782              erals, i.e., the result  always  has  type  tuple,  representing
783              "{E1, ..., En}", if Elements is [E1, ..., En].
784
785              This  function  is  occasionally  useful when it is necessary to
786              have annotations on the subnodes of a tuple node, even when  all
787              the  subnodes  are  constant literals. Note however that is_lit‐
788              eral/1 will yield false and concrete/1 will fail if  passed  the
789              result from this function.
790
791              fold_literal/1  can  be used to revert a node to the normal-form
792              representation.
793
794              See also: ann_c_tuple_skel/2, c_tuple/1,  concrete/1,  fold_lit‐
795              eral/1,  is_c_tuple/1,  is_literal/1,  tuple_es/1,  update_c_tu‐
796              ple_skel/2.
797
798       c_values(Es::[cerl()]) -> c_values()
799
800              Creates an abstract value list. If Elements is  [E1,  ...,  En],
801              the result represents "<E1, ..., En>".
802
803              See also: ann_c_values/2, is_c_values/1, update_c_values/2, val‐
804              ues_arity/1, values_es/1.
805
806       c_var(Name::var_name()) -> c_var()
807
808              Creates an abstract variable. A variable is  identified  by  its
809              name, given by the Name parameter.
810
811              If a name is given by a single atom, it should either be a "sim‐
812              ple" atom which does not need to be single-quoted in Erlang,  or
813              otherwise  its  print  name should correspond to a proper Erlang
814              variable, i.e., begin with an uppercase character or  an  under‐
815              score.  Names  on  the form {A, N} represent function name vari‐
816              ables "A/N"; these are special variables which may be bound only
817              in  the  function  definitions of a module or a letrec. They may
818              not be bound in let expressions and cannot occur in clause  pat‐
819              terns.  The atom A in a function name may be any atom; the inte‐
820              ger N must be nonnegative.  The  functions  c_fname/2  etc.  are
821              utilities for handling function name variables.
822
823              When  printing variable names, they must have the form of proper
824              Core Erlang variables and function names. E.g.,  a  name  repre‐
825              sented  by an integer such as 42 could be formatted as "_42", an
826              atom 'Xxx' simply as "Xxx", and an atom foo as "_foo".  However,
827              one  must  assure  that  any  two valid distinct names are never
828              mapped to the same strings. Tuples such as {foo, 2} representing
829              function  names  can  simply  by formatted as "'foo'/2", with no
830              risk of conflicts.
831
832              See  also:  ann_c_var/2,  c_fname/2,   c_letrec/2,   c_module/4,
833              is_c_var/1, update_c_var/2, var_name/1.
834
835       call_args(Node::c_call()) -> [cerl()]
836
837              Returns  the list of argument subtrees of an abstract inter-mod‐
838              ule call.
839
840              See also: c_call/3, call_arity/1.
841
842       call_arity(Node::c_call()) -> arity()
843
844              Returns the number of argument subtrees of  an  abstract  inter-
845              module call.
846
847              Note:  this is equivalent to length(call_args(Node)), but poten‐
848              tially more efficient.
849
850              See also: c_call/3, call_args/1.
851
852       call_module(Node::c_call()) -> cerl()
853
854              Returns the module subtree of an abstract inter-module call.
855
856              See also: c_call/3.
857
858       call_name(Node::c_call()) -> cerl()
859
860              Returns the name subtree of an abstract inter-module call.
861
862              See also: c_call/3.
863
864       case_arg(Node::c_case()) -> cerl()
865
866              Returns the argument subtree of an abstract case-expression.
867
868              See also: c_case/2.
869
870       case_arity(Node::c_case()) -> non_neg_integer()
871
872              Equivalent to clause_arity(hd(case_clauses(Node))),  but  poten‐
873              tially more efficient.
874
875              See also: c_case/2, case_clauses/1, clause_arity/1.
876
877       case_clauses(Node::c_case()) -> [cerl()]
878
879              Returns  the list of clause subtrees of an abstract case-expres‐
880              sion.
881
882              See also: c_case/2, case_arity/1.
883
884       catch_body(Node::c_catch()) -> cerl()
885
886              Returns the body subtree of an abstract catch-expression.
887
888              See also: c_catch/1.
889
890       char_lit(Node::c_literal()) -> nonempty_string()
891
892              Returns the literal string represented by an abstract character.
893              This  includes  a leading $ character. Currently, all characters
894              that are not in the set of ISO 8859-1 (Latin-1) "printing" char‐
895              acters will be escaped.
896
897              See also: c_char/1.
898
899       char_val(Node::c_literal()) -> char()
900
901              Returns the value represented by an abstract character literal.
902
903              See also: c_char/1.
904
905       clause_arity(Node::c_clause()) -> non_neg_integer()
906
907              Returns the number of pattern subtrees of an abstract clause.
908
909              Note:  this  is equivalent to length(clause_pats(Node)), but po‐
910              tentially more efficient.
911
912              See also: c_clause/3, clause_pats/1.
913
914       clause_body(Node::c_clause()) -> cerl()
915
916              Returns the body subtree of an abstract clause.
917
918              See also: c_clause/3.
919
920       clause_guard(Node::c_clause()) -> cerl()
921
922              Returns the guard subtree of an abstract clause.
923
924              See also: c_clause/3.
925
926       clause_pats(Node::c_clause()) -> [cerl()]
927
928              Returns the list of pattern subtrees of an abstract clause.
929
930              See also: c_clause/3, clause_arity/1.
931
932       clause_vars(Clause::c_clause()) -> [cerl()]
933
934              Returns the list of all abstract variables in the patterns of an
935              abstract clause. The order of listing is not defined.
936
937              See also: c_clause/3, pat_list_vars/1.
938
939       concrete(C_literal::c_literal()) -> term()
940
941              Returns  the Erlang term represented by a syntax tree. An excep‐
942              tion is thrown if Node does not represent a literal term.
943
944              Note: This is a constant time operation.
945
946              See also: abstract/1, is_literal/1.
947
948       cons_hd(C_cons::c_cons() | c_literal()) -> cerl()
949
950              Returns the head subtree of an abstract list constructor.
951
952              See also: c_cons/2.
953
954       cons_tl(C_cons::c_cons() | c_literal()) -> cerl()
955
956              Returns the tail subtree of an abstract list constructor.
957
958              Recall that the tail does not  necessarily  represent  a  proper
959              list.
960
961              See also: c_cons/2.
962
963       copy_ann(Source::cerl(), Target::cerl()) -> cerl()
964
965              Copies the list of user annotations from Source to Target.
966
967              Note:  this  is  equivalent to set_ann(Target, get_ann(Source)),
968              but potentially more efficient.
969
970              See also: get_ann/1, set_ann/2.
971
972       data_arity(C_literal::c_lct()) -> non_neg_integer()
973
974              Returns the number of subtrees of a data constructor node.  This
975              is equivalent to length(data_es(Node)), but potentially more ef‐
976              ficient.
977
978              See also: data_es/1, is_data/1.
979
980       data_es(C_literal::c_lct()) -> [cerl()]
981
982              Returns the list of subtrees of a data constructor node. If  the
983              arity of the constructor is zero, the result is the empty list.
984
985              Note:  if data_type(Node) is cons, the number of subtrees is ex‐
986              actly two. If data_type(Node) is {atomic, Value}, the number  of
987              subtrees is zero.
988
989              See also: data_arity/1, data_type/1, is_data/1, make_data/2.
990
991       data_type(C_literal::c_lct()) -> dtype()
992
993              Returns  a  type  descriptor  for  a data constructor node. (Cf.
994              is_data/1.) This is mainly useful for comparing  types  and  for
995              constructing  new  nodes  of the same type (cf. make_data/2). If
996              Node represents an integer, floating-point number, atom or empty
997              list, the result is {atomic, Value}, where Value is the value of
998              concrete(Node), otherwise the result is either cons or tuple.
999
1000              Type descriptors can be compared for equality or order  (in  the
1001              Erlang  term  order),  but  remember  that floating-point values
1002              should in general never be tested for equality.
1003
1004              See also: concrete/1, is_data/1, make_data/2, type/1.
1005
1006       float_lit(Node::c_literal()) -> string()
1007
1008              Returns the numeral string represented by a floating-point  lit‐
1009              eral node.
1010
1011              See also: c_float/1.
1012
1013       float_val(Node::c_literal()) -> float()
1014
1015              Returns the value represented by a floating-point literal node.
1016
1017              See also: c_float/1.
1018
1019       fname_arity(C_var::c_var()) -> arity()
1020
1021              Returns the arity part of an abstract function name variable.
1022
1023              See also: c_fname/2, fname_id/1.
1024
1025       fname_id(C_var::c_var()) -> atom()
1026
1027              Returns  the  identifier part of an abstract function name vari‐
1028              able.
1029
1030              See also: c_fname/2, fname_arity/1.
1031
1032       fold_literal(Node::cerl()) -> cerl()
1033
1034              Assures that literals have a compact representation. This is oc‐
1035              casionally   useful  if  c_cons_skel/2,  c_tuple_skel/1  or  un‐
1036              fold_literal/1 were used in the construction of  Node,  and  you
1037              want  to  revert to the normal "folded" representation of liter‐
1038              als. If Node represents a tuple or list  constructor,  its  ele‐
1039              ments  are  rewritten recursively, and the node is reconstructed
1040              using c_cons/2 or c_tuple/1, respectively;  otherwise,  Node  is
1041              not changed.
1042
1043              See  also:  c_cons/2,  c_cons_skel/2, c_tuple/1, c_tuple_skel/1,
1044              is_literal/1, unfold_literal/1.
1045
1046       from_records(Node::cerl()) -> cerl()
1047
1048              Translates an explicit record representation to a  corresponding
1049              abstract  syntax  tree.  The  records  are  defined  in the file
1050              "core_parse.hrl".
1051
1052              See also: to_records/1, type/1.
1053
1054       fun_arity(Node::c_fun()) -> arity()
1055
1056              Returns the number of parameter subtrees of an abstract  fun-ex‐
1057              pression.
1058
1059              Note:  this  is equivalent to length(fun_vars(Node)), but poten‐
1060              tially more efficient.
1061
1062              See also: c_fun/2, fun_vars/1.
1063
1064       fun_body(Node::c_fun()) -> cerl()
1065
1066              Returns the body subtree of an abstract fun-expression.
1067
1068              See also: c_fun/2.
1069
1070       fun_vars(Node::c_fun()) -> [cerl()]
1071
1072              Returns the list of parameter subtrees of  an  abstract  fun-ex‐
1073              pression.
1074
1075              See also: c_fun/2, fun_arity/1.
1076
1077       get_ann(Node::cerl()) -> [term()]
1078
1079              Returns  the  list  of user annotations associated with a syntax
1080              tree node. For a newly created node, this is the empty list. The
1081              annotations may be any terms.
1082
1083              See also: set_ann/2.
1084
1085       int_lit(Node::c_literal()) -> string()
1086
1087              Returns  the  numeral  string  represented by an integer literal
1088              node.
1089
1090              See also: c_int/1.
1091
1092       int_val(Node::c_literal()) -> integer()
1093
1094              Returns the value represented by an integer literal node.
1095
1096              See also: c_int/1.
1097
1098       is_c_alias(C_alias::cerl()) -> boolean()
1099
1100              Returns true if Node is an  abstract  pattern  alias,  otherwise
1101              false.
1102
1103              See also: c_alias/2.
1104
1105       is_c_apply(C_apply::cerl()) -> boolean()
1106
1107              Returns true if Node is an abstract function application, other‐
1108              wise false.
1109
1110              See also: c_apply/2.
1111
1112       is_c_atom(C_literal::cerl()) -> boolean()
1113
1114              Returns true if  Node  represents  an  atom  literal,  otherwise
1115              false.
1116
1117              See also: c_atom/1.
1118
1119       is_c_binary(C_binary::cerl()) -> boolean()
1120
1121              Returns  true  if Node is an abstract binary-template; otherwise
1122              false.
1123
1124              See also: c_binary/1.
1125
1126       is_c_bitstr(C_bitstr::cerl()) -> boolean()
1127
1128              Returns true if Node is an abstract bit-string template;  other‐
1129              wise false.
1130
1131              See also: c_bitstr/5.
1132
1133       is_c_call(C_call::cerl()) -> boolean()
1134
1135              Returns  true  if  Node is an abstract inter-module call expres‐
1136              sion; otherwise false.
1137
1138              See also: c_call/3.
1139
1140       is_c_case(C_case::cerl()) -> boolean()
1141
1142              Returns true if Node is an abstract  case-expression;  otherwise
1143              false.
1144
1145              See also: c_case/2.
1146
1147       is_c_catch(C_catch::cerl()) -> boolean()
1148
1149              Returns  true if Node is an abstract catch-expression, otherwise
1150              false.
1151
1152              See also: c_catch/1.
1153
1154       is_c_char(C_literal::c_literal()) -> boolean()
1155
1156              Returns true if Node may represent a character  literal,  other‐
1157              wise false.
1158
1159              If the local implementation of Erlang defines char() as a subset
1160              of integer(), then is_c_int(Node) will also yield true.
1161
1162              See also: c_char/1, is_print_char/1.
1163
1164       is_c_clause(C_clause::cerl()) -> boolean()
1165
1166              Returns true if Node is an abstract clause, otherwise false.
1167
1168              See also: c_clause/3.
1169
1170       is_c_cons(C_cons::cerl()) -> boolean()
1171
1172              Returns true if Node is an abstract list constructor,  otherwise
1173              false.
1174
1175       is_c_float(C_literal::cerl()) -> boolean()
1176
1177              Returns true if Node represents a floating-point literal, other‐
1178              wise false.
1179
1180              See also: c_float/1.
1181
1182       is_c_fname(C_var::cerl()) -> boolean()
1183
1184              Returns true if Node is an abstract function name variable, oth‐
1185              erwise false.
1186
1187              See also: c_fname/2, c_var/1, var_name/1.
1188
1189       is_c_fun(C_fun::cerl()) -> boolean()
1190
1191              Returns  true  if  Node is an abstract fun-expression, otherwise
1192              false.
1193
1194              See also: c_fun/2.
1195
1196       is_c_int(C_literal::cerl()) -> boolean()
1197
1198              Returns true if Node represents an  integer  literal,  otherwise
1199              false.
1200
1201              See also: c_int/1.
1202
1203       is_c_let(C_let::cerl()) -> boolean()
1204
1205              Returns  true  if  Node is an abstract let-expression, otherwise
1206              false.
1207
1208              See also: c_let/3.
1209
1210       is_c_letrec(C_letrec::cerl()) -> boolean()
1211
1212              Returns true if Node is an abstract letrec-expression, otherwise
1213              false.
1214
1215              See also: c_letrec/2.
1216
1217       is_c_list(C_cons::cerl()) -> boolean()
1218
1219              Returns  true if Node represents a proper list, otherwise false.
1220              A proper list is either the empty list [], or a cons cell  [Head
1221              | Tail], where recursively Tail is a proper list.
1222
1223              Note:  Because Node is a syntax tree, the actual run-time values
1224              corresponding to its subtrees may often  be  partially  or  com‐
1225              pletely  unknown.  Thus,  if  Node  represents e.g. "[... | Ns]"
1226              (where Ns is a variable), then the function will  return  false,
1227              because  it  is  not known whether Ns will be bound to a list at
1228              run-time. If Node instead represents e.g. "[1, 2, 3]" or  "[A  |
1229              []]", then the function will return true.
1230
1231              See also: c_cons/2, c_nil/0, list_elements/1, list_length/1.
1232
1233       is_c_map(C_map::cerl()) -> boolean()
1234
1235              Returns  true  if Node is an abstract map constructor, otherwise
1236              false.
1237
1238       is_c_map_empty(C_map::c_map() | c_literal()) -> boolean()
1239
1240       is_c_map_pattern(C_map::c_map()) -> boolean()
1241
1242       is_c_module(C_module::cerl()) -> boolean()
1243
1244              Returns true if Node is an abstract module definition, otherwise
1245              false.
1246
1247              See also: type/1.
1248
1249       is_c_nil(C_literal::cerl()) -> boolean()
1250
1251              Returns true if Node is an abstract empty list, otherwise false.
1252
1253       is_c_primop(C_primop::cerl()) -> boolean()
1254
1255              Returns  true  if  Node is an abstract primitive operation call,
1256              otherwise false.
1257
1258              See also: c_primop/2.
1259
1260       is_c_receive(C_receive::cerl()) -> boolean()
1261
1262              Returns true if Node is an abstract  receive-expression,  other‐
1263              wise false.
1264
1265              See also: c_receive/3.
1266
1267       is_c_seq(C_seq::cerl()) -> boolean()
1268
1269              Returns  true if Node is an abstract sequencing expression, oth‐
1270              erwise false.
1271
1272              See also: c_seq/2.
1273
1274       is_c_string(C_literal::cerl()) -> boolean()
1275
1276              Returns true if Node may represent a string  literal,  otherwise
1277              false.   Strings   are  defined  as  lists  of  characters;  see
1278              is_c_char/1 for details.
1279
1280              See also: c_string/1, is_c_char/1, is_print_string/1.
1281
1282       is_c_try(C_try::cerl()) -> boolean()
1283
1284              Returns true if Node is an  abstract  try-expression,  otherwise
1285              false.
1286
1287              See also: c_try/5.
1288
1289       is_c_tuple(C_tuple::cerl()) -> boolean()
1290
1291              Returns true if Node is an abstract tuple, otherwise false.
1292
1293              See also: c_tuple/1.
1294
1295       is_c_values(C_values::cerl()) -> boolean()
1296
1297              Returns true if Node is an abstract value list; otherwise false.
1298
1299              See also: c_values/1.
1300
1301       is_c_var(C_var::cerl()) -> boolean()
1302
1303              Returns true if Node is an abstract variable, otherwise false.
1304
1305              See also: c_var/1.
1306
1307       is_data(C_literal::cerl()) -> boolean()
1308
1309              Returns  true  if  Node represents a data constructor, otherwise
1310              false. Data constructors are cons cells, tuples, and atomic lit‐
1311              erals.
1312
1313              See also: data_arity/1, data_es/1, data_type/1.
1314
1315       is_leaf(Node::cerl()) -> boolean()
1316
1317              Returns  true  if Node is a leaf node, otherwise false. The cur‐
1318              rent leaf node types are literal and var.
1319
1320              Note: all literals (cf. is_literal/1) are leaf  nodes,  even  if
1321              they  represent structured (constant) values such as {foo, [bar,
1322              baz]}. Also note that variables are leaf nodes but not literals.
1323
1324              See also: is_literal/1, type/1.
1325
1326       is_literal(C_literal::cerl()) -> boolean()
1327
1328              Returns true if Node represents a literal term, otherwise false.
1329              This  function  returns  true  if  and only if the value of con‐
1330              crete(Node) is defined.
1331
1332              Note: This is a constant time operation.
1333
1334              See also: abstract/1, concrete/1, fold_literal/1.
1335
1336       is_literal_term(T::term()) -> boolean()
1337
1338              Returns true if Term can be represented as a literal,  otherwise
1339              false.  This  function  takes  time  proportional to the size of
1340              Term.
1341
1342              See also: abstract/1.
1343
1344       is_print_char(C_literal::cerl()) -> boolean()
1345
1346              Returns true if Node may represent a "printing" character,  oth‐
1347              erwise  false. (Cf. is_c_char/1.) A "printing" character has ei‐
1348              ther a given graphical representation, or a "named"  escape  se‐
1349              quence  such as "\n". Currently, only ISO 8859-1 (Latin-1) char‐
1350              acter values are recognized.
1351
1352              See also: c_char/1, is_c_char/1.
1353
1354       is_print_string(C_literal::cerl()) -> boolean()
1355
1356              Returns true if Node may represent a string  literal  containing
1357              only  "printing"  characters, otherwise false. See is_c_string/1
1358              and is_print_char/1 for  details.  Currently,  only  ISO  8859-1
1359              (Latin-1) character values are recognized.
1360
1361              See also: c_string/1, is_c_string/1, is_print_char/1.
1362
1363       let_arg(Node::c_let()) -> cerl()
1364
1365              Returns the argument subtree of an abstract let-expression.
1366
1367              See also: c_let/3.
1368
1369       let_arity(Node::c_let()) -> non_neg_integer()
1370
1371              Returns  the  number  of left-hand side variables of an abstract
1372              let-expression.
1373
1374              Note: this is equivalent to length(let_vars(Node)),  but  poten‐
1375              tially more efficient.
1376
1377              See also: c_let/3, let_vars/1.
1378
1379       let_body(Node::c_let()) -> cerl()
1380
1381              Returns the body subtree of an abstract let-expression.
1382
1383              See also: c_let/3.
1384
1385       let_vars(Node::c_let()) -> [cerl()]
1386
1387              Returns the list of left-hand side variables of an abstract let-
1388              expression.
1389
1390              See also: c_let/3, let_arity/1.
1391
1392       letrec_body(Node::c_letrec()) -> cerl()
1393
1394              Returns the body subtree of an abstract letrec-expression.
1395
1396              See also: c_letrec/2.
1397
1398       letrec_defs(Node::c_letrec()) -> [{cerl(), cerl()}]
1399
1400              Returns the list of definitions of  an  abstract  letrec-expres‐
1401              sion.  If  Node represents "letrec V1 = F1 ... Vn = Fn in Body",
1402              the returned value is [{V1, F1}, ..., {Vn, Fn}].
1403
1404              See also: c_letrec/2.
1405
1406       letrec_vars(Node::c_letrec()) -> [cerl()]
1407
1408              Returns the list of left-hand side function variable subtrees of
1409              a letrec-expression. If Node represents "letrec V1 = F1 ... Vn =
1410              Fn in Body", the returned value is [V1, ..., Vn].
1411
1412              See also: c_letrec/2.
1413
1414       list_elements(C_cons::c_cons() | c_literal()) -> [cerl()]
1415
1416              Returns the list of element subtrees of an abstract  list.  Node
1417              must  represent a proper list. E.g., if Node represents "[X1, X2
1418              | [X3, X4 | []]", then list_elements(Node) yields the list  [X1,
1419              X2, X3, X4].
1420
1421              See   also:   c_cons/2,   c_nil/0,  is_c_list/1,  list_length/1,
1422              make_list/2.
1423
1424       list_length(L::c_cons() | c_literal()) -> non_neg_integer()
1425
1426              Returns the number of element subtrees of an abstract list. Node
1427              must  represent  a  proper list. E.g., if Node represents "[X1 |
1428              [X2, X3 | [X4, X5, X6]]]", then  list_length(Node)  returns  the
1429              integer 6.
1430
1431              Note: this is equivalent to length(list_elements(Node)), but po‐
1432              tentially more efficient.
1433
1434              See also: c_cons/2, c_nil/0, is_c_list/1, list_elements/1.
1435
1436       make_data(CType::dtype(), Es::[cerl()]) -> c_lct()
1437
1438              Creates a data constructor node with the specified type and sub‐
1439              trees.  (Cf.  data_type/1.) An exception is thrown if the length
1440              of Elements is invalid for the given Type; see data_es/1 for ar‐
1441              ity constraints on constructor types.
1442
1443              See     also:     ann_make_data/3,    data_es/1,    data_type/1,
1444              make_data_skel/2, update_data/3.
1445
1446       make_data_skel(CType::dtype(), Es::[cerl()]) -> c_lct()
1447
1448              Like  make_data/2,   but   analogous   to   c_tuple_skel/1   and
1449              c_cons_skel/2.
1450
1451              See  also:  ann_make_data_skel/3, c_cons_skel/2, c_tuple_skel/1,
1452              make_data/2, update_data_skel/3.
1453
1454       make_list(List::[cerl()]) -> cerl()
1455
1456              Equivalent to make_list(List, none).
1457
1458       make_list(List::[cerl()], Tail::cerl() | none) -> cerl()
1459
1460              Creates an abstract list from the elements in List and  the  op‐
1461              tional  Tail.  If Tail is none, the result will represent a nil-
1462              terminated list, otherwise it represents "[... | Tail]".
1463
1464              See also: ann_make_list/3, c_cons/2,  c_nil/0,  list_elements/1,
1465              update_list/3.
1466
1467       make_tree(Type::ctype(), Gs::[[cerl()], ...]) -> cerl()
1468
1469              Creates  a  syntax  tree  with the given type and subtrees. Type
1470              must be a node type name (cf. type/1) that  does  not  denote  a
1471              leaf  node  type (cf. is_leaf/1). Groups must be a nonempty list
1472              of groups of syntax trees, representing the subtrees of  a  node
1473              of the given type, in left-to-right order as they would occur in
1474              the printed program text, grouped by category as  done  by  sub‐
1475              trees/1.
1476
1477              The  result  of  ann_make_tree(get_ann(Node),  type(Node),  sub‐
1478              trees(Node)) (cf. update_tree/2) represents the same source code
1479              text as the original Node, assuming that subtrees(Node) yields a
1480              nonempty list. However, it does not necessarily have  the  exact
1481              same data representation as Node.
1482
1483              See  also:  ann_make_tree/3,  is_leaf/1, subtrees/1, type/1, up‐
1484              date_tree/2.
1485
1486       map_arg(C_literal::c_map() | c_literal()) -> c_map() | c_literal()
1487
1488       map_es(C_literal::c_map() | c_literal()) -> [c_map_pair()]
1489
1490       map_pair_key(C_map_pair::c_map_pair()) -> cerl()
1491
1492       map_pair_op(C_map_pair::c_map_pair()) -> map_op()
1493
1494       map_pair_val(C_map_pair::c_map_pair()) -> cerl()
1495
1496       meta(Node::cerl()) -> cerl()
1497
1498              Creates a meta-representation of a syntax tree. The result  rep‐
1499              resents  an  Erlang  expression  "MetaTree" which, if evaluated,
1500              will yield a new syntax tree representing the same  source  code
1501              text  as  Tree  (although  the actual data representation may be
1502              different). The expression represented by MetaTree is  implemen‐
1503              tation  independent  with  regard to the data structures used by
1504              the abstract syntax tree implementation.
1505
1506              Any node in Tree whose node type is var (cf. type/1), and  whose
1507              list  of annotations (cf. get_ann/1) contains the atom meta_var,
1508              will remain unchanged in the resulting tree, except that exactly
1509              one occurrence of meta_var is removed from its annotation list.
1510
1511              The  main  use  of  the  function  meta/1 is to transform a data
1512              structure Tree, which represents a piece of program code, into a
1513              form that is representation independent when printed. E.g., sup‐
1514              pose Tree represents a variable  named  "V".  Then  (assuming  a
1515              function   print/1   for   printing  syntax  trees),  evaluating
1516              print(abstract(Tree)) - simply using abstract/1 to map  the  ac‐
1517              tual  data  structure  onto a syntax tree representation - would
1518              output a string that  might  look  something  like  "{var,  ...,
1519              'V'}", which is obviously dependent on the implementation of the
1520              abstract syntax trees. This could e.g. be useful for  caching  a
1521              syntax  tree  in  a  file. However, in some situations like in a
1522              program generator generator (with two "generator"),  it  may  be
1523              unacceptable.  Using  print(meta(Tree))  instead  would output a
1524              representation independent syntax tree generating expression; in
1525              the above case, something like "cerl:c_var('V')".
1526
1527              The  implementation  tries to generate compact code with respect
1528              to literals and lists.
1529
1530              See also: abstract/1, get_ann/1, type/1.
1531
1532       module_attrs(Node::c_module()) -> [{cerl(), cerl()}]
1533
1534              Returns the list of pairs of attribute key/value subtrees of  an
1535              abstract module definition.
1536
1537              See also: c_module/4.
1538
1539       module_defs(Node::c_module()) -> [{cerl(), cerl()}]
1540
1541              Returns  the  list of function definitions of an abstract module
1542              definition.
1543
1544              See also: c_module/4.
1545
1546       module_exports(Node::c_module()) -> [cerl()]
1547
1548              Returns the list of exports subtrees of an abstract module defi‐
1549              nition.
1550
1551              See also: c_module/4.
1552
1553       module_name(Node::c_module()) -> cerl()
1554
1555              Returns the name subtree of an abstract module definition.
1556
1557              See also: c_module/4.
1558
1559       module_vars(Node::c_module()) -> [cerl()]
1560
1561              Returns the list of left-hand side function variable subtrees of
1562              an abstract module definition.
1563
1564              See also: c_module/4.
1565
1566       pat_list_vars(Ps::[cerl()]) -> [cerl()]
1567
1568              Returns the list of all abstract variables  in  the  given  pat‐
1569              terns.  An  exception is thrown if some element in Patterns does
1570              not represent a well-formed Core Erlang clause pattern. The  or‐
1571              der of listing is not defined.
1572
1573              See also: clause_vars/1, pat_vars/1.
1574
1575       pat_vars(Node::cerl()) -> [cerl()]
1576
1577              Returns  the list of all abstract variables in a pattern. An ex‐
1578              ception is thrown if Node does not represent a well-formed  Core
1579              Erlang clause pattern. The order of listing is not defined.
1580
1581              See also: clause_vars/1, pat_list_vars/1.
1582
1583       primop_args(Node::c_primop()) -> [cerl()]
1584
1585              Returns  the  list of argument subtrees of an abstract primitive
1586              operation call.
1587
1588              See also: c_primop/2, primop_arity/1.
1589
1590       primop_arity(Node::c_primop()) -> arity()
1591
1592              Returns the number of argument subtrees of an abstract primitive
1593              operation call.
1594
1595              Note:  this  is equivalent to length(primop_args(Node)), but po‐
1596              tentially more efficient.
1597
1598              See also: c_primop/2, primop_args/1.
1599
1600       primop_name(Node::c_primop()) -> cerl()
1601
1602              Returns the name subtree  of  an  abstract  primitive  operation
1603              call.
1604
1605              See also: c_primop/2.
1606
1607       receive_action(Node::c_receive()) -> cerl()
1608
1609              Returns the action subtree of an abstract receive-expression.
1610
1611              See also: c_receive/3.
1612
1613       receive_clauses(Node::c_receive()) -> [cerl()]
1614
1615              Returns  the  list of clause subtrees of an abstract receive-ex‐
1616              pression.
1617
1618              See also: c_receive/3.
1619
1620       receive_timeout(Node::c_receive()) -> cerl()
1621
1622              Returns the timeout subtree of an abstract receive-expression.
1623
1624              See also: c_receive/3.
1625
1626       seq_arg(Node::c_seq()) -> cerl()
1627
1628              Returns the argument subtree of an abstract  sequencing  expres‐
1629              sion.
1630
1631              See also: c_seq/2.
1632
1633       seq_body(Node::c_seq()) -> cerl()
1634
1635              Returns the body subtree of an abstract sequencing expression.
1636
1637              See also: c_seq/2.
1638
1639       set_ann(Node::cerl(), List::[term()]) -> cerl()
1640
1641              Sets the list of user annotations of Node to Annotations.
1642
1643              See also: add_ann/2, copy_ann/2, get_ann/1.
1644
1645       string_lit(Node::c_literal()) -> nonempty_string()
1646
1647              Returns  the  literal  string represented by an abstract string.
1648              This includes surrounding double-quote  characters  "...".  Cur‐
1649              rently,  characters  that  are  not  in  the  set  of ISO 8859-1
1650              (Latin-1) "printing" characters will be escaped, except for spa‐
1651              ces.
1652
1653              See also: c_string/1.
1654
1655       string_val(Node::c_literal()) -> string()
1656
1657              Returns the value represented by an abstract string literal.
1658
1659              See also: c_string/1.
1660
1661       subtrees(T::cerl()) -> [[cerl()]]
1662
1663              Returns the grouped list of all subtrees of a node. If Node is a
1664              leaf node (cf. is_leaf/1), this is the empty list, otherwise the
1665              result  is  always a nonempty list, containing the lists of sub‐
1666              trees of Node, in left-to-right  order  as  they  occur  in  the
1667              printed program text, and grouped by category. Often, each group
1668              contains only a single subtree.
1669
1670              Depending on the type of Node, the size of some  groups  may  be
1671              variable  (e.g.,  the  group consisting of all the elements of a
1672              tuple), while others always contain the same number of  elements
1673              -  usually  exactly one (e.g., the group containing the argument
1674              expression of a case-expression). Note, however, that the  exact
1675              structure of the returned list (for a given node type) should in
1676              general not be depended upon,  since  it  might  be  subject  to
1677              change without notice.
1678
1679              The   function   subtrees/1   and   the   constructor  functions
1680              make_tree/2 and update_tree/2 can be a great help if  one  wants
1681              to  traverse a syntax tree, visiting all its subtrees, but treat
1682              nodes of the tree in a uniform way in most or all  cases.  Using
1683              these  functions  makes  this simple, and also assures that your
1684              code is not overly sensitive to extensions of  the  syntax  tree
1685              data type, because any node types not explicitly handled by your
1686              code can be left to a default case.
1687
1688              For example:
1689
1690                  postorder(F, Tree) ->
1691                      F(case subtrees(Tree) of
1692                          [] -> Tree;
1693                          List -> update_tree(Tree,
1694                                              [[postorder(F, Subtree)
1695                                                || Subtree <- Group]
1696                                               || Group <- List])
1697                        end).
1698
1699
1700              maps the function F on Tree and all its subtrees, doing a  post-
1701              order  traversal  of  the  syntax  tree.  (Note  the  use of up‐
1702              date_tree/2 to preserve  annotations.)  For  a  simple  function
1703              like:
1704
1705                  f(Node) ->
1706                      case type(Node) of
1707                          atom -> atom("a_" ++ atom_name(Node));
1708                          _ -> Node
1709                      end.
1710
1711
1712              the  call  postorder(fun f/1, Tree) will yield a new representa‐
1713              tion of Tree in which all atom names have been extended with the
1714              prefix  "a_",  but nothing else (including annotations) has been
1715              changed.
1716
1717              See also: is_leaf/1, make_tree/2, update_tree/2.
1718
1719       to_records(Node::cerl()) -> cerl()
1720
1721              Translates an abstract syntax tree to a  corresponding  explicit
1722              record  representation.  The  records  are  defined  in the file
1723              "cerl.hrl".
1724
1725              See also: from_records/1, type/1.
1726
1727       try_arg(Node::c_try()) -> cerl()
1728
1729              Returns the expression subtree of an abstract try-expression.
1730
1731              See also: c_try/5.
1732
1733       try_body(Node::c_try()) -> cerl()
1734
1735              Returns the success body subtree of an abstract try-expression.
1736
1737              See also: c_try/5.
1738
1739       try_evars(Node::c_try()) -> [cerl()]
1740
1741              Returns the list of exception variable subtrees of  an  abstract
1742              try-expression.
1743
1744              See also: c_try/5.
1745
1746       try_handler(Node::c_try()) -> cerl()
1747
1748              Returns  the  exception  body subtree of an abstract try-expres‐
1749              sion.
1750
1751              See also: c_try/5.
1752
1753       try_vars(Node::c_try()) -> [cerl()]
1754
1755              Returns the list of success variable  subtrees  of  an  abstract
1756              try-expression.
1757
1758              See also: c_try/5.
1759
1760       tuple_arity(C_tuple::c_tuple() | c_literal()) -> non_neg_integer()
1761
1762              Returns the number of element subtrees of an abstract tuple.
1763
1764              Note:  this  is equivalent to length(tuple_es(Node)), but poten‐
1765              tially more efficient.
1766
1767              See also: c_tuple/1, tuple_es/1.
1768
1769       tuple_es(C_tuple::c_tuple() | c_literal()) -> [cerl()]
1770
1771              Returns the list of element subtrees of an abstract tuple.
1772
1773              See also: c_tuple/1.
1774
1775       type(C_alias::cerl()) -> ctype()
1776
1777              Returns the type tag of Node. Current node types are:
1778
1779              alias apply binary bitstr call case catch clause
1780              cons fun let letrec literal map map_pair module
1781              primop receive seq try tuple values var
1782
1783
1784              Note: The name of the primary constructor function  for  a  node
1785              type  is  always  the name of the type itself, prefixed by "c_";
1786              recognizer predicates are correspondingly prefixed  by  "is_c_".
1787              Furthermore,   to  simplify  preservation  of  annotations  (cf.
1788              get_ann/1), there are analogous constructor  functions  prefixed
1789              by  "ann_c_" and "update_c_", for setting the annotation list of
1790              the new node to either a specific value or to the annotations of
1791              an existing node, respectively.
1792
1793              See  also:  abstract/1, c_alias/2, c_apply/2, c_binary/1, c_bit‐
1794              str/5,  c_call/3,  c_case/2,  c_catch/1,  c_clause/3,  c_cons/2,
1795              c_fun/2,  c_let/3,  c_letrec/2,  c_module/3,  c_primop/2,  c_re‐
1796              ceive/1,  c_seq/2,  c_try/5,  c_tuple/1,  c_values/1,   c_var/1,
1797              data_type/1,   from_records/1,  get_ann/1,  meta/1,  subtrees/1,
1798              to_records/1.
1799
1800       unfold_literal(Node::cerl()) -> cerl()
1801
1802              Assures that literals have a fully expanded  representation.  If
1803              Node  represents  a  literal tuple or list constructor, its ele‐
1804              ments are rewritten recursively, and the node  is  reconstructed
1805              using  c_cons_skel/2 or c_tuple_skel/1, respectively; otherwise,
1806              Node is not changed. The fold_literal/1 can be used to revert to
1807              the normal compact representation.
1808
1809              See  also:  c_cons/2,  c_cons_skel/2, c_tuple/1, c_tuple_skel/1,
1810              fold_literal/1, is_literal/1.
1811
1812       update_c_alias(Node::c_alias(),   Var::cerl(),   Pattern::cerl())    ->
1813       c_alias()
1814
1815              See also: c_alias/2.
1816
1817       update_c_apply(Node::c_apply(),  Operator::cerl(), Arguments::[cerl()])
1818       -> c_apply()
1819
1820              See also: c_apply/2.
1821
1822       update_c_binary(Node::c_binary(), Segments::[cerl()]) -> c_binary()
1823
1824              See also: c_binary/1.
1825
1826       update_c_bitstr(Node::c_bitstr(),     Value::cerl(),      Size::cerl(),
1827       Type::cerl(), Flags::cerl()) -> c_bitstr()
1828
1829              Equivalent  to  update_c_bitstr(Node,  Value, Size, abstract(1),
1830              Type, Flags).
1831
1832       update_c_bitstr(Node::c_bitstr(),      Val::cerl(),       Size::cerl(),
1833       Unit::cerl(), Type::cerl(), Flags::cerl()) -> c_bitstr()
1834
1835              See also: c_bitstr/5, update_c_bitstr/5.
1836
1837       update_c_call(Node::cerl(),    Module::cerl(),    Name::cerl(),   Argu‐
1838       ments::[cerl()]) -> c_call()
1839
1840              See also: c_call/3.
1841
1842       update_c_case(Node::c_case(),   Expr::cerl(),   Clauses::[cerl()])   ->
1843       c_case()
1844
1845              See also: c_case/2.
1846
1847       update_c_catch(Node::c_catch(), Body::cerl()) -> c_catch()
1848
1849              See also: c_catch/1.
1850
1851       update_c_clause(Node::c_clause(),   Patterns::[cerl()],  Guard::cerl(),
1852       Body::cerl()) -> c_clause()
1853
1854              See also: c_clause/3.
1855
1856       update_c_cons(Node::c_literal()    |    c_cons(),    C_literal::cerl(),
1857       Tail::cerl()) -> c_literal() | c_cons()
1858
1859              See also: c_cons/2.
1860
1861       update_c_cons_skel(Node::c_cons()    |    c_literal(),    Head::cerl(),
1862       Tail::cerl()) -> c_cons()
1863
1864              See also: c_cons_skel/2.
1865
1866       update_c_fname(C_var::c_var(), Atom::atom()) -> c_var()
1867
1868              Like update_c_fname/3, but takes the arity from Node.
1869
1870              See also: c_fname/2, update_c_fname/3.
1871
1872       update_c_fname(Node::c_var(), Atom::atom(), Arity::arity()) -> c_var()
1873
1874              Equivalent to update_c_var(Old, {Atom, Arity}).
1875
1876              See also: c_fname/2, update_c_fname/2.
1877
1878       update_c_fun(Node::c_fun(),   Variables::[cerl()],   Body::cerl())   ->
1879       c_fun()
1880
1881              See also: c_fun/2.
1882
1883       update_c_let(Node::c_let(),    Variables::[cerl()],   Argument::cerl(),
1884       Body::cerl()) -> c_let()
1885
1886              See also: c_let/3.
1887
1888       update_c_letrec(Node::c_letrec(),       Defs::[{cerl(),       cerl()}],
1889       Body::cerl()) -> c_letrec()
1890
1891              See also: c_letrec/2.
1892
1893       update_c_map(C_map::c_map(),  M::cerl(),  Es::[cerl()])  ->  c_map()  |
1894       c_literal()
1895
1896       update_c_map_pair(Old::c_map_pair(),      Op::map_op(),      K::cerl(),
1897       V::cerl()) -> c_map_pair()
1898
1899       update_c_module(Node::c_module(),  Name::cerl(), Exports::[cerl()], At‐
1900       trs::[{cerl(), cerl()}], Es::[{cerl(), cerl()}]) -> c_module()
1901
1902              See also: c_module/4.
1903
1904       update_c_primop(Node::cerl(),  Name::cerl(),  Arguments::[cerl()])   ->
1905       c_primop()
1906
1907              See also: c_primop/2.
1908
1909       update_c_receive(Node::c_receive(), Clauses::[cerl()], Timeout::cerl(),
1910       Action::cerl()) -> c_receive()
1911
1912              See also: c_receive/3.
1913
1914       update_c_seq(Node::c_seq(), Argument::cerl(), Body::cerl()) -> c_seq()
1915
1916              See also: c_seq/2.
1917
1918       update_c_try(Node::c_try(), Expr::cerl(),  Vs::[cerl()],  Body::cerl(),
1919       Evs::[cerl()], Handler::cerl()) -> c_try()
1920
1921              See also: c_try/5.
1922
1923       update_c_tuple(Node::c_tuple()  |  c_literal(),  Es::[cerl()]) -> c_tu‐
1924       ple() | c_literal()
1925
1926              See also: c_tuple/1.
1927
1928       update_c_tuple_skel(Old::c_tuple(), Es::[cerl()]) -> c_tuple()
1929
1930              See also: c_tuple_skel/1.
1931
1932       update_c_values(Node::c_values(), Es::[cerl()]) -> c_values()
1933
1934              See also: c_values/1.
1935
1936       update_c_var(Node::c_var(), Name::var_name()) -> c_var()
1937
1938              See also: c_var/1.
1939
1940       update_data(Node::cerl(), CType::dtype(), Es::[cerl()]) -> c_lct()
1941
1942              See also: make_data/2.
1943
1944       update_data_skel(Node::cerl(), CType::dtype(), Es::[cerl()]) -> c_lct()
1945
1946              See also: make_data_skel/2.
1947
1948       update_list(Node::cerl(), List::[cerl()]) -> cerl()
1949
1950              Equivalent to update_list(Old, List, none).
1951
1952       update_list(Node::cerl(),  List::[cerl()],  Tail::cerl()  |  none)   ->
1953       cerl()
1954
1955              See also: make_list/2, update_list/2.
1956
1957       update_tree(Node::cerl(), Gs::[[cerl()], ...]) -> cerl()
1958
1959              Creates a syntax tree with the given subtrees, and the same type
1960              and  annotations  as  the  Old  node.  This  is  equivalent   to
1961              ann_make_tree(get_ann(Node),  type(Node),  Groups),  but  poten‐
1962              tially more efficient.
1963
1964              See also: ann_make_tree/3, get_ann/1, type/1, update_tree/3.
1965
1966       update_tree(Node::cerl(), Type::ctype(), Gs::[[cerl()], ...]) -> cerl()
1967
1968              Creates a syntax tree with the given type and subtrees, and  the
1969              same  annotations  as  the  Old  node.  This  is  equivalent  to
1970              ann_make_tree(get_ann(Node), Type, Groups), but potentially more
1971              efficient.
1972
1973              See also: ann_make_tree/3, get_ann/1, update_tree/2.
1974
1975       values_arity(Node::c_values()) -> non_neg_integer()
1976
1977              Returns  the  number  of  element  subtrees of an abstract value
1978              list.
1979
1980              Note: This is equivalent to length(values_es(Node)), but  poten‐
1981              tially more efficient.
1982
1983              See also: c_values/1, values_es/1.
1984
1985       values_es(Node::c_values()) -> [cerl()]
1986
1987              Returns the list of element subtrees of an abstract value list.
1988
1989              See also: c_values/1, values_arity/1.
1990
1991       var_name(Node::c_var()) -> var_name()
1992
1993              Returns the name of an abstract variable.
1994
1995              See also: c_var/1.
1996

AUTHORS

1998       Richard Carlsson <carlsson.richard@gmail.com>
1999
2000
2001
2002                                compiler 8.1.1                         cerl(3)
Impressum