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_opaque() = #c_opaque{}:
91
92
93         c_primop() = #c_primop{}:
94
95
96         c_receive() = #c_receive{}:
97
98
99         c_seq() = #c_seq{}:
100
101
102         c_try() = #c_try{}:
103
104
105         c_tuple() = #c_tuple{}:
106
107
108         c_values() = #c_values{}:
109
110
111         c_var() = #c_var{}:
112
113
114         cerl() = c_alias() | c_apply() | c_binary() | c_bitstr() | c_call() |
115         c_case()  |  c_catch()  | c_clause() | c_cons() | c_fun() | c_let() |
116         c_letrec() | c_literal() | c_map()  |  c_map_pair()  |  c_module()  |
117         c_opaque() | c_primop() | c_receive() | c_seq() | c_try() | c_tuple()
118         | c_values() | c_var():
119
120
121         ctype() = alias | apply | binary | bitstr | call |  case  |  catch  |
122         clause  | cons | fun | let | letrec | literal | map | map_pair | mod‐
123         ule | primop | receive | seq | try | tuple | values | var:
124
125
126         dtype() = cons | tuple | {atomic, value()}:
127
128
129         map_op() = #c_literal{val=assoc} | #c_literal{val=exact}:
130
131
132         value() = integer() | float() | atom() | []:
133
134
135         var_name() = integer() | atom() | {atom(), integer()}:
136
137

EXPORTS

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

AUTHORS

2001       Richard Carlsson <carlsson.richard@gmail.com>
2002
2003
2004
2005                                compiler 8.4.1                         cerl(3)
Impressum