~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/options1_tests_SUITE_data/src/compiler/cerl.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Richard Carlsson.
 
13
%% Copyright (C) 1999-2002 Richard Carlsson.
 
14
%% Portions created by Ericsson are Copyright 2001, Ericsson Utvecklings
 
15
%% AB. All Rights Reserved.''
 
16
%% 
 
17
%%     $Id: cerl.erl,v 1.3 2010/03/04 13:54:20 maria Exp $
 
18
 
 
19
%% =====================================================================
 
20
%% @doc Core Erlang abstract syntax trees.
 
21
%%
 
22
%% <p> This module defines an abstract data type for representing Core
 
23
%% Erlang source code as syntax trees.</p>
 
24
%%
 
25
%% <p>A recommended starting point for the first-time user is the
 
26
%% documentation of the function <a
 
27
%% href="#type-1"><code>type/1</code></a>.</p>
 
28
%%
 
29
%% <h3><b>NOTES:</b></h3>
 
30
%%
 
31
%% <p>This module deals with the composition and decomposition of
 
32
%% <em>syntactic</em> entities (as opposed to semantic ones); its
 
33
%% purpose is to hide all direct references to the data structures
 
34
%% used to represent these entities. With few exceptions, the
 
35
%% functions in this module perform no semantic interpretation of
 
36
%% their inputs, and in general, the user is assumed to pass
 
37
%% type-correct arguments - if this is not done, the effects are not
 
38
%% defined.</p>
 
39
%%
 
40
%% <p>The internal representations of abstract syntax trees are
 
41
%% subject to change without notice, and should not be documented
 
42
%% outside this module. Furthermore, we do not give any guarantees on
 
43
%% how an abstract syntax tree may or may not be represented, <em>with
 
44
%% the following exceptions</em>: no syntax tree is represented by a
 
45
%% single atom, such as <code>none</code>, by a list constructor
 
46
%% <code>[X | Y]</code>, or by the empty list <code>[]</code>. This
 
47
%% can be relied on when writing functions that operate on syntax
 
48
%% trees.</p>
 
49
%%
 
50
%% @type cerl(). An abstract Core Erlang syntax tree.
 
51
%%
 
52
%% <p>Every abstract syntax tree has a <em>type</em>, given by the
 
53
%% function <a href="#type-1"><code>type/1</code></a>.  In addition,
 
54
%% each syntax tree has a list of <em>user annotations</em> (cf.  <a
 
55
%% href="#get_ann-1"><code>get_ann/1</code></a>), which are included
 
56
%% in the Core Erlang syntax.</p>
 
57
 
 
58
-module(cerl).
 
59
 
 
60
-export([abstract/1, add_ann/2, alias_pat/1, alias_var/1,
 
61
         ann_abstract/2, ann_c_alias/3, ann_c_apply/3, ann_c_atom/2,
 
62
         ann_c_call/4, ann_c_case/3, ann_c_catch/2, ann_c_char/2,
 
63
         ann_c_clause/3, ann_c_clause/4, ann_c_cons/3, ann_c_float/2,
 
64
         ann_c_fname/3, ann_c_fun/3, ann_c_int/2, ann_c_let/4,
 
65
         ann_c_letrec/3, ann_c_module/4, ann_c_module/5, ann_c_nil/1,
 
66
         ann_c_cons_skel/3, ann_c_tuple_skel/2, ann_c_primop/3,
 
67
         ann_c_receive/2, ann_c_receive/4, ann_c_seq/3, ann_c_string/2,
 
68
         ann_c_try/6, ann_c_tuple/2, ann_c_values/2, ann_c_var/2,
 
69
         ann_make_data/3, ann_make_list/2, ann_make_list/3,
 
70
         ann_make_data_skel/3, ann_make_tree/3, apply_args/1,
 
71
         apply_arity/1, apply_op/1, atom_lit/1, atom_name/1, atom_val/1,
 
72
         c_alias/2, c_apply/2, c_atom/1, c_call/3, c_case/2, c_catch/1,
 
73
         c_char/1, c_clause/2, c_clause/3, c_cons/2, c_float/1,
 
74
         c_fname/2, c_fun/2, c_int/1, c_let/3, c_letrec/2, c_module/3,
 
75
         c_module/4, c_nil/0, c_cons_skel/2, c_tuple_skel/1, c_primop/2,
 
76
         c_receive/1, c_receive/3, c_seq/2, c_string/1, c_try/5,
 
77
         c_tuple/1, c_values/1, c_var/1, call_args/1, call_arity/1,
 
78
         call_module/1, call_name/1, case_arg/1, case_arity/1,
 
79
         case_clauses/1, catch_body/1, char_lit/1, char_val/1,
 
80
         clause_arity/1, clause_body/1, clause_guard/1, clause_pats/1,
 
81
         clause_vars/1, concrete/1, cons_hd/1, cons_tl/1, copy_ann/2,
 
82
         data_arity/1, data_es/1, data_type/1, float_lit/1, float_val/1,
 
83
         fname_arity/1, fname_id/1, fold_literal/1, from_records/1,
 
84
         fun_arity/1, fun_body/1, fun_vars/1, get_ann/1, int_lit/1,
 
85
         int_val/1, is_c_alias/1, is_c_apply/1, is_c_atom/1,
 
86
         is_c_call/1, is_c_case/1, is_c_catch/1, is_c_char/1,
 
87
         is_c_clause/1, is_c_cons/1, is_c_float/1, is_c_fname/1,
 
88
         is_c_fun/1, is_c_int/1, is_c_let/1, is_c_letrec/1, is_c_list/1,
 
89
         is_c_module/1, is_c_nil/1, is_c_primop/1, is_c_receive/1,
 
90
         is_c_seq/1, is_c_string/1, is_c_try/1, is_c_tuple/1,
 
91
         is_c_values/1, is_c_var/1, is_data/1, is_leaf/1, is_literal/1,
 
92
         is_literal_term/1, is_print_char/1, is_print_string/1,
 
93
         let_arg/1, let_arity/1, let_body/1, let_vars/1, letrec_body/1,
 
94
         letrec_defs/1, letrec_vars/1, list_elements/1, list_length/1,
 
95
         make_data/2, make_list/1, make_list/2, make_data_skel/2,
 
96
         make_tree/2, meta/1, module_attrs/1, module_defs/1,
 
97
         module_exports/1, module_name/1, module_vars/1,
 
98
         pat_list_vars/1, pat_vars/1, primop_args/1, primop_arity/1,
 
99
         primop_name/1, receive_action/1, receive_clauses/1,
 
100
         receive_timeout/1, seq_arg/1, seq_body/1, set_ann/2,
 
101
         string_lit/1, string_val/1, subtrees/1, to_records/1,
 
102
         try_arg/1, try_body/1, try_vars/1, try_evars/1, try_handler/1,
 
103
         tuple_arity/1, tuple_es/1, type/1, unfold_literal/1,
 
104
         update_c_alias/3, update_c_apply/3, update_c_call/4,
 
105
         update_c_case/3, update_c_catch/2, update_c_clause/4,
 
106
         update_c_cons/3, update_c_cons_skel/3, update_c_fname/2,
 
107
         update_c_fname/3, update_c_fun/3, update_c_let/4,
 
108
         update_c_letrec/3, update_c_module/5, update_c_primop/3,
 
109
         update_c_receive/4, update_c_seq/3, update_c_try/6,
 
110
         update_c_tuple/2, update_c_tuple_skel/2, update_c_values/2,
 
111
         update_c_var/2, update_data/3, update_list/2, update_list/3,
 
112
         update_data_skel/3, update_tree/2, update_tree/3,
 
113
         values_arity/1, values_es/1, var_name/1, c_binary/1,
 
114
         update_c_binary/2, ann_c_binary/2, is_c_binary/1,
 
115
         binary_segments/1, c_bitstr/3, c_bitstr/4, c_bitstr/5,
 
116
         update_c_bitstr/5, update_c_bitstr/6, ann_c_bitstr/5,
 
117
         ann_c_bitstr/6, is_c_bitstr/1, bitstr_val/1, bitstr_size/1,
 
118
         bitstr_bitsize/1, bitstr_unit/1, bitstr_type/1,
 
119
         bitstr_flags/1]).
 
120
 
 
121
-include("core_parse.hrl").
 
122
 
 
123
 
 
124
%% =====================================================================
 
125
%% Representation (general)
 
126
%%
 
127
%% All nodes are represented by tuples of arity 2 or (generally)
 
128
%% greater, whose first element is an atom which uniquely identifies the
 
129
%% type of the node, and whose second element is a (proper) list of
 
130
%% annotation terms associated with the node - this is by default empty.
 
131
%%
 
132
%% For most node constructor functions, there are analogous functions
 
133
%% named 'ann_...', taking one extra argument 'As' (always the first
 
134
%% argument), specifying an annotation list at node creation time.
 
135
%% Similarly, there are also functions named 'update_...', taking one
 
136
%% extra argument 'Old', specifying a node from which all fields not
 
137
%% explicitly given as arguments should be copied (generally, this is
 
138
%% the annotation field only).
 
139
%% =====================================================================
 
140
 
 
141
%% This defines the general representation of constant literals:
 
142
 
 
143
-record(literal, {ann = [], val}).
 
144
 
 
145
 
 
146
%% @spec type(Node::cerl()) -> atom()
 
147
%%
 
148
%% @doc Returns the type tag of <code>Node</code>. Current node types
 
149
%% are:
 
150
%%          
 
151
%% <p><center><table border="1">
 
152
%%  <tr>
 
153
%%    <td>alias</td>
 
154
%%    <td>apply</td>
 
155
%%    <td>binary</td>
 
156
%%    <td>bitstr</td>
 
157
%%    <td>call</td>
 
158
%%    <td>case</td>
 
159
%%    <td>catch</td>
 
160
%%  </tr><tr>
 
161
%%    <td>clause</td>
 
162
%%    <td>cons</td>
 
163
%%    <td>fun</td>
 
164
%%    <td>let</td>
 
165
%%    <td>letrec</td>
 
166
%%    <td>literal</td>
 
167
%%    <td>module</td>
 
168
%%  </tr><tr>
 
169
%%    <td>primop</td>
 
170
%%    <td>receive</td>
 
171
%%    <td>seq</td>
 
172
%%    <td>try</td>
 
173
%%    <td>tuple</td>
 
174
%%    <td>values</td>
 
175
%%    <td>var</td>
 
176
%%  </tr>
 
177
%% </table></center></p>
 
178
%%
 
179
%% <p>Note: The name of the primary constructor function for a node
 
180
%% type is always the name of the type itself, prefixed by
 
181
%% "<code>c_</code>"; recognizer predicates are correspondingly
 
182
%% prefixed by "<code>is_c_</code>". Furthermore, to simplify
 
183
%% preservation of annotations (cf. <code>get_ann/1</code>), there are
 
184
%% analogous constructor functions prefixed by "<code>ann_c_</code>"
 
185
%% and "<code>update_c_</code>", for setting the annotation list of
 
186
%% the new node to either a specific value or to the annotations of an
 
187
%% existing node, respectively.</p>
 
188
%%
 
189
%% @see abstract/1
 
190
%% @see c_alias/2
 
191
%% @see c_apply/2
 
192
%% @see c_binary/1
 
193
%% @see c_bitstr/5
 
194
%% @see c_call/3
 
195
%% @see c_case/2
 
196
%% @see c_catch/1
 
197
%% @see c_clause/3
 
198
%% @see c_cons/2
 
199
%% @see c_fun/2
 
200
%% @see c_let/3
 
201
%% @see c_letrec/2
 
202
%% @see c_module/3
 
203
%% @see c_primop/2
 
204
%% @see c_receive/1
 
205
%% @see c_seq/2
 
206
%% @see c_try/3
 
207
%% @see c_tuple/1
 
208
%% @see c_values/1
 
209
%% @see c_var/1
 
210
%% @see get_ann/1
 
211
%% @see to_records/1
 
212
%% @see from_records/1
 
213
%% @see data_type/1
 
214
%% @see subtrees/1
 
215
%% @see meta/1
 
216
 
 
217
type(Node) ->
 
218
    element(1, Node).
 
219
 
 
220
 
 
221
%% @spec is_leaf(Node::cerl()) -> boolean()
 
222
%%
 
223
%% @doc Returns <code>true</code> if <code>Node</code> is a leaf node,
 
224
%% otherwise <code>false</code>. The current leaf node types are
 
225
%% <code>literal</code> and <code>var</code>.
 
226
%%
 
227
%% <p>Note: all literals (cf. <code>is_literal/1</code>) are leaf
 
228
%% nodes, even if they represent structured (constant) values such as
 
229
%% <code>{foo, [bar, baz]}</code>. Also note that variables are leaf
 
230
%% nodes but not literals.</p>
 
231
%%
 
232
%% @see type/1
 
233
%% @see is_literal/1
 
234
 
 
235
is_leaf(Node) ->
 
236
    case type(Node) of
 
237
        literal -> true;
 
238
        var -> true;
 
239
        _ -> false
 
240
    end.
 
241
 
 
242
 
 
243
%% @spec get_ann(cerl()) -> [term()]
 
244
%%
 
245
%% @doc Returns the list of user annotations associated with a syntax
 
246
%% tree node. For a newly created node, this is the empty list. The
 
247
%% annotations may be any terms.
 
248
%%
 
249
%% @see set_ann/2
 
250
 
 
251
get_ann(Node) ->
 
252
    element(2, Node).
 
253
 
 
254
 
 
255
%% @spec set_ann(Node::cerl(), Annotations::[term()]) -> cerl()
 
256
%%
 
257
%% @doc Sets the list of user annotations of <code>Node</code> to
 
258
%% <code>Annotations</code>.
 
259
%%
 
260
%% @see get_ann/1
 
261
%% @see add_ann/2
 
262
%% @see copy_ann/2
 
263
 
 
264
set_ann(Node, List) ->
 
265
    setelement(2, Node, List).
 
266
 
 
267
 
 
268
%% @spec add_ann(Annotations::[term()], Node::cerl()) -> cerl()
 
269
%%
 
270
%% @doc Appends <code>Annotations</code> to the list of user
 
271
%% annotations of <code>Node</code>.
 
272
%%
 
273
%% <p>Note: this is equivalent to <code>set_ann(Node, Annotations ++
 
274
%% get_ann(Node))</code>, but potentially more efficient.</p>
 
275
%%
 
276
%% @see get_ann/1
 
277
%% @see set_ann/2
 
278
 
 
279
add_ann(Terms, Node) ->
 
280
    set_ann(Node, Terms ++ get_ann(Node)).
 
281
 
 
282
 
 
283
%% @spec copy_ann(Source::cerl(), Target::cerl()) -> cerl()
 
284
%%
 
285
%% @doc Copies the list of user annotations from <code>Source</code>
 
286
%% to <code>Target</code>.
 
287
%%
 
288
%% <p>Note: this is equivalent to <code>set_ann(Target,
 
289
%% get_ann(Source))</code>, but potentially more efficient.</p>
 
290
%%
 
291
%% @see get_ann/1
 
292
%% @see set_ann/2
 
293
 
 
294
copy_ann(Source, Target) ->
 
295
    set_ann(Target, get_ann(Source)).
 
296
 
 
297
 
 
298
%% @spec abstract(Term::term()) -> cerl()
 
299
%%
 
300
%% @doc Creates a syntax tree corresponding to an Erlang term.
 
301
%% <code>Term</code> must be a literal term, i.e., one that can be
 
302
%% represented as a source code literal. Thus, it may not contain a
 
303
%% process identifier, port, reference, binary or function value as a
 
304
%% subterm.
 
305
%%
 
306
%% <p>Note: This is a constant time operation.</p>
 
307
%%
 
308
%% @see ann_abstract/2
 
309
%% @see concrete/1
 
310
%% @see is_literal/1
 
311
%% @see is_literal_term/1
 
312
 
 
313
abstract(T) ->
 
314
    #literal{val = T}.
 
315
 
 
316
 
 
317
%% @spec ann_abstract(Annotations::[term()], Term::term()) -> cerl()
 
318
%% @see abstract/1
 
319
 
 
320
ann_abstract(As, T) ->
 
321
    #literal{val = T, ann = As}.
 
322
 
 
323
 
 
324
%% @spec is_literal_term(Term::term()) -> boolean()
 
325
%%
 
326
%% @doc Returns <code>true</code> if <code>Term</code> can be
 
327
%% represented as a literal, otherwise <code>false</code>. This
 
328
%% function takes time proportional to the size of <code>Term</code>.
 
329
%%
 
330
%% @see abstract/1
 
331
 
 
332
is_literal_term(T) when integer(T) -> true;
 
333
is_literal_term(T) when float(T) -> true;
 
334
is_literal_term(T) when atom(T) -> true;
 
335
is_literal_term([]) -> true;
 
336
is_literal_term([H | T]) ->
 
337
    case is_literal_term(H) of
 
338
        true ->
 
339
            is_literal_term(T);
 
340
        false ->
 
341
            false
 
342
    end;
 
343
is_literal_term(T) when tuple(T) ->
 
344
    is_literal_term_list(tuple_to_list(T));
 
345
is_literal_term(_) ->
 
346
    false.
 
347
 
 
348
is_literal_term_list([T | Ts]) ->
 
349
    case is_literal_term(T) of
 
350
        true ->
 
351
            is_literal_term_list(Ts);
 
352
        false ->
 
353
            false
 
354
    end;
 
355
is_literal_term_list([]) ->
 
356
    true.
 
357
 
 
358
 
 
359
%% @spec concrete(Node::cerl()) -> term()
 
360
%%
 
361
%% @doc Returns the Erlang term represented by a syntax tree.  An
 
362
%% exception is thrown if <code>Node</code> does not represent a
 
363
%% literal term.
 
364
%%
 
365
%% <p>Note: This is a constant time operation.</p>
 
366
%%
 
367
%% @see abstract/1
 
368
%% @see is_literal/1
 
369
 
 
370
%% Because the normal tuple and list constructor operations always
 
371
%% return a literal if the arguments are literals, 'concrete' and
 
372
%% 'is_literal' never need to traverse the structure.
 
373
 
 
374
concrete(#literal{val = V}) ->
 
375
    V.
 
376
 
 
377
 
 
378
%% @spec is_literal(Node::cerl()) -> boolean()
 
379
%%
 
380
%% @doc Returns <code>true</code> if <code>Node</code> represents a
 
381
%% literal term, otherwise <code>false</code>. This function returns
 
382
%% <code>true</code> if and only if the value of
 
383
%% <code>concrete(Node)</code> is defined.
 
384
%%
 
385
%% <p>Note: This is a constant time operation.</p>
 
386
%%
 
387
%% @see abstract/1
 
388
%% @see concrete/1
 
389
%% @see fold_literal/1
 
390
 
 
391
is_literal(#literal{}) ->
 
392
    true;
 
393
is_literal(_) ->
 
394
    false.
 
395
 
 
396
 
 
397
%% @spec fold_literal(Node::cerl()) -> cerl()
 
398
%%
 
399
%% @doc Assures that literals have a compact representation. This is
 
400
%% occasionally useful if <code>c_cons_skel/2</code>,
 
401
%% <code>c_tuple_skel/1</code> or <code>unfold_literal/1</code> were
 
402
%% used in the construction of <code>Node</code>, and you want to revert
 
403
%% to the normal "folded" representation of literals. If
 
404
%% <code>Node</code> represents a tuple or list constructor, its
 
405
%% elements are rewritten recursively, and the node is reconstructed
 
406
%% using <code>c_cons/2</code> or <code>c_tuple/1</code>, respectively;
 
407
%% otherwise, <code>Node</code> is not changed.
 
408
%%
 
409
%% @see is_literal/1
 
410
%% @see c_cons_skel/2
 
411
%% @see c_tuple_skel/1
 
412
%% @see c_cons/2
 
413
%% @see c_tuple/1
 
414
%% @see unfold_literal/1
 
415
 
 
416
fold_literal(Node) ->
 
417
    case type(Node) of
 
418
        tuple ->
 
419
            update_c_tuple(Node, fold_literal_list(tuple_es(Node)));
 
420
        cons ->
 
421
            update_c_cons(Node, fold_literal(cons_hd(Node)),
 
422
                          fold_literal(cons_tl(Node)));
 
423
        _ ->
 
424
            Node    
 
425
    end.
 
426
 
 
427
fold_literal_list([E | Es]) ->
 
428
    [fold_literal(E) | fold_literal_list(Es)];
 
429
fold_literal_list([]) ->
 
430
    [].
 
431
 
 
432
 
 
433
%% @spec unfold_literal(Node::cerl()) -> cerl()
 
434
%%
 
435
%% @doc Assures that literals have a fully expanded representation. If
 
436
%% <code>Node</code> represents a literal tuple or list constructor, its
 
437
%% elements are rewritten recursively, and the node is reconstructed
 
438
%% using <code>c_cons_skel/2</code> or <code>c_tuple_skel/1</code>,
 
439
%% respectively; otherwise, <code>Node</code> is not changed. The {@link
 
440
%% fold_literal/1} can be used to revert to the normal compact
 
441
%% representation.
 
442
%%
 
443
%% @see is_literal/1
 
444
%% @see c_cons_skel/2
 
445
%% @see c_tuple_skel/1
 
446
%% @see c_cons/2
 
447
%% @see c_tuple/1
 
448
%% @see fold_literal/1
 
449
 
 
450
unfold_literal(Node) ->
 
451
    case type(Node) of
 
452
        literal ->
 
453
            copy_ann(Node, unfold_concrete(concrete(Node)));
 
454
        _ ->
 
455
            Node
 
456
    end.
 
457
 
 
458
unfold_concrete(Val) ->
 
459
    case Val of
 
460
        _ when tuple(Val) ->
 
461
            c_tuple_skel(unfold_concrete_list(tuple_to_list(Val)));
 
462
        [H|T] ->
 
463
            c_cons_skel(unfold_concrete(H), unfold_concrete(T));
 
464
        _ ->
 
465
            abstract(Val)
 
466
    end.
 
467
 
 
468
unfold_concrete_list([E | Es]) ->
 
469
    [unfold_concrete(E) | unfold_concrete_list(Es)];
 
470
unfold_concrete_list([]) ->
 
471
    [].
 
472
 
 
473
 
 
474
%% ---------------------------------------------------------------------
 
475
 
 
476
-record(module, {ann = [], name, exports, attrs, defs}).
 
477
 
 
478
 
 
479
%% @spec c_module(Name::cerl(), Exports, Definitions) -> cerl()
 
480
%%
 
481
%%     Exports = [cerl()]
 
482
%%     Definitions = [{cerl(), cerl()}]
 
483
%%
 
484
%% @equiv c_module(Name, Exports, [], Definitions)
 
485
 
 
486
c_module(Name, Exports, Es) ->
 
487
    #module{name = Name, exports = Exports, attrs = [], defs = Es}.
 
488
 
 
489
 
 
490
%% @spec c_module(Name::cerl(), Exports, Attributes, Definitions) ->
 
491
%%           cerl()
 
492
%%
 
493
%%     Exports = [cerl()]
 
494
%%     Attributes = [{cerl(), cerl()}]
 
495
%%     Definitions = [{cerl(), cerl()}]
 
496
%%
 
497
%% @doc Creates an abstract module definition. The result represents
 
498
%% <pre>
 
499
%%   module <em>Name</em> [<em>E1</em>, ..., <em>Ek</em>]
 
500
%%     attributes [<em>K1</em> = <em>T1</em>, ...,
 
501
%%                 <em>Km</em> = <em>Tm</em>]
 
502
%%     <em>V1</em> = <em>F1</em>
 
503
%%     ...
 
504
%%     <em>Vn</em> = <em>Fn</em>
 
505
%%   end</pre>
 
506
%%
 
507
%% if <code>Exports</code> = <code>[E1, ..., Ek]</code>,
 
508
%% <code>Attributes</code> = <code>[{K1, T1}, ..., {Km, Tm}]</code>,
 
509
%% and <code>Definitions</code> = <code>[{V1, F1}, ..., {Vn,
 
510
%% Fn}]</code>.
 
511
%%
 
512
%% <p><code>Name</code> and all the <code>Ki</code> must be atom
 
513
%% literals, and all the <code>Ti</code> must be constant literals. All
 
514
%% the <code>Vi</code> and <code>Ei</code> must have type
 
515
%% <code>var</code> and represent function names. All the
 
516
%% <code>Fi</code> must have type <code>'fun'</code>.</p>
 
517
%%
 
518
%% @see c_module/3
 
519
%% @see module_name/1
 
520
%% @see module_exports/1
 
521
%% @see module_attrs/1
 
522
%% @see module_defs/1
 
523
%% @see module_vars/1
 
524
%% @see ann_c_module/4
 
525
%% @see ann_c_module/5
 
526
%% @see update_c_module/5
 
527
%% @see c_atom/1
 
528
%% @see c_var/1
 
529
%% @see c_fun/2
 
530
%% @see is_literal/1
 
531
 
 
532
c_module(Name, Exports, Attrs, Es) ->
 
533
    #module{name = Name, exports = Exports, attrs = Attrs, defs = Es}.
 
534
 
 
535
 
 
536
%% @spec ann_c_module(As::[term()], Name::cerl(), Exports,
 
537
%%                    Definitions) -> cerl()
 
538
%%
 
539
%%     Exports = [cerl()]
 
540
%%     Definitions = [{cerl(), cerl()}]
 
541
%%
 
542
%% @see c_module/3
 
543
%% @see ann_c_module/5
 
544
 
 
545
ann_c_module(As, Name, Exports, Es) ->
 
546
    #module{name = Name, exports = Exports, attrs = [], defs = Es,
 
547
            ann = As}.
 
548
 
 
549
 
 
550
%% @spec ann_c_module(As::[term()], Name::cerl(), Exports,
 
551
%%                    Attributes, Definitions) -> cerl()
 
552
%%
 
553
%%     Exports = [cerl()]
 
554
%%     Attributes = [{cerl(), cerl()}]
 
555
%%     Definitions = [{cerl(), cerl()}]
 
556
%%
 
557
%% @see c_module/4
 
558
%% @see ann_c_module/4
 
559
 
 
560
ann_c_module(As, Name, Exports, Attrs, Es) ->
 
561
    #module{name = Name, exports = Exports, attrs = Attrs, defs = Es,
 
562
            ann = As}.
 
563
 
 
564
 
 
565
%% @spec update_c_module(Old::cerl(), Name::cerl(), Exports,
 
566
%%                       Attributes, Definitions) -> cerl()
 
567
%%
 
568
%%     Exports = [cerl()]
 
569
%%     Attributes = [{cerl(), cerl()}]
 
570
%%     Definitions = [{cerl(), cerl()}]
 
571
%%
 
572
%% @see c_module/4
 
573
 
 
574
update_c_module(Node, Name, Exports, Attrs, Es) ->
 
575
    #module{name = Name, exports = Exports, attrs = Attrs, defs = Es,
 
576
            ann = get_ann(Node)}.
 
577
 
 
578
 
 
579
%% @spec is_c_module(Node::cerl()) -> boolean()
 
580
%%
 
581
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
582
%% module definition, otherwise <code>false</code>.
 
583
%%
 
584
%% @see type/1
 
585
 
 
586
is_c_module(#module{}) ->
 
587
    true;
 
588
is_c_module(_) ->
 
589
    false.
 
590
 
 
591
 
 
592
%% @spec module_name(Node::cerl()) -> cerl()
 
593
%%
 
594
%% @doc Returns the name subtree of an abstract module definition.
 
595
%%
 
596
%% @see c_module/4
 
597
 
 
598
module_name(Node) ->
 
599
    Node#module.name.
 
600
 
 
601
 
 
602
%% @spec module_exports(Node::cerl()) -> [cerl()]
 
603
%%
 
604
%% @doc Returns the list of exports subtrees of an abstract module
 
605
%% definition.
 
606
%%
 
607
%% @see c_module/4
 
608
 
 
609
module_exports(Node) ->
 
610
    Node#module.exports.
 
611
 
 
612
 
 
613
%% @spec module_attrs(Node::cerl()) -> [{cerl(), cerl()}]
 
614
%%
 
615
%% @doc Returns the list of pairs of attribute key/value subtrees of
 
616
%% an abstract module definition.
 
617
%%
 
618
%% @see c_module/4
 
619
 
 
620
module_attrs(Node) ->
 
621
    Node#module.attrs.
 
622
 
 
623
 
 
624
%% @spec module_defs(Node::cerl()) -> [{cerl(), cerl()}]
 
625
%%
 
626
%% @doc Returns the list of function definitions of an abstract module
 
627
%% definition.
 
628
%%
 
629
%% @see c_module/4
 
630
 
 
631
module_defs(Node) ->
 
632
    Node#module.defs.
 
633
 
 
634
 
 
635
%% @spec module_vars(Node::cerl()) -> [cerl()]
 
636
%%
 
637
%% @doc Returns the list of left-hand side function variable subtrees
 
638
%% of an abstract module definition.
 
639
%%
 
640
%% @see c_module/4
 
641
 
 
642
module_vars(Node) ->
 
643
    [F || {F, _} <- module_defs(Node)].
 
644
 
 
645
 
 
646
%% ---------------------------------------------------------------------
 
647
 
 
648
%% @spec c_int(Value::integer()) -> cerl()
 
649
%%
 
650
%%
 
651
%% @doc Creates an abstract integer literal. The lexical
 
652
%% representation is the canonical decimal numeral of
 
653
%% <code>Value</code>.
 
654
%%
 
655
%% @see ann_c_int/2
 
656
%% @see is_c_int/1
 
657
%% @see int_val/1
 
658
%% @see int_lit/1
 
659
%% @see c_char/1
 
660
 
 
661
c_int(Value) ->
 
662
    #literal{val = Value}.
 
663
 
 
664
 
 
665
%% @spec ann_c_int(As::[term()], Value::integer()) -> cerl()
 
666
%% @see c_int/1
 
667
 
 
668
ann_c_int(As, Value) ->
 
669
    #literal{val = Value, ann = As}.
 
670
 
 
671
 
 
672
%% @spec is_c_int(Node::cerl()) -> boolean()
 
673
%%
 
674
%% @doc Returns <code>true</code> if <code>Node</code> represents an
 
675
%% integer literal, otherwise <code>false</code>.
 
676
%% @see c_int/1
 
677
 
 
678
is_c_int(#literal{val = V}) when integer(V) ->
 
679
    true;
 
680
is_c_int(_) ->
 
681
    false.
 
682
 
 
683
 
 
684
%% @spec int_val(cerl()) -> integer()
 
685
%%
 
686
%% @doc Returns the value represented by an integer literal node.
 
687
%% @see c_int/1
 
688
 
 
689
int_val(Node) ->
 
690
    Node#literal.val.
 
691
 
 
692
 
 
693
%% @spec int_lit(cerl()) -> string()
 
694
%%
 
695
%% @doc Returns the numeral string represented by an integer literal
 
696
%% node.
 
697
%% @see c_int/1
 
698
 
 
699
int_lit(Node) ->
 
700
    integer_to_list(int_val(Node)).
 
701
 
 
702
 
 
703
%% ---------------------------------------------------------------------
 
704
 
 
705
%% @spec c_float(Value::float()) -> cerl()
 
706
%%
 
707
%% @doc Creates an abstract floating-point literal.  The lexical
 
708
%% representation is the decimal floating-point numeral of
 
709
%% <code>Value</code>.
 
710
%%
 
711
%% @see ann_c_float/2
 
712
%% @see is_c_float/1
 
713
%% @see float_val/1
 
714
%% @see float_lit/1
 
715
 
 
716
%% Note that not all floating-point numerals can be represented with
 
717
%% full precision.
 
718
 
 
719
c_float(Value) ->
 
720
    #literal{val = Value}.
 
721
 
 
722
 
 
723
%% @spec ann_c_float(As::[term()], Value::float()) -> cerl()
 
724
%% @see c_float/1
 
725
 
 
726
ann_c_float(As, Value) ->
 
727
    #literal{val = Value, ann = As}.
 
728
 
 
729
 
 
730
%% @spec is_c_float(Node::cerl()) -> boolean()
 
731
%%
 
732
%% @doc Returns <code>true</code> if <code>Node</code> represents a
 
733
%% floating-point literal, otherwise <code>false</code>.
 
734
%% @see c_float/1
 
735
 
 
736
is_c_float(#literal{val = V}) when float(V) ->
 
737
    true;
 
738
is_c_float(_) ->
 
739
    false.
 
740
 
 
741
 
 
742
%% @spec float_val(cerl()) -> float()
 
743
%%
 
744
%% @doc Returns the value represented by a floating-point literal
 
745
%% node.
 
746
%% @see c_float/1
 
747
 
 
748
float_val(Node) ->
 
749
    Node#literal.val.
 
750
 
 
751
 
 
752
%% @spec float_lit(cerl()) -> string()
 
753
%%
 
754
%% @doc Returns the numeral string represented by a floating-point
 
755
%% literal node.
 
756
%% @see c_float/1
 
757
 
 
758
float_lit(Node) ->
 
759
    float_to_list(float_val(Node)).
 
760
 
 
761
 
 
762
%% ---------------------------------------------------------------------
 
763
 
 
764
%% @spec c_atom(Name) -> cerl()
 
765
%%          Name = atom() | string()
 
766
%%
 
767
%% @doc Creates an abstract atom literal.  The print name of the atom
 
768
%% is the character sequence represented by <code>Name</code>.
 
769
%%
 
770
%% <p>Note: passing a string as argument to this function causes a
 
771
%% corresponding atom to be created for the internal representation.</p>
 
772
%%
 
773
%% @see ann_c_atom/2
 
774
%% @see is_c_atom/1
 
775
%% @see atom_val/1
 
776
%% @see atom_name/1
 
777
%% @see atom_lit/1
 
778
 
 
779
c_atom(Name) when atom(Name) ->
 
780
    #literal{val = Name};
 
781
c_atom(Name) ->
 
782
    #literal{val = list_to_atom(Name)}.
 
783
 
 
784
 
 
785
%% @spec ann_c_atom(As::[term()], Name) -> cerl()
 
786
%%          Name = atom() | string()
 
787
%% @see c_atom/1
 
788
 
 
789
ann_c_atom(As, Name) when atom(Name) ->
 
790
    #literal{val = Name, ann = As};
 
791
ann_c_atom(As, Name) ->
 
792
    #literal{val = list_to_atom(Name), ann = As}.
 
793
 
 
794
 
 
795
%% @spec is_c_atom(Node::cerl()) -> boolean()
 
796
%%
 
797
%% @doc Returns <code>true</code> if <code>Node</code> represents an
 
798
%% atom literal, otherwise <code>false</code>.
 
799
%%
 
800
%% @see c_atom/1
 
801
 
 
802
is_c_atom(#literal{val = V}) when atom(V) ->
 
803
    true;
 
804
is_c_atom(_) ->
 
805
    false.
 
806
 
 
807
%% @spec atom_val(cerl())-> atom()
 
808
%%
 
809
%% @doc Returns the value represented by an abstract atom.
 
810
%%
 
811
%% @see c_atom/1
 
812
 
 
813
atom_val(Node) ->
 
814
    Node#literal.val.
 
815
 
 
816
 
 
817
%% @spec atom_name(cerl()) -> string()
 
818
%%
 
819
%% @doc Returns the printname of an abstract atom.
 
820
%%
 
821
%% @see c_atom/1
 
822
 
 
823
atom_name(Node) ->
 
824
    atom_to_list(atom_val(Node)).
 
825
 
 
826
 
 
827
%% @spec atom_lit(cerl()) -> string()
 
828
%%
 
829
%% @doc Returns the literal string represented by an abstract
 
830
%% atom. This always includes surrounding single-quote characters.
 
831
%%
 
832
%% <p>Note that an abstract atom may have several literal
 
833
%% representations, and that the representation yielded by this
 
834
%% function is not fixed; e.g.,
 
835
%% <code>atom_lit(c_atom("a\012b"))</code> could yield the string
 
836
%% <code>"\'a\\nb\'"</code>.</p>
 
837
%%
 
838
%% @see c_atom/1
 
839
 
 
840
%% TODO: replace the use of the unofficial 'write_string/2'.
 
841
 
 
842
atom_lit(Node) ->
 
843
    io_lib:write_string(atom_name(Node), $'). %' stupid Emacs.
 
844
 
 
845
 
 
846
%% ---------------------------------------------------------------------
 
847
 
 
848
%% @spec c_char(Value) -> cerl()
 
849
%%
 
850
%%    Value = char() | integer()
 
851
%%
 
852
%% @doc Creates an abstract character literal. If the local
 
853
%% implementation of Erlang defines <code>char()</code> as a subset of
 
854
%% <code>integer()</code>, this function is equivalent to
 
855
%% <code>c_int/1</code>. Otherwise, if the given value is an integer,
 
856
%% it will be converted to the character with the corresponding
 
857
%% code. The lexical representation of a character is
 
858
%% "<code>$<em>Char</em></code>", where <code>Char</code> is a single
 
859
%% printing character or an escape sequence.
 
860
%%
 
861
%% @see c_int/1
 
862
%% @see c_string/1
 
863
%% @see ann_c_char/2
 
864
%% @see is_c_char/1
 
865
%% @see char_val/1
 
866
%% @see char_lit/1
 
867
%% @see is_print_char/1
 
868
 
 
869
c_char(Value)  when integer(Value), Value >= 0 ->
 
870
    #literal{val = Value}.
 
871
 
 
872
 
 
873
%% @spec ann_c_char(As::[term()], Value::char()) -> cerl()
 
874
%% @see c_char/1
 
875
 
 
876
ann_c_char(As, Value) ->
 
877
    #literal{val = Value, ann = As}.
 
878
 
 
879
 
 
880
%% @spec is_c_char(Node::cerl()) -> boolean()
 
881
%%
 
882
%% @doc Returns <code>true</code> if <code>Node</code> may represent a
 
883
%% character literal, otherwise <code>false</code>.
 
884
%%
 
885
%% <p>If the local implementation of Erlang defines
 
886
%% <code>char()</code> as a subset of <code>integer()</code>, then
 
887
%% <code>is_c_int(<em>Node</em>)</code> will also yield
 
888
%% <code>true</code>.</p>
 
889
%%
 
890
%% @see c_char/1
 
891
%% @see is_print_char/1
 
892
 
 
893
is_c_char(#literal{val = V}) when integer(V), V >= 0 ->
 
894
    is_char_value(V);
 
895
is_c_char(_) ->
 
896
    false.
 
897
 
 
898
 
 
899
%% @spec is_print_char(Node::cerl()) -> boolean()
 
900
%%
 
901
%% @doc Returns <code>true</code> if <code>Node</code> may represent a
 
902
%% "printing" character, otherwise <code>false</code>. (Cf.
 
903
%% <code>is_c_char/1</code>.)  A "printing" character has either a
 
904
%% given graphical representation, or a "named" escape sequence such
 
905
%% as "<code>\n</code>". Currently, only ISO 8859-1 (Latin-1)
 
906
%% character values are recognized.
 
907
%%
 
908
%% @see c_char/1
 
909
%% @see is_c_char/1
 
910
 
 
911
is_print_char(#literal{val = V}) when integer(V), V >= 0 ->
 
912
    is_print_char_value(V);
 
913
is_print_char(_) ->
 
914
    false.
 
915
 
 
916
 
 
917
%% @spec char_val(cerl()) -> char()
 
918
%%
 
919
%% @doc Returns the value represented by an abstract character literal.
 
920
%%
 
921
%% @see c_char/1
 
922
 
 
923
char_val(Node) ->
 
924
    Node#literal.val.
 
925
 
 
926
 
 
927
%% @spec char_lit(cerl()) -> string()
 
928
%%
 
929
%% @doc Returns the literal string represented by an abstract
 
930
%% character. This includes a leading <code>$</code>
 
931
%% character. Currently, all characters that are not in the set of ISO
 
932
%% 8859-1 (Latin-1) "printing" characters will be escaped.
 
933
%%
 
934
%% @see c_char/1
 
935
 
 
936
char_lit(Node) ->
 
937
    io_lib:write_char(char_val(Node)).
 
938
 
 
939
 
 
940
%% ---------------------------------------------------------------------
 
941
 
 
942
%% @spec c_string(Value::string()) -> cerl()
 
943
%%
 
944
%% @doc Creates an abstract string literal. Equivalent to creating an
 
945
%% abstract list of the corresponding character literals
 
946
%% (cf. <code>is_c_string/1</code>), but is typically more
 
947
%% efficient. The lexical representation of a string is
 
948
%% "<code>"<em>Chars</em>"</code>", where <code>Chars</code> is a
 
949
%% sequence of printing characters or spaces.
 
950
%%
 
951
%% @see c_char/1
 
952
%% @see ann_c_string/2
 
953
%% @see is_c_string/1
 
954
%% @see string_val/1
 
955
%% @see string_lit/1
 
956
%% @see is_print_string/1
 
957
 
 
958
c_string(Value) ->
 
959
    #literal{val = Value}.
 
960
 
 
961
 
 
962
%% @spec ann_c_string(As::[term()], Value::string()) -> cerl()
 
963
%% @see c_string/1
 
964
 
 
965
ann_c_string(As, Value) ->
 
966
    #literal{val = Value, ann = As}.
 
967
 
 
968
 
 
969
%% @spec is_c_string(Node::cerl()) -> boolean()
 
970
%%
 
971
%% @doc Returns <code>true</code> if <code>Node</code> may represent a
 
972
%% string literal, otherwise <code>false</code>. Strings are defined
 
973
%% as lists of characters; see <code>is_c_char/1</code> for details.
 
974
%%
 
975
%% @see c_string/1
 
976
%% @see is_c_char/1
 
977
%% @see is_print_string/1
 
978
 
 
979
is_c_string(#literal{val = V}) ->
 
980
    is_char_list(V);
 
981
is_c_string(_) ->
 
982
    false.
 
983
 
 
984
 
 
985
%% @spec is_print_string(Node::cerl()) -> boolean()
 
986
%%
 
987
%% @doc Returns <code>true</code> if <code>Node</code> may represent a
 
988
%% string literal containing only "printing" characters, otherwise
 
989
%% <code>false</code>. See <code>is_c_string/1</code> and
 
990
%% <code>is_print_char/1</code> for details. Currently, only ISO
 
991
%% 8859-1 (Latin-1) character values are recognized.
 
992
%%
 
993
%% @see c_string/1
 
994
%% @see is_c_string/1
 
995
%% @see is_print_char/1
 
996
 
 
997
is_print_string(#literal{val = V}) ->
 
998
    is_print_char_list(V);
 
999
is_print_string(_) ->
 
1000
    false.
 
1001
 
 
1002
 
 
1003
%% @spec string_val(cerl()) -> string()
 
1004
%%
 
1005
%% @doc Returns the value represented by an abstract string literal.
 
1006
%%
 
1007
%% @see c_string/1
 
1008
 
 
1009
string_val(Node) ->
 
1010
    Node#literal.val.
 
1011
 
 
1012
 
 
1013
%% @spec string_lit(cerl()) -> string()
 
1014
%%
 
1015
%% @doc Returns the literal string represented by an abstract string.
 
1016
%% This includes surrounding double-quote characters
 
1017
%% <code>"..."</code>. Currently, characters that are not in the set
 
1018
%% of ISO 8859-1 (Latin-1) "printing" characters will be escaped,
 
1019
%% except for spaces.
 
1020
%%
 
1021
%% @see c_string/1
 
1022
 
 
1023
string_lit(Node) ->
 
1024
    io_lib:write_string(string_val(Node)).
 
1025
 
 
1026
 
 
1027
%% ---------------------------------------------------------------------
 
1028
 
 
1029
%% @spec c_nil() -> cerl()
 
1030
%%
 
1031
%% @doc Creates an abstract empty list. The result represents
 
1032
%% "<code>[]</code>". The empty list is traditionally called "nil".
 
1033
%%
 
1034
%% @see ann_c_nil/1
 
1035
%% @see is_c_list/1
 
1036
%% @see c_cons/2
 
1037
 
 
1038
c_nil() ->
 
1039
    #literal{val = []}.
 
1040
 
 
1041
 
 
1042
%% @spec ann_c_nil(As::[term()]) -> cerl()
 
1043
%% @see c_nil/0
 
1044
 
 
1045
ann_c_nil(As) ->
 
1046
    #literal{val = [], ann = As}.
 
1047
 
 
1048
 
 
1049
%% @spec is_c_nil(Node::cerl()) -> boolean()
 
1050
%%
 
1051
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1052
%% empty list, otherwise <code>false</code>.
 
1053
 
 
1054
is_c_nil(#literal{val = []}) ->
 
1055
    true;
 
1056
is_c_nil(_) ->
 
1057
    false.
 
1058
 
 
1059
 
 
1060
%% ---------------------------------------------------------------------
 
1061
 
 
1062
%% @spec c_cons(Head::cerl(), Tail::cerl()) -> cerl()
 
1063
%%
 
1064
%% @doc Creates an abstract list constructor. The result represents
 
1065
%% "<code>[<em>Head</em> | <em>Tail</em>]</code>". Note that if both
 
1066
%% <code>Head</code> and <code>Tail</code> have type
 
1067
%% <code>literal</code>, then the result will also have type
 
1068
%% <code>literal</code>, and annotations on <code>Head</code> and
 
1069
%% <code>Tail</code> are lost.
 
1070
%%
 
1071
%% <p>Recall that in Erlang, the tail element of a list constructor is
 
1072
%% not necessarily a list.</p>
 
1073
%%
 
1074
%% @see ann_c_cons/3
 
1075
%% @see update_c_cons/3
 
1076
%% @see c_cons_skel/2
 
1077
%% @see is_c_cons/1
 
1078
%% @see cons_hd/1
 
1079
%% @see cons_tl/1
 
1080
%% @see is_c_list/1
 
1081
%% @see c_nil/0
 
1082
%% @see list_elements/1
 
1083
%% @see list_length/1
 
1084
%% @see make_list/2
 
1085
 
 
1086
-record(cons, {ann = [], hd, tl}).
 
1087
 
 
1088
%% *Always* collapse literals.
 
1089
 
 
1090
c_cons(#literal{val = Head}, #literal{val = Tail}) ->
 
1091
    #literal{val = [Head | Tail]};
 
1092
c_cons(Head, Tail) ->
 
1093
    #cons{hd = Head, tl = Tail}.
 
1094
 
 
1095
 
 
1096
%% @spec ann_c_cons(As::[term()], Head::cerl(), Tail::cerl()) -> cerl()
 
1097
%% @see c_cons/2
 
1098
 
 
1099
ann_c_cons(As, #literal{val = Head}, #literal{val = Tail}) ->
 
1100
    #literal{val = [Head | Tail], ann = As};
 
1101
ann_c_cons(As, Head, Tail) ->
 
1102
    #cons{hd = Head, tl = Tail, ann = As}.
 
1103
 
 
1104
 
 
1105
%% @spec update_c_cons(Old::cerl(), Head::cerl(), Tail::cerl()) ->
 
1106
%%           cerl()
 
1107
%% @see c_cons/2
 
1108
 
 
1109
update_c_cons(Node, #literal{val = Head}, #literal{val = Tail}) ->
 
1110
    #literal{val = [Head | Tail], ann = get_ann(Node)};
 
1111
update_c_cons(Node, Head, Tail) ->
 
1112
    #cons{hd = Head, tl = Tail, ann = get_ann(Node)}.
 
1113
 
 
1114
 
 
1115
%% @spec c_cons_skel(Head::cerl(), Tail::cerl()) -> cerl()
 
1116
%%
 
1117
%% @doc Creates an abstract list constructor skeleton. Does not fold
 
1118
%% constant literals, i.e., the result always has type
 
1119
%% <code>cons</code>, representing "<code>[<em>Head</em> |
 
1120
%% <em>Tail</em>]</code>".
 
1121
%%
 
1122
%% <p>This function is occasionally useful when it is necessary to have
 
1123
%% annotations on the subnodes of a list constructor node, even when the
 
1124
%% subnodes are constant literals. Note however that
 
1125
%% <code>is_literal/1</code> will yield <code>false</code> and
 
1126
%% <code>concrete/1</code> will fail if passed the result from this
 
1127
%% function.</p>
 
1128
%%
 
1129
%% <p><code>fold_literal/1</code> can be used to revert a node to the
 
1130
%% normal-form representation.</p>
 
1131
%%
 
1132
%% @see ann_c_cons_skel/3
 
1133
%% @see update_c_cons_skel/3
 
1134
%% @see c_cons/2
 
1135
%% @see is_c_cons/1
 
1136
%% @see is_c_list/1
 
1137
%% @see c_nil/0
 
1138
%% @see is_literal/1
 
1139
%% @see fold_literal/1
 
1140
%% @see concrete/1
 
1141
 
 
1142
%% *Never* collapse literals.
 
1143
 
 
1144
c_cons_skel(Head, Tail) ->
 
1145
    #cons{hd = Head, tl = Tail}.
 
1146
 
 
1147
 
 
1148
%% @spec ann_c_cons_skel(As::[term()], Head::cerl(), Tail::cerl()) ->
 
1149
%%           cerl()
 
1150
%% @see c_cons_skel/2
 
1151
 
 
1152
ann_c_cons_skel(As, Head, Tail) ->
 
1153
    #cons{hd = Head, tl = Tail, ann = As}.
 
1154
 
 
1155
 
 
1156
%% @spec update_c_cons_skel(Old::cerl(), Head::cerl(), Tail::cerl()) ->
 
1157
%%           cerl()
 
1158
%% @see c_cons_skel/2
 
1159
 
 
1160
update_c_cons_skel(Node, Head, Tail) ->
 
1161
    #cons{hd = Head, tl = Tail, ann = get_ann(Node)}.
 
1162
 
 
1163
 
 
1164
%% @spec is_c_cons(Node::cerl()) -> boolean()
 
1165
%%
 
1166
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1167
%% list constructor, otherwise <code>false</code>.
 
1168
 
 
1169
is_c_cons(#cons{}) ->
 
1170
    true;
 
1171
is_c_cons(#literal{val = [_ | _]}) ->
 
1172
    true;
 
1173
is_c_cons(_) ->
 
1174
    false.
 
1175
 
 
1176
 
 
1177
%% @spec cons_hd(cerl()) -> cerl()
 
1178
%%
 
1179
%% @doc Returns the head subtree of an abstract list constructor.
 
1180
%%
 
1181
%% @see c_cons/2
 
1182
 
 
1183
cons_hd(#cons{hd = Head}) ->
 
1184
    Head;
 
1185
cons_hd(#literal{val = [Head | _]}) ->
 
1186
    #literal{val = Head}.
 
1187
 
 
1188
 
 
1189
%% @spec cons_tl(cerl()) -> cerl()
 
1190
%%
 
1191
%% @doc Returns the tail subtree of an abstract list constructor.
 
1192
%%
 
1193
%% <p>Recall that the tail does not necessarily represent a proper
 
1194
%% list.</p>
 
1195
%%
 
1196
%% @see c_cons/2
 
1197
 
 
1198
cons_tl(#cons{tl = Tail}) ->
 
1199
    Tail;
 
1200
cons_tl(#literal{val = [_ | Tail]}) ->
 
1201
    #literal{val = Tail}.
 
1202
 
 
1203
 
 
1204
%% @spec is_c_list(Node::cerl()) -> boolean()
 
1205
%%
 
1206
%% @doc Returns <code>true</code> if <code>Node</code> represents a
 
1207
%% proper list, otherwise <code>false</code>. A proper list is either
 
1208
%% the empty list <code>[]</code>, or a cons cell <code>[<em>Head</em> |
 
1209
%% <em>Tail</em>]</code>, where recursively <code>Tail</code> is a
 
1210
%% proper list.
 
1211
%% 
 
1212
%% <p>Note: Because <code>Node</code> is a syntax tree, the actual
 
1213
%% run-time values corresponding to its subtrees may often be partially
 
1214
%% or completely unknown. Thus, if <code>Node</code> represents e.g.
 
1215
%% "<code>[... | Ns]</code>" (where <code>Ns</code> is a variable), then
 
1216
%% the function will return <code>false</code>, because it is not known
 
1217
%% whether <code>Ns</code> will be bound to a list at run-time. If
 
1218
%% <code>Node</code> instead represents e.g. "<code>[1, 2, 3]</code>" or
 
1219
%% "<code>[A | []]</code>", then the function will return
 
1220
%% <code>true</code>.</p>
 
1221
%%
 
1222
%% @see c_cons/2
 
1223
%% @see c_nil/0
 
1224
%% @see list_elements/1
 
1225
%% @see list_length/1
 
1226
 
 
1227
is_c_list(#cons{tl = Tail}) ->
 
1228
    is_c_list(Tail);
 
1229
is_c_list(#literal{val = V}) ->
 
1230
    is_proper_list(V);
 
1231
is_c_list(_) ->
 
1232
    false.
 
1233
 
 
1234
is_proper_list([_ | Tail]) ->
 
1235
    is_proper_list(Tail);
 
1236
is_proper_list([]) ->
 
1237
    true;
 
1238
is_proper_list(_) ->
 
1239
    false.
 
1240
 
 
1241
%% @spec list_elements(cerl()) -> [cerl()]
 
1242
%%
 
1243
%% @doc Returns the list of element subtrees of an abstract list.
 
1244
%% <code>Node</code> must represent a proper list. E.g., if
 
1245
%% <code>Node</code> represents "<code>[<em>X1</em>, <em>X2</em> |
 
1246
%% [<em>X3</em>, <em>X4</em> | []]</code>", then
 
1247
%% <code>list_elements(Node)</code> yields the list <code>[X1, X2, X3,
 
1248
%% X4]</code>.
 
1249
%%
 
1250
%% @see c_cons/2
 
1251
%% @see c_nil/1
 
1252
%% @see is_c_list/1
 
1253
%% @see list_length/1
 
1254
%% @see make_list/2
 
1255
 
 
1256
list_elements(#cons{hd = Head, tl = Tail}) ->
 
1257
    [Head | list_elements(Tail)];
 
1258
list_elements(#literal{val = V}) ->
 
1259
    abstract_list(V).
 
1260
 
 
1261
abstract_list([X | Xs]) ->
 
1262
    [abstract(X) | abstract_list(Xs)];
 
1263
abstract_list([]) ->
 
1264
    [].
 
1265
 
 
1266
 
 
1267
%% @spec list_length(Node::cerl()) -> integer()
 
1268
%%
 
1269
%% @doc Returns the number of element subtrees of an abstract list.
 
1270
%% <code>Node</code> must represent a proper list. E.g., if
 
1271
%% <code>Node</code> represents "<code>[X1 | [X2, X3 | [X4, X5,
 
1272
%% X6]]]</code>", then <code>list_length(Node)</code> returns the
 
1273
%% integer 6.
 
1274
%%
 
1275
%% <p>Note: this is equivalent to
 
1276
%% <code>length(list_elements(Node))</code>, but potentially more
 
1277
%% efficient.</p>
 
1278
%%
 
1279
%% @see c_cons/2
 
1280
%% @see c_nil/1
 
1281
%% @see is_c_list/1
 
1282
%% @see list_elements/1
 
1283
 
 
1284
list_length(L) ->
 
1285
    list_length(L, 0).
 
1286
 
 
1287
list_length(#cons{tl = Tail}, A) ->
 
1288
    list_length(Tail, A + 1);
 
1289
list_length(#literal{val = V}, A) ->
 
1290
    A + length(V).
 
1291
 
 
1292
 
 
1293
%% @spec make_list(List) -> Node
 
1294
%% @equiv make_list(List, none)
 
1295
 
 
1296
make_list(List) ->
 
1297
    ann_make_list([], List).
 
1298
 
 
1299
 
 
1300
%% @spec make_list(List::[cerl()], Tail) -> cerl()
 
1301
%%
 
1302
%%          Tail = cerl() | none
 
1303
%%
 
1304
%% @doc Creates an abstract list from the elements in <code>List</code>
 
1305
%% and the optional <code>Tail</code>. If <code>Tail</code> is
 
1306
%% <code>none</code>, the result will represent a nil-terminated list,
 
1307
%% otherwise it represents "<code>[... | <em>Tail</em>]</code>".
 
1308
%%
 
1309
%% @see c_cons/2
 
1310
%% @see c_nil/0
 
1311
%% @see ann_make_list/3
 
1312
%% @see update_list/3
 
1313
%% @see list_elements/1
 
1314
 
 
1315
make_list(List, Tail) ->
 
1316
    ann_make_list([], List, Tail).
 
1317
 
 
1318
 
 
1319
%% @spec update_list(Old::cerl(), List::[cerl()]) -> cerl()
 
1320
%% @equiv update_list(Old, List, none)
 
1321
 
 
1322
update_list(Node, List) ->
 
1323
    ann_make_list(get_ann(Node), List).
 
1324
 
 
1325
 
 
1326
%% @spec update_list(Old::cerl(), List::[cerl()], Tail) -> cerl()
 
1327
%%
 
1328
%%          Tail = cerl() | none
 
1329
%%
 
1330
%% @see make_list/2
 
1331
%% @see update_list/2
 
1332
 
 
1333
update_list(Node, List, Tail) ->
 
1334
    ann_make_list(get_ann(Node), List, Tail).
 
1335
 
 
1336
 
 
1337
%% @spec ann_make_list(As::[term()], List::[cerl()]) -> cerl()
 
1338
%% @equiv ann_make_list(As, List, none)
 
1339
 
 
1340
ann_make_list(As, List) ->
 
1341
    ann_make_list(As, List, none).
 
1342
 
 
1343
 
 
1344
%% @spec ann_make_list(As::[term()], List::[cerl()], Tail) -> cerl()
 
1345
%%
 
1346
%%          Tail = cerl() | none
 
1347
%%
 
1348
%% @see make_list/2
 
1349
%% @see ann_make_list/2
 
1350
 
 
1351
ann_make_list(As, [H | T], Tail) ->
 
1352
    ann_c_cons(As, H, make_list(T, Tail));    % `c_cons' folds literals
 
1353
ann_make_list(As, [], none) ->
 
1354
    ann_c_nil(As);
 
1355
ann_make_list(_, [], Node) ->
 
1356
    Node.
 
1357
 
 
1358
 
 
1359
%% ---------------------------------------------------------------------
 
1360
 
 
1361
%% @spec c_tuple(Elements::[cerl()]) -> cerl()
 
1362
%%
 
1363
%% @doc Creates an abstract tuple. If <code>Elements</code> is
 
1364
%% <code>[E1, ..., En]</code>, the result represents
 
1365
%% "<code>{<em>E1</em>, ..., <em>En</em>}</code>".  Note that if all
 
1366
%% nodes in <code>Elements</code> have type <code>literal</code>, or if
 
1367
%% <code>Elements</code> is empty, then the result will also have type
 
1368
%% <code>literal</code> and annotations on nodes in
 
1369
%% <code>Elements</code> are lost.
 
1370
%%
 
1371
%% <p>Recall that Erlang has distinct 1-tuples, i.e., <code>{X}</code>
 
1372
%% is always distinct from <code>X</code> itself.</p>
 
1373
%%
 
1374
%% @see ann_c_tuple/2
 
1375
%% @see update_c_tuple/2
 
1376
%% @see is_c_tuple/1
 
1377
%% @see tuple_es/1
 
1378
%% @see tuple_arity/1
 
1379
%% @see c_tuple_skel/1
 
1380
 
 
1381
-record(tuple, {ann = [], es}).
 
1382
 
 
1383
%% *Always* collapse literals.
 
1384
 
 
1385
c_tuple(Es) ->
 
1386
    case is_lit_list(Es) of
 
1387
        false ->
 
1388
            #tuple{es = Es};
 
1389
        true ->
 
1390
            #literal{val = list_to_tuple(lit_list_vals(Es))}
 
1391
    end.
 
1392
 
 
1393
 
 
1394
%% @spec ann_c_tuple(As::[term()], Elements::[cerl()]) -> cerl()
 
1395
%% @see c_tuple/1
 
1396
 
 
1397
ann_c_tuple(As, Es) ->
 
1398
    case is_lit_list(Es) of
 
1399
        false ->
 
1400
            #tuple{es = Es, ann = As};
 
1401
        true ->
 
1402
            #literal{val = list_to_tuple(lit_list_vals(Es)), ann = As}
 
1403
    end.
 
1404
 
 
1405
 
 
1406
%% @spec update_c_tuple(Old::cerl(),  Elements::[cerl()]) -> cerl()
 
1407
%% @see c_tuple/1
 
1408
 
 
1409
update_c_tuple(Node, Es) ->
 
1410
    case is_lit_list(Es) of
 
1411
        false ->
 
1412
            #tuple{es = Es, ann = get_ann(Node)};
 
1413
        true ->
 
1414
            #literal{val = list_to_tuple(lit_list_vals(Es)),
 
1415
                     ann = get_ann(Node)}
 
1416
    end.
 
1417
 
 
1418
 
 
1419
%% @spec c_tuple_skel(Elements::[cerl()]) -> cerl()
 
1420
%%
 
1421
%% @doc Creates an abstract tuple skeleton. Does not fold constant
 
1422
%% literals, i.e., the result always has type <code>tuple</code>,
 
1423
%% representing "<code>{<em>E1</em>, ..., <em>En</em>}</code>", if
 
1424
%% <code>Elements</code> is <code>[E1, ..., En]</code>.
 
1425
%% 
 
1426
%% <p>This function is occasionally useful when it is necessary to have
 
1427
%% annotations on the subnodes of a tuple node, even when all the
 
1428
%% subnodes are constant literals. Note however that
 
1429
%% <code>is_literal/1</code> will yield <code>false</code> and
 
1430
%% <code>concrete/1</code> will fail if passed the result from this
 
1431
%% function.</p>
 
1432
%%
 
1433
%% <p><code>fold_literal/1</code> can be used to revert a node to the
 
1434
%% normal-form representation.</p>
 
1435
%%
 
1436
%% @see ann_c_tuple_skel/2
 
1437
%% @see update_c_tuple_skel/2
 
1438
%% @see c_tuple/1
 
1439
%% @see tuple_es/1
 
1440
%% @see is_c_tuple/1
 
1441
%% @see is_literal/1
 
1442
%% @see fold_literal/1
 
1443
%% @see concrete/1
 
1444
 
 
1445
%% *Never* collapse literals.
 
1446
 
 
1447
c_tuple_skel(Es) ->
 
1448
    #tuple{es = Es}.
 
1449
 
 
1450
 
 
1451
%% @spec ann_c_tuple_skel(As::[term()], Elements::[cerl()]) -> cerl()
 
1452
%% @see c_tuple_skel/1
 
1453
 
 
1454
ann_c_tuple_skel(As, Es) ->
 
1455
    #tuple{es = Es, ann = As}.
 
1456
 
 
1457
 
 
1458
%% @spec update_c_tuple_skel(Old::cerl(), Elements::[cerl()]) -> cerl()
 
1459
%% @see c_tuple_skel/1
 
1460
 
 
1461
update_c_tuple_skel(Old, Es) ->
 
1462
    #tuple{es = Es, ann = get_ann(Old)}.
 
1463
 
 
1464
 
 
1465
%% @spec is_c_tuple(Node::cerl()) -> boolean()
 
1466
%%
 
1467
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1468
%% tuple, otherwise <code>false</code>.
 
1469
%%
 
1470
%% @see c_tuple/1
 
1471
 
 
1472
is_c_tuple(#tuple{}) ->
 
1473
    true;
 
1474
is_c_tuple(#literal{val = V}) when tuple(V) ->
 
1475
    true;
 
1476
is_c_tuple(_) ->
 
1477
    false.
 
1478
 
 
1479
 
 
1480
%% @spec tuple_es(cerl()) -> [cerl()]
 
1481
%%
 
1482
%% @doc Returns the list of element subtrees of an abstract tuple.
 
1483
%%
 
1484
%% @see c_tuple/1
 
1485
 
 
1486
tuple_es(#tuple{es = Es}) ->
 
1487
    Es;
 
1488
tuple_es(#literal{val = V}) ->
 
1489
    make_lit_list(tuple_to_list(V)).
 
1490
 
 
1491
 
 
1492
%% @spec tuple_arity(Node::cerl()) -> integer()
 
1493
%%
 
1494
%% @doc Returns the number of element subtrees of an abstract tuple.
 
1495
%%
 
1496
%% <p>Note: this is equivalent to <code>length(tuple_es(Node))</code>,
 
1497
%% but potentially more efficient.</p>
 
1498
%%
 
1499
%% @see tuple_es/1
 
1500
%% @see c_tuple/1
 
1501
 
 
1502
tuple_arity(#tuple{es = Es}) ->
 
1503
    length(Es);
 
1504
tuple_arity(#literal{val = V}) when tuple(V) ->
 
1505
    size(V).
 
1506
 
 
1507
 
 
1508
%% ---------------------------------------------------------------------
 
1509
 
 
1510
%% @spec c_var(Name::var_name()) -> cerl()
 
1511
%%
 
1512
%%     var_name() = integer() | atom() | {atom(), integer()}
 
1513
%%
 
1514
%% @doc Creates an abstract variable. A variable is identified by its
 
1515
%% name, given by the <code>Name</code> parameter.
 
1516
%%
 
1517
%% <p>If a name is given by a single atom, it should either be a
 
1518
%% "simple" atom which does not need to be single-quoted in Erlang, or
 
1519
%% otherwise its print name should correspond to a proper Erlang
 
1520
%% variable, i.e., begin with an uppercase character or an
 
1521
%% underscore. Names on the form <code>{A, N}</code> represent
 
1522
%% function name variables "<code><em>A</em>/<em>N</em></code>"; these
 
1523
%% are special variables which may be bound only in the function
 
1524
%% definitions of a module or a <code>letrec</code>.  They may not be
 
1525
%% bound in <code>let</code> expressions and cannot occur in clause
 
1526
%% patterns. The atom <code>A</code> in a function name may be any
 
1527
%% atom; the integer <code>N</code> must be nonnegative. The functions
 
1528
%% <code>c_fname/2</code> etc. are utilities for handling function
 
1529
%% name variables.</p>
 
1530
%%
 
1531
%% <p>When printing variable names, they must have the form of proper
 
1532
%% Core Erlang variables and function names. E.g., a name represented
 
1533
%% by an integer such as <code>42</code> could be formatted as
 
1534
%% "<code>_42</code>", an atom <code>'Xxx'</code> simply as
 
1535
%% "<code>Xxx</code>", and an atom <code>foo</code> as
 
1536
%% "<code>_foo</code>". However, one must assure that any two valid
 
1537
%% distinct names are never mapped to the same strings.  Tuples such
 
1538
%% as <code>{foo, 2}</code> representing function names can simply by
 
1539
%% formatted as "<code>'foo'/2</code>", with no risk of conflicts.</p>
 
1540
%%
 
1541
%% @see ann_c_var/2
 
1542
%% @see update_c_var/2
 
1543
%% @see is_c_var/1
 
1544
%% @see var_name/1
 
1545
%% @see c_fname/2
 
1546
%% @see c_module/4
 
1547
%% @see c_letrec/2
 
1548
 
 
1549
-record(var, {ann = [], name}).
 
1550
 
 
1551
c_var(Name) ->
 
1552
    #var{name = Name}.
 
1553
 
 
1554
 
 
1555
%% @spec ann_c_var(As::[term()], Name::var_name()) -> cerl()
 
1556
%%
 
1557
%% @see c_var/1
 
1558
 
 
1559
ann_c_var(As, Name) ->
 
1560
    #var{name = Name, ann = As}.
 
1561
 
 
1562
%% @spec update_c_var(Old::cerl(), Name::var_name()) -> cerl()
 
1563
%%
 
1564
%% @see c_var/1
 
1565
 
 
1566
update_c_var(Node, Name) ->
 
1567
    #var{name = Name, ann = get_ann(Node)}.
 
1568
 
 
1569
 
 
1570
%% @spec is_c_var(Node::cerl()) -> boolean()
 
1571
%%
 
1572
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1573
%% variable, otherwise <code>false</code>.
 
1574
%%
 
1575
%% @see c_var/1
 
1576
 
 
1577
is_c_var(#var{}) ->
 
1578
    true;
 
1579
is_c_var(_) ->
 
1580
    false.
 
1581
 
 
1582
 
 
1583
%% @spec c_fname(Name::atom(), Arity::integer()) -> cerl()
 
1584
%% @equiv c_var({Name, Arity})
 
1585
%% @see fname_id/1
 
1586
%% @see fname_arity/1
 
1587
%% @see is_c_fname/1
 
1588
%% @see ann_c_fname/3
 
1589
%% @see update_c_fname/3
 
1590
 
 
1591
c_fname(Atom, Arity) ->
 
1592
    c_var({Atom, Arity}).
 
1593
 
 
1594
 
 
1595
%% @spec ann_c_fname(As::[term()], Name::atom(), Arity::integer()) ->
 
1596
%%           cerl()
 
1597
%% @equiv ann_c_var(As, {Atom, Arity})
 
1598
%% @see c_fname/2
 
1599
 
 
1600
ann_c_fname(As, Atom, Arity) ->
 
1601
    ann_c_var(As, {Atom, Arity}).
 
1602
 
 
1603
 
 
1604
%% @spec update_c_fname(Old::cerl(), Name::atom()) -> cerl()
 
1605
%% @doc Like <code>update_c_fname/3</code>, but takes the arity from
 
1606
%% <code>Node</code>.
 
1607
%% @see update_c_fname/3
 
1608
%% @see c_fname/2
 
1609
 
 
1610
update_c_fname(#var{name = {_, Arity}, ann = As}, Atom) ->
 
1611
    #var{name = {Atom, Arity}, ann = As}.
 
1612
 
 
1613
 
 
1614
%% @spec update_c_fname(Old::cerl(), Name::atom(), Arity::integer()) ->
 
1615
%%           cerl()
 
1616
%% @equiv update_c_var(Old, {Atom, Arity})
 
1617
%% @see update_c_fname/2
 
1618
%% @see c_fname/2
 
1619
 
 
1620
update_c_fname(Node, Atom, Arity) ->
 
1621
    update_c_var(Node, {Atom, Arity}).
 
1622
 
 
1623
 
 
1624
%% @spec is_c_fname(Node::cerl()) -> boolean()
 
1625
%%
 
1626
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1627
%% function name variable, otherwise <code>false</code>.
 
1628
%%
 
1629
%% @see c_fname/2
 
1630
%% @see c_var/1
 
1631
%% @see c_var_name/1
 
1632
 
 
1633
is_c_fname(#var{name = {A, N}}) when atom(A), integer(N), N >= 0 ->
 
1634
    true;
 
1635
is_c_fname(_) ->
 
1636
    false.
 
1637
 
 
1638
 
 
1639
%% @spec var_name(cerl()) -> var_name()
 
1640
%%
 
1641
%% @doc Returns the name of an abstract variable.
 
1642
%%
 
1643
%% @see c_var/1
 
1644
 
 
1645
var_name(Node) ->
 
1646
    Node#var.name.
 
1647
 
 
1648
 
 
1649
%% @spec fname_id(cerl()) -> atom()
 
1650
%%
 
1651
%% @doc Returns the identifier part of an abstract function name
 
1652
%% variable.
 
1653
%% 
 
1654
%% @see fname_arity/1
 
1655
%% @see c_fname/2
 
1656
 
 
1657
fname_id(#var{name={A,_}}) ->
 
1658
    A.
 
1659
 
 
1660
 
 
1661
%% @spec fname_arity(cerl()) -> integer()
 
1662
%%
 
1663
%% @doc Returns the arity part of an abstract function name variable.
 
1664
%%
 
1665
%% @see fname_id/1
 
1666
%% @see c_fname/2
 
1667
 
 
1668
fname_arity(#var{name={_,N}}) ->
 
1669
    N.
 
1670
 
 
1671
 
 
1672
%% ---------------------------------------------------------------------
 
1673
 
 
1674
%% @spec c_values(Elements::[cerl()]) -> cerl()
 
1675
%%
 
1676
%% @doc Creates an abstract value list. If <code>Elements</code> is
 
1677
%% <code>[E1, ..., En]</code>, the result represents
 
1678
%% "<code>&lt;<em>E1</em>, ..., <em>En</em>&gt;</code>".
 
1679
%%
 
1680
%% @see ann_c_values/2
 
1681
%% @see update_c_values/2
 
1682
%% @see is_c_values/1
 
1683
%% @see values_es/1
 
1684
%% @see values_arity/1
 
1685
 
 
1686
-record(values, {ann = [], es}).
 
1687
 
 
1688
c_values(Es) ->
 
1689
    #values{es = Es}.
 
1690
 
 
1691
 
 
1692
%% @spec ann_c_values(As::[term()], Elements::[cerl()]) -> cerl()
 
1693
%% @see c_values/1
 
1694
 
 
1695
ann_c_values(As, Es) ->
 
1696
    #values{es = Es, ann = As}.
 
1697
 
 
1698
 
 
1699
%% @spec update_c_values(Old::cerl(), Elements::[cerl()]) -> cerl()
 
1700
%% @see c_values/1
 
1701
 
 
1702
update_c_values(Node, Es) ->
 
1703
    #values{es = Es, ann = get_ann(Node)}.
 
1704
 
 
1705
 
 
1706
%% @spec is_c_values(Node::cerl()) -> boolean()
 
1707
%%
 
1708
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1709
%% value list; otherwise <code>false</code>.
 
1710
%%
 
1711
%% @see c_values/1
 
1712
 
 
1713
is_c_values(#values{}) ->
 
1714
    true;
 
1715
is_c_values(_) ->
 
1716
    false.
 
1717
 
 
1718
 
 
1719
%% @spec values_es(cerl()) -> [cerl()]
 
1720
%%
 
1721
%% @doc Returns the list of element subtrees of an abstract value
 
1722
%% list.
 
1723
%%
 
1724
%% @see c_values/1
 
1725
%% @see values_arity/1
 
1726
 
 
1727
values_es(Node) ->
 
1728
    Node#values.es.
 
1729
 
 
1730
 
 
1731
%% @spec values_arity(Node::cerl()) -> integer()
 
1732
%%
 
1733
%% @doc Returns the number of element subtrees of an abstract value
 
1734
%% list.
 
1735
%% 
 
1736
%% <p>Note: This is equivalent to
 
1737
%% <code>length(values_es(Node))</code>, but potentially more
 
1738
%% efficient.</p>
 
1739
%%
 
1740
%% @see c_values/1
 
1741
%% @see values_es/1
 
1742
 
 
1743
values_arity(Node) ->
 
1744
    length(values_es(Node)).
 
1745
 
 
1746
 
 
1747
%% ---------------------------------------------------------------------
 
1748
 
 
1749
%% @spec c_binary(Segments::[cerl()]) -> cerl()
 
1750
%%
 
1751
%% @doc Creates an abstract binary-template. A binary object is a
 
1752
%% sequence of 8-bit bytes. It is specified by zero or more bit-string
 
1753
%% template <em>segments</em> of arbitrary lengths (in number of bits),
 
1754
%% such that the sum of the lengths is evenly divisible by 8. If
 
1755
%% <code>Segments</code> is <code>[S1, ..., Sn]</code>, the result
 
1756
%% represents "<code>#{<em>S1</em>, ..., <em>Sn</em>}#</code>". All the
 
1757
%% <code>Si</code> must have type <code>bitstr</code>.
 
1758
%%
 
1759
%% @see ann_c_binary/2
 
1760
%% @see update_c_binary/2
 
1761
%% @see is_c_binary/1
 
1762
%% @see binary_segments/1
 
1763
%% @see c_bitstr/5
 
1764
 
 
1765
-record(binary, {ann = [], segments}).
 
1766
 
 
1767
c_binary(Segments) ->
 
1768
    #binary{segments = Segments}.
 
1769
 
 
1770
 
 
1771
%% @spec ann_c_binary(As::[term()], Segments::[cerl()]) -> cerl()
 
1772
%% @see c_binary/1
 
1773
 
 
1774
ann_c_binary(As, Segments) ->
 
1775
    #binary{segments = Segments, ann = As}.
 
1776
 
 
1777
 
 
1778
%% @spec update_c_binary(Old::cerl(), Segments::[cerl()]) -> cerl()
 
1779
%% @see c_binary/1
 
1780
 
 
1781
update_c_binary(Node, Segments) ->
 
1782
    #binary{segments = Segments, ann = get_ann(Node)}.
 
1783
 
 
1784
 
 
1785
%% @spec is_c_binary(Node::cerl()) -> boolean()
 
1786
%%
 
1787
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1788
%% binary-template; otherwise <code>false</code>.
 
1789
%%
 
1790
%% @see c_binary/1
 
1791
 
 
1792
is_c_binary(#binary{}) ->
 
1793
    true;
 
1794
is_c_binary(_) ->
 
1795
    false.
 
1796
 
 
1797
 
 
1798
%% @spec binary_segments(cerl()) -> [cerl()]
 
1799
%%
 
1800
%% @doc Returns the list of segment subtrees of an abstract
 
1801
%% binary-template.
 
1802
%%
 
1803
%% @see c_binary/1
 
1804
%% @see c_bitstr/5
 
1805
 
 
1806
binary_segments(Node) ->
 
1807
    Node#binary.segments.
 
1808
 
 
1809
 
 
1810
%% @spec c_bitstr(Value::cerl(), Size::cerl(), Unit::cerl(),
 
1811
%%                Type::cerl(), Flags::cerl()) -> cerl()
 
1812
%%
 
1813
%% @doc Creates an abstract bit-string template. These can only occur as
 
1814
%% components of an abstract binary-template (see {@link c_binary/1}).
 
1815
%% The result represents "<code>#&lt;<em>Value</em>&gt;(<em>Size</em>,
 
1816
%% <em>Unit</em>, <em>Type</em>, <em>Flags</em>)</code>", where
 
1817
%% <code>Unit</code> must represent a positive integer constant,
 
1818
%% <code>Type</code> must represent a constant atom (one of
 
1819
%% <code>'integer'</code>, <code>'float'</code>, or
 
1820
%% <code>'binary'</code>), and <code>Flags</code> must represent a
 
1821
%% constant list <code>"[<em>F1</em>, ..., <em>Fn</em>]"</code> where
 
1822
%% all the <code>Fi</code> are atoms.
 
1823
%% 
 
1824
%% @see c_binary/1
 
1825
%% @see ann_c_bitstr/6
 
1826
%% @see update_c_bitstr/6
 
1827
%% @see is_c_bitstr/1
 
1828
%% @see bitstr_val/1
 
1829
%% @see bitstr_size/1
 
1830
%% @see bitstr_unit/1
 
1831
%% @see bitstr_type/1
 
1832
%% @see bitstr_flags/1
 
1833
 
 
1834
-record(bitstr, {ann = [], val, size, unit, type, flags}).
 
1835
 
 
1836
c_bitstr(Val, Size, Unit, Type, Flags) ->
 
1837
    #bitstr{val = Val, size = Size, unit = Unit, type = Type,
 
1838
            flags = Flags}.
 
1839
 
 
1840
 
 
1841
%% @spec c_bitstr(Value::cerl(), Size::cerl(), Type::cerl(),
 
1842
%%                Flags::cerl()) -> cerl()
 
1843
%% @equiv c_bitstr(Value, Size, abstract(1), Type, Flags)
 
1844
 
 
1845
c_bitstr(Val, Size, Type, Flags) ->
 
1846
    c_bitstr(Val, Size, abstract(1), Type, Flags).
 
1847
 
 
1848
 
 
1849
%% @spec c_bitstr(Value::cerl(), Type::cerl(),
 
1850
%%                Flags::cerl()) -> cerl()
 
1851
%% @equiv c_bitstr(Value, abstract(all), abstract(1), Type, Flags)
 
1852
 
 
1853
c_bitstr(Val, Type, Flags) ->
 
1854
    c_bitstr(Val, abstract(all), abstract(1), Type, Flags).
 
1855
 
 
1856
 
 
1857
%% @spec ann_c_bitstr(As::[term()], Value::cerl(), Size::cerl(),
 
1858
%%           Unit::cerl(), Type::cerl(), Flags::cerl()) -> cerl()
 
1859
%% @see c_bitstr/5
 
1860
%% @see ann_c_bitstr/5
 
1861
 
 
1862
ann_c_bitstr(As, Val, Size, Unit, Type, Flags) ->
 
1863
    #bitstr{val = Val, size = Size, unit = Unit, type = Type,
 
1864
             flags = Flags, ann = As}.
 
1865
 
 
1866
%% @spec ann_c_bitstr(As::[term()], Value::cerl(), Size::cerl(),
 
1867
%%                    Type::cerl(), Flags::cerl()) -> cerl()
 
1868
%% @equiv ann_c_bitstr(As, Value, Size, abstract(1), Type, Flags)
 
1869
 
 
1870
ann_c_bitstr(As, Value, Size, Type, Flags) ->
 
1871
    ann_c_bitstr(As, Value, Size, abstract(1), Type, Flags).
 
1872
 
 
1873
 
 
1874
%% @spec update_c_bitstr(Old::cerl(), Value::cerl(), Size::cerl(),
 
1875
%%           Unit::cerl(), Type::cerl(), Flags::cerl()) -> cerl()
 
1876
%% @see c_bitstr/5
 
1877
%% @see update_c_bitstr/5
 
1878
 
 
1879
update_c_bitstr(Node, Val, Size, Unit, Type, Flags) ->
 
1880
    #bitstr{val = Val, size = Size, unit = Unit, type = Type,
 
1881
             flags = Flags, ann = get_ann(Node)}.
 
1882
 
 
1883
 
 
1884
%% @spec update_c_bitstr(Old::cerl(), Value::cerl(), Size::cerl(),
 
1885
%%                       Type::cerl(), Flags::cerl()) -> cerl()
 
1886
%% @equiv update_c_bitstr(Node, Value, Size, abstract(1), Type, Flags)
 
1887
 
 
1888
update_c_bitstr(Node, Value, Size, Type, Flags) ->
 
1889
    update_c_bitstr(Node, Value, Size, abstract(1), Type, Flags).
 
1890
 
 
1891
%% @spec is_c_bitstr(Node::cerl()) -> boolean()
 
1892
%%
 
1893
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
1894
%% bit-string template; otherwise <code>false</code>.
 
1895
%%
 
1896
%% @see c_bitstr/5
 
1897
 
 
1898
is_c_bitstr(#bitstr{}) ->
 
1899
    true;
 
1900
is_c_bitstr(_) ->
 
1901
    false.
 
1902
 
 
1903
 
 
1904
%% @spec bitstr_val(cerl()) -> cerl()
 
1905
%%
 
1906
%% @doc Returns the value subtree of an abstract bit-string template.
 
1907
%%
 
1908
%% @see c_bitstr/5
 
1909
 
 
1910
bitstr_val(Node) ->
 
1911
    Node#bitstr.val.
 
1912
 
 
1913
 
 
1914
%% @spec bitstr_size(cerl()) -> cerl()
 
1915
%%
 
1916
%% @doc Returns the size subtree of an abstract bit-string template.
 
1917
%%
 
1918
%% @see c_bitstr/5
 
1919
 
 
1920
bitstr_size(Node) ->
 
1921
    Node#bitstr.size.
 
1922
 
 
1923
 
 
1924
%% @spec bitstr_bitsize(cerl()) -> integer() | any | all
 
1925
%%
 
1926
%% @doc Returns the total size in bits of an abstract bit-string
 
1927
%% template. If the size field is an integer literal, the result is the
 
1928
%% product of the size and unit values; if the size field is the atom
 
1929
%% literal <code>all</code>, the atom <code>all</code> is returned; in
 
1930
%% all other cases, the atom <code>any</code> is returned.
 
1931
%%
 
1932
%% @see c_bitstr/5
 
1933
 
 
1934
bitstr_bitsize(Node) ->
 
1935
    Size = Node#bitstr.size,
 
1936
    case is_literal(Size) of
 
1937
        true ->
 
1938
            case concrete(Size) of
 
1939
                all ->
 
1940
                    all;
 
1941
                S when integer(S) ->
 
1942
                    S*concrete(Node#bitstr.unit);
 
1943
                true ->
 
1944
                    any
 
1945
            end;
 
1946
        false ->
 
1947
            any
 
1948
    end.
 
1949
 
 
1950
 
 
1951
%% @spec bitstr_unit(cerl()) -> cerl()
 
1952
%%
 
1953
%% @doc Returns the unit subtree of an abstract bit-string template.
 
1954
%%
 
1955
%% @see c_bitstr/5
 
1956
 
 
1957
bitstr_unit(Node) ->
 
1958
    Node#bitstr.unit.
 
1959
 
 
1960
 
 
1961
%% @spec bitstr_type(cerl()) -> cerl()
 
1962
%%
 
1963
%% @doc Returns the type subtree of an abstract bit-string template.
 
1964
%%
 
1965
%% @see c_bitstr/5
 
1966
 
 
1967
bitstr_type(Node) ->
 
1968
    Node#bitstr.type.
 
1969
 
 
1970
 
 
1971
%% @spec bitstr_flags(cerl()) -> cerl()
 
1972
%%
 
1973
%% @doc Returns the flags subtree of an abstract bit-string template.
 
1974
%%
 
1975
%% @see c_bitstr/5
 
1976
 
 
1977
bitstr_flags(Node) ->
 
1978
    Node#bitstr.flags.
 
1979
 
 
1980
 
 
1981
%% ---------------------------------------------------------------------
 
1982
 
 
1983
%% @spec c_fun(Variables::[cerl()], Body::cerl()) -> cerl()
 
1984
%%
 
1985
%% @doc Creates an abstract fun-expression. If <code>Variables</code>
 
1986
%% is <code>[V1, ..., Vn]</code>, the result represents "<code>fun
 
1987
%% (<em>V1</em>, ..., <em>Vn</em>) -> <em>Body</em></code>". All the
 
1988
%% <code>Vi</code> must have type <code>var</code>.
 
1989
%%
 
1990
%% @see ann_c_fun/3
 
1991
%% @see update_c_fun/3
 
1992
%% @see is_c_fun/1
 
1993
%% @see fun_vars/1
 
1994
%% @see fun_body/1
 
1995
%% @see fun_arity/1
 
1996
 
 
1997
-record('fun', {ann = [], vars, body}).
 
1998
 
 
1999
c_fun(Variables, Body) ->
 
2000
    #'fun'{vars = Variables, body = Body}.
 
2001
 
 
2002
 
 
2003
%% @spec ann_c_fun(As::[term()], Variables::[cerl()], Body::cerl()) ->
 
2004
%%           cerl()
 
2005
%% @see c_fun/2
 
2006
 
 
2007
ann_c_fun(As, Variables, Body) ->
 
2008
    #'fun'{vars = Variables, body = Body, ann = As}.
 
2009
 
 
2010
 
 
2011
%% @spec update_c_fun(Old::cerl(), Variables::[cerl()],
 
2012
%%                    Body::cerl()) -> cerl()
 
2013
%% @see c_fun/2
 
2014
 
 
2015
update_c_fun(Node, Variables, Body) ->
 
2016
    #'fun'{vars = Variables, body = Body, ann = get_ann(Node)}.
 
2017
 
 
2018
 
 
2019
%% @spec is_c_fun(Node::cerl()) -> boolean()
 
2020
%%
 
2021
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2022
%% fun-expression, otherwise <code>false</code>.
 
2023
%%
 
2024
%% @see c_fun/2
 
2025
 
 
2026
is_c_fun(#'fun'{}) ->
 
2027
    true;               % Now this is fun!
 
2028
is_c_fun(_) ->
 
2029
    false.
 
2030
 
 
2031
 
 
2032
%% @spec fun_vars(cerl()) -> [cerl()]
 
2033
%%
 
2034
%% @doc Returns the list of parameter subtrees of an abstract
 
2035
%% fun-expression.
 
2036
%%
 
2037
%% @see c_fun/2
 
2038
%% @see fun_arity/1
 
2039
 
 
2040
fun_vars(Node) ->
 
2041
    Node#'fun'.vars.
 
2042
 
 
2043
 
 
2044
%% @spec fun_body(cerl()) -> cerl()
 
2045
%%
 
2046
%% @doc Returns the body subtree of an abstract fun-expression.
 
2047
%%
 
2048
%% @see c_fun/2
 
2049
 
 
2050
fun_body(Node) ->
 
2051
    Node#'fun'.body.
 
2052
 
 
2053
 
 
2054
%% @spec fun_arity(Node::cerl()) -> integer()
 
2055
%%
 
2056
%% @doc Returns the number of parameter subtrees of an abstract
 
2057
%% fun-expression.
 
2058
%% 
 
2059
%% <p>Note: this is equivalent to <code>length(fun_vars(Node))</code>,
 
2060
%% but potentially more efficient.</p>
 
2061
%%
 
2062
%% @see c_fun/2
 
2063
%% @see fun_vars/1
 
2064
 
 
2065
fun_arity(Node) ->
 
2066
    length(fun_vars(Node)).
 
2067
 
 
2068
 
 
2069
%% ---------------------------------------------------------------------
 
2070
 
 
2071
%% @spec c_seq(Argument::cerl(), Body::cerl()) -> cerl()
 
2072
%%
 
2073
%% @doc Creates an abstract sequencing expression. The result
 
2074
%% represents "<code>do <em>Argument</em> <em>Body</em></code>".
 
2075
%%
 
2076
%% @see ann_c_seq/3
 
2077
%% @see update_c_seq/3
 
2078
%% @see is_c_seq/1
 
2079
%% @see seq_arg/1
 
2080
%% @see seq_body/1
 
2081
 
 
2082
-record(seq, {ann = [], arg, body}).
 
2083
 
 
2084
c_seq(Argument, Body) ->
 
2085
    #seq{arg = Argument, body = Body}.
 
2086
 
 
2087
 
 
2088
%% @spec ann_c_seq(As::[term()], Argument::cerl(), Body::cerl()) ->
 
2089
%%           cerl()
 
2090
%% @see c_seq/2
 
2091
 
 
2092
ann_c_seq(As, Argument, Body) ->
 
2093
    #seq{arg = Argument, body = Body, ann = As}.
 
2094
 
 
2095
 
 
2096
%% @spec update_c_seq(Old::cerl(), Argument::cerl(), Body::cerl()) ->
 
2097
%%           cerl()
 
2098
%% @see c_seq/2
 
2099
 
 
2100
update_c_seq(Node, Argument, Body) ->
 
2101
    #seq{arg = Argument, body = Body, ann = get_ann(Node)}.
 
2102
 
 
2103
 
 
2104
%% @spec is_c_seq(Node::cerl()) -> boolean()
 
2105
%%
 
2106
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2107
%% sequencing expression, otherwise <code>false</code>.
 
2108
%%
 
2109
%% @see c_seq/2
 
2110
 
 
2111
is_c_seq(#seq{}) ->
 
2112
    true;
 
2113
is_c_seq(_) ->
 
2114
    false.
 
2115
 
 
2116
 
 
2117
%% @spec seq_arg(cerl()) -> cerl()
 
2118
%%
 
2119
%% @doc Returns the argument subtree of an abstract sequencing
 
2120
%% expression.
 
2121
%%
 
2122
%% @see c_seq/2
 
2123
 
 
2124
seq_arg(Node) ->
 
2125
    Node#seq.arg.
 
2126
 
 
2127
 
 
2128
%% @spec seq_body(cerl()) -> cerl()
 
2129
%%
 
2130
%% @doc Returns the body subtree of an abstract sequencing expression.
 
2131
%%
 
2132
%% @see c_seq/2
 
2133
 
 
2134
seq_body(Node) ->
 
2135
    Node#seq.body.
 
2136
 
 
2137
 
 
2138
%% ---------------------------------------------------------------------
 
2139
 
 
2140
%% @spec c_let(Variables::[cerl()], Argument::cerl(), Body::cerl()) ->
 
2141
%%           cerl()
 
2142
%%
 
2143
%% @doc Creates an abstract let-expression. If <code>Variables</code>
 
2144
%% is <code>[V1, ..., Vn]</code>, the result represents "<code>let
 
2145
%% &lt;<em>V1</em>, ..., <em>Vn</em>&gt; = <em>Argument</em> in
 
2146
%% <em>Body</em></code>".  All the <code>Vi</code> must have type
 
2147
%% <code>var</code>.
 
2148
%%
 
2149
%% @see ann_c_let/4
 
2150
%% @see update_c_let/4
 
2151
%% @see is_c_let/1
 
2152
%% @see let_vars/1
 
2153
%% @see let_arg/1
 
2154
%% @see let_body/1
 
2155
%% @see let_arity/1
 
2156
 
 
2157
-record('let', {ann = [], vars, arg, body}).
 
2158
 
 
2159
c_let(Variables, Argument, Body) ->
 
2160
    #'let'{vars = Variables, arg = Argument, body = Body}.
 
2161
 
 
2162
 
 
2163
%% ann_c_let(As, Variables, Argument, Body) -> Node
 
2164
%% @see c_let/3
 
2165
 
 
2166
ann_c_let(As, Variables, Argument, Body) ->
 
2167
    #'let'{vars = Variables, arg = Argument, body = Body, ann = As}.
 
2168
 
 
2169
 
 
2170
%% update_c_let(Old, Variables, Argument, Body) -> Node
 
2171
%% @see c_let/3
 
2172
 
 
2173
update_c_let(Node, Variables, Argument, Body) ->
 
2174
    #'let'{vars = Variables, arg = Argument, body = Body,
 
2175
           ann = get_ann(Node)}.
 
2176
 
 
2177
 
 
2178
%% @spec is_c_let(Node::cerl()) -> boolean()
 
2179
%%
 
2180
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2181
%% let-expression, otherwise <code>false</code>.
 
2182
%%
 
2183
%% @see c_let/3
 
2184
 
 
2185
is_c_let(#'let'{}) ->
 
2186
    true;
 
2187
is_c_let(_) ->
 
2188
    false.
 
2189
 
 
2190
 
 
2191
%% @spec let_vars(cerl()) -> [cerl()]
 
2192
%%
 
2193
%% @doc Returns the list of left-hand side variables of an abstract
 
2194
%% let-expression.
 
2195
%%
 
2196
%% @see c_let/3
 
2197
%% @see let_arity/1
 
2198
 
 
2199
let_vars(Node) ->
 
2200
    Node#'let'.vars.
 
2201
 
 
2202
 
 
2203
%% @spec let_arg(cerl()) -> cerl()
 
2204
%%
 
2205
%% @doc Returns the argument subtree of an abstract let-expression.
 
2206
%%
 
2207
%% @see c_let/3
 
2208
 
 
2209
let_arg(Node) ->
 
2210
    Node#'let'.arg.
 
2211
 
 
2212
 
 
2213
%% @spec let_body(cerl()) -> cerl()
 
2214
%%
 
2215
%% @doc Returns the body subtree of an abstract let-expression.
 
2216
%%
 
2217
%% @see c_let/3
 
2218
 
 
2219
let_body(Node) ->
 
2220
    Node#'let'.body.
 
2221
 
 
2222
 
 
2223
%% @spec let_arity(Node::cerl()) -> integer()
 
2224
%%
 
2225
%% @doc Returns the number of left-hand side variables of an abstract
 
2226
%% let-expression.
 
2227
%% 
 
2228
%% <p>Note: this is equivalent to <code>length(let_vars(Node))</code>,
 
2229
%% but potentially more efficient.</p>
 
2230
%%
 
2231
%% @see c_let/3
 
2232
%% @see let_vars/1
 
2233
 
 
2234
let_arity(Node) ->
 
2235
    length(let_vars(Node)).
 
2236
 
 
2237
 
 
2238
%% ---------------------------------------------------------------------
 
2239
 
 
2240
%% @spec c_letrec(Definitions::[{cerl(), cerl()}], Body::cerl()) ->
 
2241
%%           cerl()
 
2242
%%
 
2243
%% @doc Creates an abstract letrec-expression. If
 
2244
%% <code>Definitions</code> is <code>[{V1, F1}, ..., {Vn, Fn}]</code>,
 
2245
%% the result represents "<code>letrec <em>V1</em> = <em>F1</em>
 
2246
%% ... <em>Vn</em> = <em>Fn</em> in <em>Body</em></code>.  All the
 
2247
%% <code>Vi</code> must have type <code>var</code> and represent
 
2248
%% function names.  All the <code>Fi</code> must have type
 
2249
%% <code>'fun'</code>.
 
2250
%%
 
2251
%% @see ann_c_letrec/3
 
2252
%% @see update_c_letrec/3
 
2253
%% @see is_c_letrec/1
 
2254
%% @see letrec_defs/1
 
2255
%% @see letrec_body/1
 
2256
%% @see letrec_vars/1
 
2257
 
 
2258
-record(letrec, {ann = [], defs, body}).
 
2259
 
 
2260
c_letrec(Defs, Body) ->
 
2261
    #letrec{defs = Defs, body = Body}.
 
2262
 
 
2263
 
 
2264
%% @spec ann_c_letrec(As::[term()], Definitions::[{cerl(), cerl()}],
 
2265
%%                    Body::cerl()) -> cerl()
 
2266
%% @see c_letrec/2
 
2267
 
 
2268
ann_c_letrec(As, Defs, Body) ->
 
2269
    #letrec{defs = Defs, body = Body, ann = As}.
 
2270
 
 
2271
 
 
2272
%% @spec update_c_letrec(Old::cerl(),
 
2273
%%                       Definitions::[{cerl(), cerl()}],
 
2274
%%                       Body::cerl()) -> cerl()
 
2275
%% @see c_letrec/2
 
2276
 
 
2277
update_c_letrec(Node, Defs, Body) ->
 
2278
    #letrec{defs = Defs, body = Body, ann = get_ann(Node)}.
 
2279
 
 
2280
 
 
2281
%% @spec is_c_letrec(Node::cerl()) -> boolean()
 
2282
%%
 
2283
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2284
%% letrec-expression, otherwise <code>false</code>.
 
2285
%%
 
2286
%% @see c_letrec/2
 
2287
 
 
2288
is_c_letrec(#letrec{}) ->
 
2289
    true;
 
2290
is_c_letrec(_) ->
 
2291
    false.
 
2292
 
 
2293
 
 
2294
%% @spec letrec_defs(Node::cerl()) -> [{cerl(), cerl()}]
 
2295
%%
 
2296
%% @doc Returns the list of definitions of an abstract
 
2297
%% letrec-expression. If <code>Node</code> represents "<code>letrec
 
2298
%% <em>V1</em> = <em>F1</em> ... <em>Vn</em> = <em>Fn</em> in
 
2299
%% <em>Body</em></code>", the returned value is <code>[{V1, F1}, ...,
 
2300
%% {Vn, Fn}]</code>.
 
2301
%%
 
2302
%% @see c_letrec/2
 
2303
 
 
2304
letrec_defs(Node) ->
 
2305
    Node#letrec.defs.
 
2306
 
 
2307
 
 
2308
%% @spec letrec_body(cerl()) -> cerl()
 
2309
%%
 
2310
%% @doc Returns the body subtree of an abstract letrec-expression.
 
2311
%%
 
2312
%% @see c_letrec/2
 
2313
 
 
2314
letrec_body(Node) ->
 
2315
    Node#letrec.body.
 
2316
 
 
2317
 
 
2318
%% @spec letrec_vars(cerl()) -> [cerl()]
 
2319
%%
 
2320
%% @doc Returns the list of left-hand side function variable subtrees
 
2321
%% of a letrec-expression. If <code>Node</code> represents
 
2322
%% "<code>letrec <em>V1</em> = <em>F1</em> ... <em>Vn</em> =
 
2323
%% <em>Fn</em> in <em>Body</em></code>", the returned value is
 
2324
%% <code>[V1, ..., Vn]</code>.
 
2325
%%
 
2326
%% @see c_letrec/2
 
2327
 
 
2328
letrec_vars(Node) ->
 
2329
    [F || {F, _} <- letrec_defs(Node)].
 
2330
 
 
2331
 
 
2332
%% ---------------------------------------------------------------------
 
2333
 
 
2334
%% @spec c_case(Argument::cerl(), Clauses::[cerl()]) -> cerl()
 
2335
%%
 
2336
%% @doc Creates an abstract case-expression. If <code>Clauses</code>
 
2337
%% is <code>[C1, ..., Cn]</code>, the result represents "<code>case
 
2338
%% <em>Argument</em> of <em>C1</em> ... <em>Cn</em>
 
2339
%% end</code>". <code>Clauses</code> must not be empty.
 
2340
%%
 
2341
%% @see ann_c_case/3
 
2342
%% @see update_c_case/3
 
2343
%% @see is_c_case/1
 
2344
%% @see c_clause/3
 
2345
%% @see case_arg/1
 
2346
%% @see case_clauses/1
 
2347
%% @see case_arity/1
 
2348
 
 
2349
-record('case', {ann = [], arg, clauses}).
 
2350
 
 
2351
c_case(Expr, Clauses) ->
 
2352
    #'case'{arg = Expr, clauses = Clauses}.
 
2353
 
 
2354
 
 
2355
%% @spec ann_c_case(As::[term()], Argument::cerl(),
 
2356
%%                  Clauses::[cerl()]) -> cerl()
 
2357
%% @see c_case/2
 
2358
 
 
2359
ann_c_case(As, Expr, Clauses) ->
 
2360
    #'case'{arg = Expr, clauses = Clauses, ann = As}.
 
2361
 
 
2362
 
 
2363
%% @spec update_c_case(Old::cerl(), Argument::cerl(),
 
2364
%%                     Clauses::[cerl()]) -> cerl()
 
2365
%% @see c_case/2
 
2366
 
 
2367
update_c_case(Node, Expr, Clauses) ->
 
2368
    #'case'{arg = Expr, clauses = Clauses, ann = get_ann(Node)}.
 
2369
 
 
2370
 
 
2371
%% is_c_case(Node) -> boolean()
 
2372
%%
 
2373
%%          Node = cerl()
 
2374
%%
 
2375
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2376
%% case-expression; otherwise <code>false</code>.
 
2377
%%
 
2378
%% @see c_case/2
 
2379
 
 
2380
is_c_case(#'case'{}) ->
 
2381
    true;
 
2382
is_c_case(_) ->
 
2383
    false.
 
2384
 
 
2385
 
 
2386
%% @spec case_arg(cerl()) -> cerl()
 
2387
%%
 
2388
%% @doc Returns the argument subtree of an abstract case-expression.
 
2389
%%
 
2390
%% @see c_case/2
 
2391
 
 
2392
case_arg(Node) ->
 
2393
    Node#'case'.arg.
 
2394
 
 
2395
 
 
2396
%% @spec case_clauses(cerl()) -> [cerl()]
 
2397
%%
 
2398
%% @doc Returns the list of clause subtrees of an abstract
 
2399
%% case-expression.
 
2400
%%
 
2401
%% @see c_case/2
 
2402
%% @see case_arity/1
 
2403
 
 
2404
case_clauses(Node) ->
 
2405
    Node#'case'.clauses.
 
2406
 
 
2407
 
 
2408
%% @spec case_arity(Node::cerl()) -> integer()
 
2409
%%
 
2410
%% @doc Equivalent to
 
2411
%% <code>clause_arity(hd(case_clauses(Node)))</code>, but potentially
 
2412
%% more efficient.
 
2413
%%
 
2414
%% @see c_case/2
 
2415
%% @see case_clauses/1
 
2416
%% @see clause_arity/1
 
2417
 
 
2418
case_arity(Node) ->
 
2419
    clause_arity(hd(case_clauses(Node))).
 
2420
 
 
2421
 
 
2422
%% ---------------------------------------------------------------------
 
2423
 
 
2424
%% @spec c_clause(Patterns::[cerl()], Body::cerl()) -> cerl()
 
2425
%% @equiv c_clause(Patterns, c_atom(true), Body)
 
2426
%% @see c_atom/1
 
2427
 
 
2428
c_clause(Patterns, Body) ->
 
2429
    c_clause(Patterns, c_atom(true), Body).
 
2430
 
 
2431
 
 
2432
%% @spec c_clause(Patterns::[cerl()], Guard::cerl(), Body::cerl()) ->
 
2433
%%           cerl()
 
2434
%%
 
2435
%% @doc Creates an an abstract clause. If <code>Patterns</code> is
 
2436
%% <code>[P1, ..., Pn]</code>, the result represents
 
2437
%% "<code>&lt;<em>P1</em>, ..., <em>Pn</em>&gt; when <em>Guard</em> ->
 
2438
%% <em>Body</em></code>".
 
2439
%%
 
2440
%% @see c_clause/2
 
2441
%% @see ann_c_clause/4
 
2442
%% @see update_c_clause/4
 
2443
%% @see is_c_clause/1
 
2444
%% @see c_case/2
 
2445
%% @see c_receive/3
 
2446
%% @see clause_pats/1
 
2447
%% @see clause_guard/1
 
2448
%% @see clause_body/1
 
2449
%% @see clause_arity/1
 
2450
%% @see clause_vars/1
 
2451
 
 
2452
-record(clause, {ann = [], pats, guard, body}).
 
2453
 
 
2454
c_clause(Patterns, Guard, Body) ->
 
2455
    #clause{pats = Patterns, guard = Guard, body = Body}.
 
2456
 
 
2457
 
 
2458
%% @spec ann_c_clause(As::[term()], Patterns::[cerl()],
 
2459
%%                    Body::cerl()) -> cerl()
 
2460
%% @equiv ann_c_clause(As, Patterns, c_atom(true), Body)
 
2461
%% @see c_clause/3
 
2462
ann_c_clause(As, Patterns, Body) ->
 
2463
    ann_c_clause(As, Patterns, c_atom(true), Body).
 
2464
 
 
2465
 
 
2466
%% @spec ann_c_clause(As::[term()], Patterns::[cerl()], Guard::cerl(),
 
2467
%%                    Body::cerl()) -> cerl()
 
2468
%% @see ann_c_clause/3
 
2469
%% @see c_clause/3
 
2470
 
 
2471
ann_c_clause(As, Patterns, Guard, Body) ->
 
2472
    #clause{pats = Patterns, guard = Guard, body = Body, ann = As}.
 
2473
 
 
2474
 
 
2475
%% @spec update_c_clause(Old::cerl(), Patterns::[cerl()],
 
2476
%%                       Guard::cerl(), Body::cerl()) -> cerl()
 
2477
%% @see c_clause/3
 
2478
 
 
2479
update_c_clause(Node, Patterns, Guard, Body) ->
 
2480
    #clause{pats = Patterns, guard = Guard, body = Body,
 
2481
            ann = get_ann(Node)}.
 
2482
 
 
2483
 
 
2484
%% @spec is_c_clause(Node::cerl()) -> boolean()
 
2485
%%
 
2486
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2487
%% clause, otherwise <code>false</code>.
 
2488
%%
 
2489
%% @see c_clause/3
 
2490
 
 
2491
is_c_clause(#clause{}) ->
 
2492
    true;
 
2493
is_c_clause(_) ->
 
2494
    false.
 
2495
 
 
2496
 
 
2497
%% @spec clause_pats(cerl()) -> [cerl()]
 
2498
%%
 
2499
%% @doc Returns the list of pattern subtrees of an abstract clause.
 
2500
%%
 
2501
%% @see c_clause/3
 
2502
%% @see clause_arity/1
 
2503
 
 
2504
clause_pats(Node) ->
 
2505
    Node#clause.pats.
 
2506
 
 
2507
 
 
2508
%% @spec clause_guard(cerl()) -> cerl()
 
2509
%%
 
2510
%% @doc Returns the guard subtree of an abstract clause.
 
2511
%% 
 
2512
%% @see c_clause/3
 
2513
 
 
2514
clause_guard(Node) ->
 
2515
    Node#clause.guard.
 
2516
 
 
2517
 
 
2518
%% @spec clause_body(cerl()) -> cerl()
 
2519
%%
 
2520
%% @doc Returns the body subtree of an abstract clause.
 
2521
%%
 
2522
%% @see c_clause/3
 
2523
 
 
2524
clause_body(Node) ->
 
2525
    Node#clause.body.
 
2526
 
 
2527
 
 
2528
%% @spec clause_arity(Node::cerl()) -> integer()
 
2529
%%
 
2530
%% @doc Returns the number of pattern subtrees of an abstract clause.
 
2531
%%
 
2532
%% <p>Note: this is equivalent to
 
2533
%% <code>length(clause_pats(Node))</code>, but potentially more
 
2534
%% efficient.</p>
 
2535
%%
 
2536
%% @see c_clause/3
 
2537
%% @see clause_pats/1
 
2538
 
 
2539
clause_arity(Node) ->
 
2540
    length(clause_pats(Node)).
 
2541
 
 
2542
 
 
2543
%% @spec clause_vars(cerl()) -> [cerl()]
 
2544
%%
 
2545
%% @doc Returns the list of all abstract variables in the patterns of
 
2546
%% an abstract clause. The order of listing is not defined.
 
2547
%%
 
2548
%% @see c_clause/3
 
2549
%% @see pat_list_vars/1
 
2550
 
 
2551
clause_vars(Clause) ->
 
2552
    pat_list_vars(clause_pats(Clause)).
 
2553
 
 
2554
 
 
2555
%% @spec pat_vars(Pattern::cerl()) -> [cerl()]
 
2556
%%
 
2557
%% @doc Returns the list of all abstract variables in a pattern. An
 
2558
%% exception is thrown if <code>Node</code> does not represent a
 
2559
%% well-formed Core Erlang clause pattern. The order of listing is not
 
2560
%% defined.
 
2561
%%
 
2562
%% @see pat_list_vars/1
 
2563
%% @see clause_vars/1
 
2564
 
 
2565
pat_vars(Node) ->
 
2566
    pat_vars(Node, []).
 
2567
 
 
2568
pat_vars(Node, Vs) ->
 
2569
    case type(Node) of
 
2570
        var ->
 
2571
            [Node | Vs];
 
2572
        literal ->
 
2573
            Vs;
 
2574
        cons ->
 
2575
            pat_vars(cons_hd(Node), pat_vars(cons_tl(Node), Vs));
 
2576
        tuple ->
 
2577
            pat_list_vars(tuple_es(Node), Vs);
 
2578
        binary ->
 
2579
            pat_list_vars(binary_segments(Node), Vs);
 
2580
        bitstr ->
 
2581
            pat_vars(bitstr_val(Node), Vs);
 
2582
        alias ->
 
2583
            pat_vars(alias_pat(Node), [alias_var(Node) | Vs])
 
2584
    end.
 
2585
 
 
2586
 
 
2587
%% @spec pat_list_vars(Patterns::[cerl()]) -> [cerl()]
 
2588
%%
 
2589
%% @doc Returns the list of all abstract variables in the given
 
2590
%% patterns. An exception is thrown if some element in
 
2591
%% <code>Patterns</code> does not represent a well-formed Core Erlang
 
2592
%% clause pattern. The order of listing is not defined.
 
2593
%%
 
2594
%% @see pat_vars/1
 
2595
%% @see clause_vars/1
 
2596
 
 
2597
pat_list_vars(Ps) ->
 
2598
    pat_list_vars(Ps, []).
 
2599
 
 
2600
pat_list_vars([P | Ps], Vs) ->
 
2601
    pat_list_vars(Ps, pat_vars(P, Vs));
 
2602
pat_list_vars([], Vs) ->
 
2603
    Vs.
 
2604
 
 
2605
 
 
2606
%% ---------------------------------------------------------------------
 
2607
 
 
2608
%% @spec c_alias(Variable::cerl(), Pattern::cerl()) -> cerl()
 
2609
%%
 
2610
%% @doc Creates an abstract pattern alias. The result represents
 
2611
%% "<code><em>Variable</em> = <em>Pattern</em></code>".
 
2612
%%
 
2613
%% @see ann_c_alias/3
 
2614
%% @see update_c_alias/3
 
2615
%% @see is_c_alias/1
 
2616
%% @see alias_var/1
 
2617
%% @see alias_pat/1
 
2618
%% @see c_clause/3
 
2619
 
 
2620
-record(alias, {ann = [], var, pat}).
 
2621
 
 
2622
c_alias(Var, Pattern) ->
 
2623
    #alias{var = Var, pat = Pattern}.
 
2624
 
 
2625
 
 
2626
%% @spec ann_c_alias(As::[term()], Variable::cerl(),
 
2627
%%                   Pattern::cerl()) -> cerl()
 
2628
%% @see c_alias/2
 
2629
 
 
2630
ann_c_alias(As, Var, Pattern) ->
 
2631
    #alias{var = Var, pat = Pattern, ann = As}.
 
2632
 
 
2633
 
 
2634
%% @spec update_c_alias(Old::cerl(), Variable::cerl(),
 
2635
%%                      Pattern::cerl()) -> cerl()
 
2636
%% @see c_alias/2
 
2637
 
 
2638
update_c_alias(Node, Var, Pattern) ->
 
2639
    #alias{var = Var, pat = Pattern, ann = get_ann(Node)}.
 
2640
 
 
2641
 
 
2642
%% @spec is_c_alias(Node::cerl()) -> boolean()
 
2643
%%
 
2644
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2645
%% pattern alias, otherwise <code>false</code>.
 
2646
%%
 
2647
%% @see c_alias/2
 
2648
 
 
2649
is_c_alias(#alias{}) ->
 
2650
    true;
 
2651
is_c_alias(_) ->
 
2652
    false.
 
2653
 
 
2654
 
 
2655
%% @spec alias_var(cerl()) -> cerl()
 
2656
%%
 
2657
%% @doc Returns the variable subtree of an abstract pattern alias.
 
2658
%%
 
2659
%% @see c_alias/2
 
2660
 
 
2661
alias_var(Node) ->
 
2662
    Node#alias.var.
 
2663
 
 
2664
 
 
2665
%% @spec alias_pat(cerl()) -> cerl()
 
2666
%%
 
2667
%% @doc Returns the pattern subtree of an abstract pattern alias.
 
2668
%%
 
2669
%% @see c_alias/2
 
2670
 
 
2671
alias_pat(Node) ->
 
2672
    Node#alias.pat.
 
2673
 
 
2674
 
 
2675
%% ---------------------------------------------------------------------
 
2676
 
 
2677
%% @spec c_receive(Clauses::[cerl()]) -> cerl()
 
2678
%% @equiv c_receive(Clauses, c_atom(infinity), c_atom(true))
 
2679
%% @see c_atom/1
 
2680
 
 
2681
c_receive(Clauses) ->
 
2682
    c_receive(Clauses, c_atom(infinity), c_atom(true)).
 
2683
 
 
2684
 
 
2685
%% @spec c_receive(Clauses::[cerl()], Timeout::cerl(),
 
2686
%%                 Action::cerl()) -> cerl()
 
2687
%%
 
2688
%% @doc Creates an abstract receive-expression. If
 
2689
%% <code>Clauses</code> is <code>[C1, ..., Cn]</code>, the result
 
2690
%% represents "<code>receive <em>C1</em> ... <em>Cn</em> after
 
2691
%% <em>Timeout</em> -> <em>Action</em> end</code>".
 
2692
%%
 
2693
%% @see c_receive/1
 
2694
%% @see ann_c_receive/4
 
2695
%% @see update_c_receive/4
 
2696
%% @see is_c_receive/1
 
2697
%% @see receive_clauses/1
 
2698
%% @see receive_timeout/1
 
2699
%% @see receive_action/1
 
2700
 
 
2701
-record('receive', {ann = [], clauses, timeout, action}).
 
2702
 
 
2703
c_receive(Clauses, Timeout, Action) ->
 
2704
    #'receive'{clauses = Clauses, timeout = Timeout, action = Action}.
 
2705
 
 
2706
 
 
2707
%% @spec ann_c_receive(As::[term()], Clauses::[cerl()]) -> cerl()
 
2708
%% @equiv ann_c_receive(As, Clauses, c_atom(infinity), c_atom(true))
 
2709
%% @see c_receive/3
 
2710
%% @see c_atom/1
 
2711
 
 
2712
ann_c_receive(As, Clauses) ->
 
2713
    ann_c_receive(As, Clauses, c_atom(infinity), c_atom(true)).
 
2714
 
 
2715
 
 
2716
%% @spec ann_c_receive(As::[term()], Clauses::[cerl()],
 
2717
%%                     Timeout::cerl(), Action::cerl()) -> cerl()
 
2718
%% @see ann_c_receive/2
 
2719
%% @see c_receive/3
 
2720
 
 
2721
ann_c_receive(As, Clauses, Timeout, Action) ->
 
2722
    #'receive'{clauses = Clauses, timeout = Timeout, action = Action,
 
2723
               ann = As}.
 
2724
 
 
2725
 
 
2726
%% @spec update_c_receive(Old::cerl(), Clauses::[cerl()],
 
2727
%%                        Timeout::cerl(), Action::cerl()) -> cerl()
 
2728
%% @see c_receive/3
 
2729
 
 
2730
update_c_receive(Node, Clauses, Timeout, Action) ->
 
2731
    #'receive'{clauses = Clauses, timeout = Timeout, action = Action,
 
2732
               ann = get_ann(Node)}.
 
2733
 
 
2734
 
 
2735
%% @spec is_c_receive(Node::cerl()) -> boolean()
 
2736
%%
 
2737
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2738
%% receive-expression, otherwise <code>false</code>.
 
2739
%%
 
2740
%% @see c_receive/3
 
2741
 
 
2742
is_c_receive(#'receive'{}) ->
 
2743
    true;
 
2744
is_c_receive(_) ->
 
2745
    false.
 
2746
 
 
2747
 
 
2748
%% @spec receive_clauses(cerl()) -> [cerl()]
 
2749
%%
 
2750
%% @doc Returns the list of clause subtrees of an abstract
 
2751
%% receive-expression.
 
2752
%%
 
2753
%% @see c_receive/3
 
2754
 
 
2755
receive_clauses(Node) ->
 
2756
    Node#'receive'.clauses.
 
2757
 
 
2758
 
 
2759
%% @spec receive_timeout(cerl()) -> cerl()
 
2760
%%
 
2761
%% @doc Returns the timeout subtree of an abstract receive-expression.
 
2762
%%
 
2763
%% @see c_receive/3
 
2764
 
 
2765
receive_timeout(Node) ->
 
2766
    Node#'receive'.timeout.
 
2767
 
 
2768
 
 
2769
%% @spec receive_action(cerl()) -> cerl()
 
2770
%%
 
2771
%% @doc Returns the action subtree of an abstract receive-expression.
 
2772
%%
 
2773
%% @see c_receive/3
 
2774
 
 
2775
receive_action(Node) ->
 
2776
    Node#'receive'.action.
 
2777
 
 
2778
 
 
2779
%% ---------------------------------------------------------------------
 
2780
 
 
2781
%% @spec c_apply(Operator::cerl(), Arguments::[cerl()]) -> cerl()
 
2782
%%
 
2783
%% @doc Creates an abstract function application. If
 
2784
%% <code>Arguments</code> is <code>[A1, ..., An]</code>, the result
 
2785
%% represents "<code>apply <em>Operator</em>(<em>A1</em>, ...,
 
2786
%% <em>An</em>)</code>".
 
2787
%%
 
2788
%% @see ann_c_apply/3
 
2789
%% @see update_c_apply/3
 
2790
%% @see is_c_apply/1
 
2791
%% @see apply_op/1
 
2792
%% @see apply_args/1
 
2793
%% @see apply_arity/1
 
2794
%% @see c_call/3
 
2795
%% @see c_primop/2
 
2796
 
 
2797
-record(apply, {ann = [], op, args}).
 
2798
 
 
2799
c_apply(Operator, Arguments) ->
 
2800
    #apply{op = Operator, args = Arguments}.
 
2801
 
 
2802
 
 
2803
%% @spec ann_c_apply(As::[term()], Operator::cerl(),
 
2804
%%                   Arguments::[cerl()]) -> cerl()
 
2805
%% @see c_apply/2
 
2806
 
 
2807
ann_c_apply(As, Operator, Arguments) ->
 
2808
    #apply{op = Operator, args = Arguments, ann = As}.
 
2809
 
 
2810
 
 
2811
%% @spec update_c_apply(Old::cerl(), Operator::cerl(),
 
2812
%%                      Arguments::[cerl()]) -> cerl()
 
2813
%% @see c_apply/2
 
2814
 
 
2815
update_c_apply(Node, Operator, Arguments) ->
 
2816
    #apply{op = Operator, args = Arguments, ann = get_ann(Node)}.
 
2817
 
 
2818
 
 
2819
%% @spec is_c_apply(Node::cerl()) -> boolean()
 
2820
%%
 
2821
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2822
%% function application, otherwise <code>false</code>.
 
2823
%%
 
2824
%% @see c_apply/2
 
2825
 
 
2826
is_c_apply(#apply{}) ->
 
2827
    true;
 
2828
is_c_apply(_) ->
 
2829
    false.
 
2830
 
 
2831
 
 
2832
%% @spec apply_op(cerl()) -> cerl()
 
2833
%%
 
2834
%% @doc Returns the operator subtree of an abstract function
 
2835
%% application.
 
2836
%%
 
2837
%% @see c_apply/2
 
2838
 
 
2839
apply_op(Node) ->
 
2840
    Node#apply.op.
 
2841
 
 
2842
 
 
2843
%% @spec apply_args(cerl()) -> [cerl()]
 
2844
%%
 
2845
%% @doc Returns the list of argument subtrees of an abstract function
 
2846
%% application.
 
2847
%%
 
2848
%% @see c_apply/2
 
2849
%% @see apply_arity/1
 
2850
 
 
2851
apply_args(Node) ->
 
2852
    Node#apply.args.
 
2853
 
 
2854
 
 
2855
%% @spec apply_arity(Node::cerl()) -> integer()
 
2856
%%
 
2857
%% @doc Returns the number of argument subtrees of an abstract
 
2858
%% function application.
 
2859
%%
 
2860
%% <p>Note: this is equivalent to
 
2861
%% <code>length(apply_args(Node))</code>, but potentially more
 
2862
%% efficient.</p>
 
2863
%%
 
2864
%% @see c_apply/2
 
2865
%% @see apply_args/1
 
2866
 
 
2867
apply_arity(Node) ->
 
2868
    length(apply_args(Node)).
 
2869
 
 
2870
 
 
2871
%% ---------------------------------------------------------------------
 
2872
 
 
2873
%% @spec c_call(Module::cerl(), Name::cerl(), Arguments::[cerl()]) ->
 
2874
%%           cerl()
 
2875
%%
 
2876
%% @doc Creates an abstract inter-module call. If
 
2877
%% <code>Arguments</code> is <code>[A1, ..., An]</code>, the result
 
2878
%% represents "<code>call <em>Module</em>:<em>Name</em>(<em>A1</em>,
 
2879
%% ..., <em>An</em>)</code>".
 
2880
%%
 
2881
%% @see ann_c_call/4
 
2882
%% @see update_c_call/4
 
2883
%% @see is_c_call/1
 
2884
%% @see call_module/1
 
2885
%% @see call_name/1
 
2886
%% @see call_args/1
 
2887
%% @see call_arity/1
 
2888
%% @see c_apply/2
 
2889
%% @see c_primop/2
 
2890
 
 
2891
-record(call, {ann = [], module, name, args}).
 
2892
 
 
2893
c_call(Module, Name, Arguments) ->
 
2894
    #call{module = Module, name = Name, args = Arguments}.
 
2895
 
 
2896
 
 
2897
%% @spec ann_c_call(As::[term()], Module::cerl(), Name::cerl(),
 
2898
%%                  Arguments::[cerl()]) -> cerl()
 
2899
%% @see c_call/3
 
2900
 
 
2901
ann_c_call(As, Module, Name, Arguments) ->
 
2902
    #call{module = Module, name = Name, args = Arguments, ann = As}.
 
2903
 
 
2904
 
 
2905
%% @spec update_c_call(Old::cerl(), Module::cerl(), Name::cerl(),
 
2906
%%                  Arguments::[cerl()]) -> cerl()
 
2907
%% @see c_call/3
 
2908
 
 
2909
update_c_call(Node, Module, Name, Arguments) ->
 
2910
    #call{module = Module, name = Name, args = Arguments,
 
2911
          ann = get_ann(Node)}.
 
2912
 
 
2913
 
 
2914
%% @spec is_c_call(Node::cerl()) -> boolean()
 
2915
%%
 
2916
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
2917
%% inter-module call expression; otherwise <code>false</code>.
 
2918
%%
 
2919
%% @see c_call/3
 
2920
 
 
2921
is_c_call(#call{}) ->
 
2922
    true;
 
2923
is_c_call(_) ->
 
2924
    false.
 
2925
 
 
2926
 
 
2927
%% @spec call_module(cerl()) -> cerl()
 
2928
%%
 
2929
%% @doc Returns the module subtree of an abstract inter-module call.
 
2930
%%
 
2931
%% @see c_call/3
 
2932
 
 
2933
call_module(Node) ->
 
2934
    Node#call.module.
 
2935
 
 
2936
 
 
2937
%% @spec call_name(cerl()) -> cerl()
 
2938
%%
 
2939
%% @doc Returns the name subtree of an abstract inter-module call.
 
2940
%%
 
2941
%% @see c_call/3
 
2942
 
 
2943
call_name(Node) ->
 
2944
    Node#call.name.
 
2945
 
 
2946
 
 
2947
%% @spec call_args(cerl()) -> [cerl()]
 
2948
%%
 
2949
%% @doc Returns the list of argument subtrees of an abstract
 
2950
%% inter-module call.
 
2951
%%
 
2952
%% @see c_call/3
 
2953
%% @see call_arity/1
 
2954
 
 
2955
call_args(Node) ->
 
2956
    Node#call.args.
 
2957
 
 
2958
 
 
2959
%% @spec call_arity(Node::cerl()) -> integer()
 
2960
%%
 
2961
%% @doc Returns the number of argument subtrees of an abstract
 
2962
%% inter-module call.
 
2963
%%
 
2964
%% <p>Note: this is equivalent to
 
2965
%% <code>length(call_args(Node))</code>, but potentially more
 
2966
%% efficient.</p>
 
2967
%%
 
2968
%% @see c_call/3
 
2969
%% @see call_args/1
 
2970
 
 
2971
call_arity(Node) ->
 
2972
    length(call_args(Node)).
 
2973
 
 
2974
 
 
2975
%% ---------------------------------------------------------------------
 
2976
 
 
2977
%% @spec c_primop(Name::cerl(), Arguments::[cerl()]) -> cerl()
 
2978
%%
 
2979
%% @doc Creates an abstract primitive operation call. If
 
2980
%% <code>Arguments</code> is <code>[A1, ..., An]</code>, the result
 
2981
%% represents "<code>primop <em>Name</em>(<em>A1</em>, ...,
 
2982
%% <em>An</em>)</code>". <code>Name</code> must be an atom literal.
 
2983
%%
 
2984
%% @see ann_c_primop/3
 
2985
%% @see update_c_primop/3
 
2986
%% @see is_c_primop/1
 
2987
%% @see primop_name/1
 
2988
%% @see primop_args/1
 
2989
%% @see primop_arity/1
 
2990
%% @see c_apply/2
 
2991
%% @see c_call/3
 
2992
 
 
2993
-record(primop, {ann = [], name, args}).
 
2994
 
 
2995
c_primop(Name, Arguments) ->
 
2996
    #primop{name = Name, args = Arguments}.
 
2997
 
 
2998
 
 
2999
%% @spec ann_c_primop(As::[term()], Name::cerl(),
 
3000
%%                    Arguments::[cerl()]) -> cerl()
 
3001
%% @see c_primop/2
 
3002
 
 
3003
ann_c_primop(As, Name, Arguments) ->
 
3004
    #primop{name = Name, args = Arguments, ann = As}.
 
3005
 
 
3006
 
 
3007
%% @spec update_c_primop(Old::cerl(), Name::cerl(),
 
3008
%%                       Arguments::[cerl()]) -> cerl()
 
3009
%% @see c_primop/2
 
3010
 
 
3011
update_c_primop(Node, Name, Arguments) ->
 
3012
    #primop{name = Name, args = Arguments, ann = get_ann(Node)}.
 
3013
 
 
3014
 
 
3015
%% @spec is_c_primop(Node::cerl()) -> boolean()
 
3016
%%
 
3017
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
3018
%% primitive operation call, otherwise <code>false</code>.
 
3019
%%
 
3020
%% @see c_primop/2
 
3021
 
 
3022
is_c_primop(#primop{}) ->
 
3023
    true;
 
3024
is_c_primop(_) ->
 
3025
    false.
 
3026
 
 
3027
 
 
3028
%% @spec primop_name(cerl()) -> cerl()
 
3029
%%
 
3030
%% @doc Returns the name subtree of an abstract primitive operation
 
3031
%% call.
 
3032
%%
 
3033
%% @see c_primop/2
 
3034
 
 
3035
primop_name(Node) ->
 
3036
    Node#primop.name.
 
3037
 
 
3038
 
 
3039
%% @spec primop_args(cerl()) -> [cerl()]
 
3040
%%
 
3041
%% @doc Returns the list of argument subtrees of an abstract primitive
 
3042
%% operation call.
 
3043
%%
 
3044
%% @see c_primop/2
 
3045
%% @see primop_arity/1
 
3046
 
 
3047
primop_args(Node) ->
 
3048
    Node#primop.args.
 
3049
 
 
3050
 
 
3051
%% @spec primop_arity(Node::cerl()) -> integer()
 
3052
%%
 
3053
%% @doc Returns the number of argument subtrees of an abstract
 
3054
%% primitive operation call.
 
3055
%%
 
3056
%% <p>Note: this is equivalent to
 
3057
%% <code>length(primop_args(Node))</code>, but potentially more
 
3058
%% efficient.</p>
 
3059
%%
 
3060
%% @see c_primop/2
 
3061
%% @see primop_args/1
 
3062
 
 
3063
primop_arity(Node) ->
 
3064
    length(primop_args(Node)).
 
3065
 
 
3066
 
 
3067
%% ---------------------------------------------------------------------
 
3068
 
 
3069
%% @spec c_try(Argument::cerl(), Variables::[cerl()], Body::cerl(),
 
3070
%%             ExceptionVars::[cerl()], Handler::cerl()) -> cerl()
 
3071
%%
 
3072
%% @doc Creates an abstract try-expression. If <code>Variables</code> is
 
3073
%% <code>[V1, ..., Vn]</code> and <code>ExceptionVars</code> is
 
3074
%% <code>[X1, ..., Xm]</code>, the result represents "<code>try
 
3075
%% <em>Argument</em> of &lt;<em>V1</em>, ..., <em>Vn</em>&gt; ->
 
3076
%% <em>Body</em> catch &lt;<em>X1</em>, ..., <em>Xm</em>&gt; ->
 
3077
%% <em>Handler</em></code>". All the <code>Vi</code> and <code>Xi</code>
 
3078
%% must have type <code>var</code>.
 
3079
%%
 
3080
%% @see ann_c_try/6
 
3081
%% @see update_c_try/6
 
3082
%% @see is_c_try/1
 
3083
%% @see try_arg/1
 
3084
%% @see try_vars/1
 
3085
%% @see try_body/1
 
3086
%% @see c_catch/1
 
3087
 
 
3088
-record('try', {ann = [], arg, vars, body, evars, handler}).
 
3089
 
 
3090
c_try(Expr, Vs, Body, Evs, Handler) ->
 
3091
    #'try'{arg = Expr, vars = Vs, body = Body,
 
3092
           evars = Evs, handler = Handler}.
 
3093
 
 
3094
 
 
3095
%% @spec ann_c_try(As::[term()], Expression::cerl(),
 
3096
%%                 Variables::[cerl()], Body::cerl(),
 
3097
%%                 EVars::[cerl()], EBody::[cerl()]) -> cerl()
 
3098
%% @see c_try/3
 
3099
 
 
3100
ann_c_try(As, Expr, Vs, Body, Evs, Handler) ->
 
3101
    #'try'{arg = Expr, vars = Vs, body = Body,
 
3102
           evars = Evs, handler = Handler, ann = As}.
 
3103
 
 
3104
 
 
3105
%% @spec update_c_try(Old::cerl(), Expression::cerl(),
 
3106
%%                    Variables::[cerl()], Body::cerl(),
 
3107
%%                    EVars::[cerl()], EBody::[cerl()]) -> cerl()
 
3108
%% @see c_try/3
 
3109
 
 
3110
update_c_try(Node, Expr, Vs, Body, Evs, Handler) ->
 
3111
    #'try'{arg = Expr, vars = Vs, body = Body,
 
3112
           evars = Evs, handler = Handler, ann = get_ann(Node)}.
 
3113
 
 
3114
 
 
3115
%% @spec is_c_try(Node::cerl()) -> boolean()
 
3116
%%
 
3117
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
3118
%% try-expression, otherwise <code>false</code>.
 
3119
%%
 
3120
%% @see c_try/3
 
3121
 
 
3122
is_c_try(#'try'{}) ->
 
3123
    true;
 
3124
is_c_try(_) ->
 
3125
    false.
 
3126
 
 
3127
 
 
3128
%% @spec try_arg(cerl()) -> cerl()
 
3129
%%
 
3130
%% @doc Returns the expression subtree of an abstract try-expression.
 
3131
%%
 
3132
%% @see c_try/3
 
3133
 
 
3134
try_arg(Node) ->
 
3135
    Node#'try'.arg.
 
3136
 
 
3137
 
 
3138
%% @spec try_vars(cerl()) -> [cerl()]
 
3139
%%
 
3140
%% @doc Returns the list of success variable subtrees of an abstract
 
3141
%% try-expression.
 
3142
%%
 
3143
%% @see c_try/3
 
3144
 
 
3145
try_vars(Node) ->
 
3146
    Node#'try'.vars.
 
3147
 
 
3148
 
 
3149
%% @spec try_body(cerl()) -> cerl()
 
3150
%%
 
3151
%% @doc Returns the success body subtree of an abstract try-expression.
 
3152
%%
 
3153
%% @see c_try/3
 
3154
 
 
3155
try_body(Node) ->
 
3156
    Node#'try'.body.
 
3157
 
 
3158
 
 
3159
%% @spec try_evars(cerl()) -> [cerl()]
 
3160
%%
 
3161
%% @doc Returns the list of exception variable subtrees of an abstract
 
3162
%% try-expression.
 
3163
%%
 
3164
%% @see c_try/3
 
3165
 
 
3166
try_evars(Node) ->
 
3167
    Node#'try'.evars.
 
3168
 
 
3169
 
 
3170
%% @spec try_handler(cerl()) -> cerl()
 
3171
%%
 
3172
%% @doc Returns the exception body subtree of an abstract
 
3173
%% try-expression.
 
3174
%%
 
3175
%% @see c_try/3
 
3176
 
 
3177
try_handler(Node) ->
 
3178
    Node#'try'.handler.
 
3179
 
 
3180
 
 
3181
%% ---------------------------------------------------------------------
 
3182
 
 
3183
%% @spec c_catch(Body::cerl()) -> cerl()
 
3184
%%
 
3185
%% @doc Creates an abstract catch-expression. The result represents
 
3186
%% "<code>catch <em>Body</em></code>".
 
3187
%%
 
3188
%% <p>Note: catch-expressions can be rewritten as try-expressions, and
 
3189
%% will eventually be removed from Core Erlang.</p>
 
3190
%%
 
3191
%% @see ann_c_catch/2
 
3192
%% @see update_c_catch/2
 
3193
%% @see is_c_catch/1
 
3194
%% @see catch_body/1
 
3195
%% @see c_try/3
 
3196
 
 
3197
-record('catch', {ann = [], body}).
 
3198
 
 
3199
c_catch(Body) ->
 
3200
    #'catch'{body = Body}.
 
3201
 
 
3202
 
 
3203
%% @spec ann_c_catch(As::[term()], Body::cerl()) -> cerl()
 
3204
%% @see c_catch/1
 
3205
 
 
3206
ann_c_catch(As, Body) ->
 
3207
    #'catch'{body = Body, ann = As}.
 
3208
 
 
3209
 
 
3210
%% @spec update_c_catch(Old::cerl(), Body::cerl()) -> cerl()
 
3211
%% @see c_catch/1
 
3212
 
 
3213
update_c_catch(Node, Body) ->
 
3214
    #'catch'{body = Body, ann = get_ann(Node)}.
 
3215
 
 
3216
 
 
3217
%% @spec is_c_catch(Node::cerl()) -> boolean()
 
3218
%%
 
3219
%% @doc Returns <code>true</code> if <code>Node</code> is an abstract
 
3220
%% catch-expression, otherwise <code>false</code>.
 
3221
%%
 
3222
%% @see c_catch/1
 
3223
 
 
3224
is_c_catch(#'catch'{}) ->
 
3225
    true;
 
3226
is_c_catch(_) ->
 
3227
    false.
 
3228
 
 
3229
 
 
3230
%% @spec catch_body(Node::cerl()) -> cerl()
 
3231
%%
 
3232
%% @doc Returns the body subtree of an abstract catch-expression.
 
3233
%%
 
3234
%% @see c_catch/1
 
3235
 
 
3236
catch_body(Node) ->
 
3237
    Node#'catch'.body.
 
3238
 
 
3239
 
 
3240
%% ---------------------------------------------------------------------
 
3241
 
 
3242
%% @spec to_records(Tree::cerl()) -> record(record_types())
 
3243
%%
 
3244
%% @doc Translates an abstract syntax tree to a corresponding explicit
 
3245
%% record representation. The records are defined in the file
 
3246
%% "<code>cerl.hrl</code>".
 
3247
%%
 
3248
%% <p>Note: Compound constant literals are always unfolded in the
 
3249
%% record representation.</p>
 
3250
%%
 
3251
%% @see type/1
 
3252
%% @see from_records/1
 
3253
 
 
3254
to_records(Node) ->
 
3255
    A = get_ann(Node),
 
3256
    case type(Node) of
 
3257
        literal ->
 
3258
            lit_to_records(concrete(Node), A);
 
3259
        binary ->
 
3260
            #c_binary{anno = A,
 
3261
                      segments =
 
3262
                      list_to_records(binary_segments(Node))};
 
3263
        bitstr ->
 
3264
            #c_bitstr{anno = A,
 
3265
                      val = to_records(bitstr_val(Node)),
 
3266
                      size = to_records(bitstr_size(Node)),
 
3267
                      unit = to_records(bitstr_unit(Node)),
 
3268
                      type = to_records(bitstr_type(Node)),
 
3269
                      flags = to_records(bitstr_flags(Node))};
 
3270
        cons ->
 
3271
            #c_cons{anno = A,
 
3272
                    hd = to_records(cons_hd(Node)),
 
3273
                    tl = to_records(cons_tl(Node))};
 
3274
        tuple ->
 
3275
            #c_tuple{anno = A,
 
3276
                     es = list_to_records(tuple_es(Node))};
 
3277
        var ->
 
3278
            case is_c_fname(Node) of
 
3279
                true ->
 
3280
                    #c_fname{anno = A,
 
3281
                             id = fname_id(Node),
 
3282
                             arity = fname_arity(Node)};
 
3283
                false ->
 
3284
                    #c_var{anno = A, name = var_name(Node)}
 
3285
            end;
 
3286
        values ->
 
3287
            #c_values{anno = A,
 
3288
                      es = list_to_records(values_es(Node))};
 
3289
        'fun' ->
 
3290
            #c_fun{anno = A,
 
3291
                   vars = list_to_records(fun_vars(Node)),
 
3292
                   body = to_records(fun_body(Node))};
 
3293
        seq ->
 
3294
            #c_seq{anno = A,
 
3295
                   arg = to_records(seq_arg(Node)),
 
3296
                   body = to_records(seq_body(Node))};
 
3297
        'let' ->
 
3298
            #c_let{anno = A,
 
3299
                   vars = list_to_records(let_vars(Node)),
 
3300
                   arg = to_records(let_arg(Node)),
 
3301
                   body = to_records(let_body(Node))};
 
3302
        letrec ->
 
3303
            #c_letrec{anno = A,
 
3304
                      defs = [#c_def{name = to_records(N),
 
3305
                                     val = to_records(F)}
 
3306
                              || {N, F} <- letrec_defs(Node)],
 
3307
                      body = to_records(letrec_body(Node))};
 
3308
        'case' ->
 
3309
            #c_case{anno = A,
 
3310
                    arg = to_records(case_arg(Node)),
 
3311
                    clauses =
 
3312
                    list_to_records(case_clauses(Node))};
 
3313
        clause ->
 
3314
            #c_clause{anno = A,
 
3315
                      pats = list_to_records(clause_pats(Node)),
 
3316
                      guard = to_records(clause_guard(Node)),
 
3317
                      body = to_records(clause_body(Node))};
 
3318
        alias ->
 
3319
            #c_alias{anno = A,
 
3320
                     var = to_records(alias_var(Node)),
 
3321
                     pat = to_records(alias_pat(Node))};
 
3322
        'receive' ->
 
3323
            #c_receive{anno = A,
 
3324
                       clauses = 
 
3325
                       list_to_records(receive_clauses(Node)),
 
3326
                       timeout =
 
3327
                       to_records(receive_timeout(Node)),
 
3328
                       action = 
 
3329
                       to_records(receive_action(Node))};
 
3330
        apply ->
 
3331
            #c_apply{anno = A,
 
3332
                     op = to_records(apply_op(Node)),
 
3333
                     args = list_to_records(apply_args(Node))};
 
3334
        call ->
 
3335
            #c_call{anno = A,
 
3336
                    module = to_records(call_module(Node)),
 
3337
                    name = to_records(call_name(Node)),
 
3338
                    args = list_to_records(call_args(Node))};
 
3339
        primop ->
 
3340
            #c_primop{anno = A,
 
3341
                      name = to_records(primop_name(Node)),
 
3342
                      args = list_to_records(primop_args(Node))};
 
3343
        'try' ->
 
3344
            #c_try{anno = A,
 
3345
                   arg = to_records(try_arg(Node)),
 
3346
                   vars = list_to_records(try_vars(Node)),
 
3347
                   body = to_records(try_body(Node)),
 
3348
                   evars = list_to_records(try_evars(Node)),
 
3349
                   handler = to_records(try_handler(Node))};
 
3350
        'catch' ->
 
3351
            #c_catch{anno = A,
 
3352
                     body = to_records(catch_body(Node))};
 
3353
        module ->
 
3354
            #c_module{anno = A,
 
3355
                      name = to_records(module_name(Node)),
 
3356
                      exports = list_to_records(
 
3357
                                  module_exports(Node)),
 
3358
                      attrs = [#c_def{name = to_records(K),
 
3359
                                      val = to_records(V)}
 
3360
                               || {K, V} <- module_attrs(Node)],
 
3361
                      defs = [#c_def{name = to_records(N),
 
3362
                                     val = to_records(F)}
 
3363
                              || {N, F} <- module_defs(Node)]}
 
3364
    end.
 
3365
 
 
3366
list_to_records([T | Ts]) ->
 
3367
    [to_records(T) | list_to_records(Ts)];
 
3368
list_to_records([]) ->
 
3369
    [].
 
3370
 
 
3371
lit_to_records(V, A) when integer(V) ->
 
3372
    #c_int{anno = A, val = V};
 
3373
lit_to_records(V, A) when float(V) ->
 
3374
    #c_float{anno = A, val = V};
 
3375
lit_to_records(V, A) when atom(V) ->
 
3376
    #c_atom{anno = A, val = V};
 
3377
lit_to_records([H | T] = V, A) ->
 
3378
    case is_print_char_list(V) of
 
3379
        true ->
 
3380
            #c_string{anno = A, val = V};
 
3381
        false ->
 
3382
            #c_cons{anno = A,
 
3383
                    hd = lit_to_records(H, []),
 
3384
                    tl = lit_to_records(T, [])}
 
3385
    end;
 
3386
lit_to_records([], A) ->
 
3387
    #c_nil{anno = A};
 
3388
lit_to_records(V, A) when tuple(V) ->
 
3389
    #c_tuple{anno = A, es = lit_list_to_records(tuple_to_list(V))}.
 
3390
 
 
3391
lit_list_to_records([T | Ts]) ->
 
3392
    [lit_to_records(T, []) | lit_list_to_records(Ts)];
 
3393
lit_list_to_records([]) ->
 
3394
    [].
 
3395
 
 
3396
 
 
3397
%% @spec from_records(Tree::record(record_types())) -> cerl()
 
3398
%%
 
3399
%%     record_types() = c_alias | c_apply | c_call | c_case | c_catch |
 
3400
%%                      c_clause | c_cons | c_def| c_fun | c_let |
 
3401
%%                      c_letrec |c_lit | c_module | c_primop |
 
3402
%%                      c_receive | c_seq | c_try | c_tuple |
 
3403
%%                      c_values | c_var
 
3404
%%
 
3405
%% @doc Translates an explicit record representation to a
 
3406
%% corresponding abstract syntax tree.  The records are defined in the
 
3407
%% file "<code>cerl.hrl</code>".
 
3408
%%
 
3409
%% <p>Note: Compound constant literals are folded, discarding
 
3410
%% annotations on subtrees. There are no <code>c_def</code> nodes in
 
3411
%% the abstract representation; annotations on <code>c_def</code>
 
3412
%% records are discarded.</p>
 
3413
%%
 
3414
%% @see type/1
 
3415
%% @see to_records/1
 
3416
 
 
3417
from_records(#c_int{val = V, anno = As}) ->
 
3418
    ann_c_int(As, V);
 
3419
from_records(#c_float{val = V, anno = As}) ->
 
3420
    ann_c_float(As, V);
 
3421
from_records(#c_atom{val = V, anno = As}) ->
 
3422
    ann_c_atom(As, V);
 
3423
from_records(#c_char{val = V, anno = As}) ->
 
3424
    ann_c_char(As, V);
 
3425
from_records(#c_string{val = V, anno = As}) ->
 
3426
    ann_c_string(As, V);
 
3427
from_records(#c_nil{anno = As}) ->
 
3428
    ann_c_nil(As);
 
3429
from_records(#c_binary{segments = Ss, anno = As}) ->
 
3430
    ann_c_binary(As, from_records_list(Ss));
 
3431
from_records(#c_bitstr{val = V, size = S, unit = U, type = T,
 
3432
                       flags = Fs, anno = As}) ->
 
3433
    ann_c_bitstr(As, from_records(V), from_records(S), from_records(U),
 
3434
                 from_records(T), from_records(Fs));
 
3435
from_records(#c_cons{hd = H, tl = T, anno = As}) ->
 
3436
    ann_c_cons(As, from_records(H), from_records(T));
 
3437
from_records(#c_tuple{es = Es, anno = As}) ->
 
3438
    ann_c_tuple(As, from_records_list(Es));
 
3439
from_records(#c_var{name = Name, anno = As}) ->
 
3440
    ann_c_var(As, Name);
 
3441
from_records(#c_fname{id = Id, arity = Arity, anno = As}) ->
 
3442
    ann_c_fname(As, Id, Arity);
 
3443
from_records(#c_values{es = Es, anno = As}) ->
 
3444
    ann_c_values(As, from_records_list(Es));
 
3445
from_records(#c_fun{vars = Vs, body = B, anno = As}) ->
 
3446
    ann_c_fun(As, from_records_list(Vs), from_records(B));
 
3447
from_records(#c_seq{arg = A, body = B, anno = As}) ->
 
3448
    ann_c_seq(As, from_records(A), from_records(B));
 
3449
from_records(#c_let{vars = Vs, arg = A, body = B, anno = As}) ->
 
3450
    ann_c_let(As, from_records_list(Vs), from_records(A),
 
3451
              from_records(B));
 
3452
from_records(#c_letrec{defs = Fs, body = B, anno = As}) ->
 
3453
    ann_c_letrec(As, [{from_records(N), from_records(F)}
 
3454
                      || #c_def{name = N, val = F} <- Fs],
 
3455
                 from_records(B));
 
3456
from_records(#c_case{arg = A, clauses = Cs, anno = As}) ->
 
3457
    ann_c_case(As, from_records(A), from_records_list(Cs));
 
3458
from_records(#c_clause{pats = Ps, guard = G, body = B, anno = As}) ->
 
3459
    ann_c_clause(As, from_records_list(Ps), from_records(G),
 
3460
                 from_records(B));
 
3461
from_records(#c_alias{var = V, pat = P, anno = As}) ->
 
3462
    ann_c_alias(As, from_records(V), from_records(P));
 
3463
from_records(#c_receive{clauses = Cs, timeout = T, action = A,
 
3464
                        anno = As}) ->
 
3465
    ann_c_receive(As, from_records_list(Cs), from_records(T),
 
3466
                  from_records(A));
 
3467
from_records(#c_apply{op = Op, args = Es, anno = As}) ->
 
3468
    ann_c_apply(As, from_records(Op), from_records_list(Es));
 
3469
from_records(#c_call{module = M, name = N, args = Es, anno = As}) ->
 
3470
    ann_c_call(As, from_records(M), from_records(N),
 
3471
               from_records_list(Es));
 
3472
from_records(#c_primop{name = N, args = Es, anno = As}) ->
 
3473
    ann_c_primop(As, from_records(N), from_records_list(Es));
 
3474
from_records(#c_try{arg = E, vars = Vs, body = B,
 
3475
                    evars = Evs, handler = H, anno = As}) ->
 
3476
    ann_c_try(As, from_records(E), from_records_list(Vs),
 
3477
              from_records(B), from_records_list(Evs), from_records(H));
 
3478
from_records(#c_catch{body = B, anno = As}) ->
 
3479
    ann_c_catch(As, from_records(B));
 
3480
from_records(#c_module{name = N, exports = Es, attrs = Ds, defs = Fs,
 
3481
                       anno = As}) ->
 
3482
    ann_c_module(As, from_records(N),
 
3483
                 from_records_list(Es),
 
3484
                 [{from_records(K), from_records(V)}
 
3485
                  || #c_def{name = K, val = V} <- Ds],
 
3486
                 [{from_records(V), from_records(F)}
 
3487
                  || #c_def{name = V, val = F} <- Fs]).
 
3488
 
 
3489
from_records_list([T | Ts]) ->
 
3490
    [from_records(T) | from_records_list(Ts)];
 
3491
from_records_list([]) ->
 
3492
    [].
 
3493
 
 
3494
 
 
3495
%% ---------------------------------------------------------------------
 
3496
 
 
3497
%% @spec is_data(Node::cerl()) -> boolean()
 
3498
%%
 
3499
%% @doc Returns <code>true</code> if <code>Node</code> represents a
 
3500
%% data constructor, otherwise <code>false</code>. Data constructors
 
3501
%% are cons cells, tuples, and atomic literals.
 
3502
%%
 
3503
%% @see data_type/1
 
3504
%% @see data_es/1
 
3505
%% @see data_arity/1
 
3506
 
 
3507
is_data(#literal{}) ->
 
3508
    true;
 
3509
is_data(#cons{}) ->
 
3510
    true;
 
3511
is_data(#tuple{}) ->
 
3512
    true;
 
3513
is_data(_) ->
 
3514
    false.
 
3515
 
 
3516
 
 
3517
%% @spec data_type(Node::cerl()) -> dtype()
 
3518
%%
 
3519
%%     dtype() = cons | tuple | {'atomic', Value}
 
3520
%%     Value = integer() | float() | atom() | []
 
3521
%%
 
3522
%% @doc Returns a type descriptor for a data constructor
 
3523
%% node. (Cf. <code>is_data/1</code>.) This is mainly useful for
 
3524
%% comparing types and for constructing new nodes of the same type
 
3525
%% (cf. <code>make_data/2</code>). If <code>Node</code> represents an
 
3526
%% integer, floating-point number, atom or empty list, the result is
 
3527
%% <code>{'atomic', Value}</code>, where <code>Value</code> is the value
 
3528
%% of <code>concrete(Node)</code>, otherwise the result is either
 
3529
%% <code>cons</code> or <code>tuple</code>.
 
3530
%%
 
3531
%% <p>Type descriptors can be compared for equality or order (in the
 
3532
%% Erlang term order), but remember that floating-point values should
 
3533
%% in general never be tested for equality.</p>
 
3534
%%
 
3535
%% @see is_data/1
 
3536
%% @see make_data/2
 
3537
%% @see type/1
 
3538
%% @see concrete/1
 
3539
 
 
3540
data_type(#literal{val = V}) ->
 
3541
    case V of
 
3542
        [_ | _] ->
 
3543
            cons;
 
3544
        _ when tuple(V) ->
 
3545
            tuple;
 
3546
        _ ->
 
3547
            {'atomic', V}
 
3548
    end;
 
3549
data_type(#cons{}) ->
 
3550
    cons;
 
3551
data_type(#tuple{}) ->
 
3552
    tuple.
 
3553
 
 
3554
 
 
3555
%% @spec data_es(Node::cerl()) -> [cerl()]
 
3556
%%
 
3557
%% @doc Returns the list of subtrees of a data constructor node. If
 
3558
%% the arity of the constructor is zero, the result is the empty list.
 
3559
%%
 
3560
%% <p>Note: if <code>data_type(Node)</code> is <code>cons</code>, the
 
3561
%% number of subtrees is exactly two. If <code>data_type(Node)</code>
 
3562
%% is <code>{'atomic', Value}</code>, the number of subtrees is
 
3563
%% zero.</p>
 
3564
%%
 
3565
%% @see is_data/1
 
3566
%% @see data_type/1
 
3567
%% @see data_arity/1
 
3568
%% @see make_data/2
 
3569
 
 
3570
data_es(#literal{val = V}) ->
 
3571
    case V of
 
3572
        [Head | Tail] ->
 
3573
            [#literal{val = Head}, #literal{val = Tail}];
 
3574
        _ when tuple(V) ->
 
3575
            make_lit_list(tuple_to_list(V));
 
3576
        _ ->
 
3577
            []
 
3578
    end;
 
3579
data_es(#cons{hd = H, tl = T}) ->
 
3580
    [H, T];
 
3581
data_es(#tuple{es = Es}) ->
 
3582
    Es.
 
3583
 
 
3584
 
 
3585
%% @spec data_arity(Node::cerl()) -> integer()
 
3586
%%
 
3587
%% @doc Returns the number of subtrees of a data constructor
 
3588
%% node. This is equivalent to <code>length(data_es(Node))</code>, but
 
3589
%% potentially more efficient.
 
3590
%%
 
3591
%% @see is_data/1
 
3592
%% @see data_es/1
 
3593
 
 
3594
data_arity(#literal{val = V}) ->
 
3595
    case V of
 
3596
        [_ | _] ->
 
3597
            2;
 
3598
        _ when tuple(V) ->
 
3599
            size(V);
 
3600
        _ ->
 
3601
            0
 
3602
    end;
 
3603
data_arity(#cons{}) ->
 
3604
    2;
 
3605
data_arity(#tuple{es = Es}) ->
 
3606
    length(Es).
 
3607
 
 
3608
 
 
3609
%% @spec make_data(Type::dtype(), Elements::[cerl()]) -> cerl()
 
3610
%%
 
3611
%% @doc Creates a data constructor node with the specified type and
 
3612
%% subtrees. (Cf. <code>data_type/1</code>.)  An exception is thrown
 
3613
%% if the length of <code>Elements</code> is invalid for the given
 
3614
%% <code>Type</code>; see <code>data_es/1</code> for arity constraints
 
3615
%% on constructor types.
 
3616
%%
 
3617
%% @see data_type/1
 
3618
%% @see data_es/1
 
3619
%% @see ann_make_data/3
 
3620
%% @see update_data/3
 
3621
%% @see make_data_skel/2
 
3622
 
 
3623
make_data(CType, Es) ->
 
3624
    ann_make_data([], CType, Es).
 
3625
 
 
3626
 
 
3627
%% @spec ann_make_data(As::[term()], Type::dtype(),
 
3628
%%                     Elements::[cerl()]) -> cerl()
 
3629
%% @see make_data/2
 
3630
 
 
3631
ann_make_data(As, {'atomic', V}, []) -> #literal{val = V, ann = As};
 
3632
ann_make_data(As, cons, [H, T]) -> ann_c_cons(As, H, T);
 
3633
ann_make_data(As, tuple, Es) -> ann_c_tuple(As, Es).
 
3634
 
 
3635
 
 
3636
%% @spec update_data(Old::cerl(), Type::dtype(),
 
3637
%%                   Elements::[cerl()]) -> cerl()
 
3638
%% @see make_data/2
 
3639
 
 
3640
update_data(Node, CType, Es) ->
 
3641
    ann_make_data(get_ann(Node), CType, Es).
 
3642
 
 
3643
 
 
3644
%% @spec make_data_skel(Type::dtype(), Elements::[cerl()]) -> cerl()
 
3645
%%
 
3646
%% @doc Like <code>make_data/2</code>, but analogous to
 
3647
%% <code>c_tuple_skel/1</code> and <code>c_cons_skel/2</code>.
 
3648
%%
 
3649
%% @see ann_make_data_skel/3
 
3650
%% @see update_data_skel/3
 
3651
%% @see make_data/2
 
3652
%% @see c_tuple_skel/1
 
3653
%% @see c_cons_skel/2
 
3654
 
 
3655
make_data_skel(CType, Es) ->
 
3656
    ann_make_data_skel([], CType, Es).
 
3657
 
 
3658
 
 
3659
%% @spec ann_make_data_skel(As::[term()], Type::dtype(),
 
3660
%%                          Elements::[cerl()]) -> cerl()
 
3661
%% @see make_data_skel/2
 
3662
 
 
3663
ann_make_data_skel(As, {'atomic', V}, []) -> #literal{val = V, ann = As};
 
3664
ann_make_data_skel(As, cons, [H, T]) -> ann_c_cons_skel(As, H, T);
 
3665
ann_make_data_skel(As, tuple, Es) -> ann_c_tuple_skel(As, Es).
 
3666
 
 
3667
 
 
3668
%% @spec update_data_skel(Old::cerl(), Type::dtype(),
 
3669
%%                        Elements::[cerl()]) -> cerl()
 
3670
%% @see make_data_skel/2
 
3671
 
 
3672
update_data_skel(Node, CType, Es) ->
 
3673
    ann_make_data_skel(get_ann(Node), CType, Es).
 
3674
 
 
3675
 
 
3676
%% ---------------------------------------------------------------------
 
3677
 
 
3678
%% @spec subtrees(Node::cerl()) -> [[cerl()]]
 
3679
%%
 
3680
%% @doc Returns the grouped list of all subtrees of a node. If
 
3681
%% <code>Node</code> is a leaf node (cf. <code>is_leaf/1</code>), this
 
3682
%% is the empty list, otherwise the result is always a nonempty list,
 
3683
%% containing the lists of subtrees of <code>Node</code>, in
 
3684
%% left-to-right order as they occur in the printed program text, and
 
3685
%% grouped by category. Often, each group contains only a single
 
3686
%% subtree.
 
3687
%%
 
3688
%% <p>Depending on the type of <code>Node</code>, the size of some
 
3689
%% groups may be variable (e.g., the group consisting of all the
 
3690
%% elements of a tuple), while others always contain the same number
 
3691
%% of elements - usually exactly one (e.g., the group containing the
 
3692
%% argument expression of a case-expression). Note, however, that the
 
3693
%% exact structure of the returned list (for a given node type) should
 
3694
%% in general not be depended upon, since it might be subject to
 
3695
%% change without notice.</p>
 
3696
%%
 
3697
%% <p>The function <code>subtrees/1</code> and the constructor functions
 
3698
%% <code>make_tree/2</code> and <code>update_tree/2</code> can be a
 
3699
%% great help if one wants to traverse a syntax tree, visiting all its
 
3700
%% subtrees, but treat nodes of the tree in a uniform way in most or all
 
3701
%% cases. Using these functions makes this simple, and also assures that
 
3702
%% your code is not overly sensitive to extensions of the syntax tree
 
3703
%% data type, because any node types not explicitly handled by your code
 
3704
%% can be left to a default case.</p>
 
3705
%%
 
3706
%% <p>For example:
 
3707
%% <pre>
 
3708
%%   postorder(F, Tree) ->
 
3709
%%       F(case subtrees(Tree) of
 
3710
%%           [] -> Tree;
 
3711
%%           List -> update_tree(Tree,
 
3712
%%                               [[postorder(F, Subtree)
 
3713
%%                                 || Subtree &lt;- Group]
 
3714
%%                                || Group &lt;- List])
 
3715
%%         end).
 
3716
%% </pre>
 
3717
%% maps the function <code>F</code> on <code>Tree</code> and all its
 
3718
%% subtrees, doing a post-order traversal of the syntax tree. (Note
 
3719
%% the use of <code>update_tree/2</code> to preserve annotations.) For
 
3720
%% a simple function like:
 
3721
%% <pre>
 
3722
%%   f(Node) ->
 
3723
%%       case type(Node) of
 
3724
%%           atom -> atom("a_" ++ atom_name(Node));
 
3725
%%           _ -> Node
 
3726
%%       end.
 
3727
%% </pre>
 
3728
%% the call <code>postorder(fun f/1, Tree)</code> will yield a new
 
3729
%% representation of <code>Tree</code> in which all atom names have
 
3730
%% been extended with the prefix "a_", but nothing else (including
 
3731
%% annotations) has been changed.</p>
 
3732
%%
 
3733
%% @see is_leaf/1
 
3734
%% @see make_tree/2
 
3735
%% @see update_tree/2
 
3736
 
 
3737
subtrees(T) ->
 
3738
    case is_leaf(T) of
 
3739
        true ->
 
3740
            [];
 
3741
        false ->
 
3742
            case type(T) of
 
3743
                values ->
 
3744
                    [values_es(T)];
 
3745
                binary ->
 
3746
                    [binary_segments(T)];
 
3747
                bitstr ->
 
3748
                    [[bitstr_val(T)], [bitstr_size(T)],
 
3749
                     [bitstr_unit(T)], [bitstr_type(T)],
 
3750
                     [bitstr_flags(T)]];
 
3751
                cons ->
 
3752
                    [[cons_hd(T)], [cons_tl(T)]];
 
3753
                tuple ->
 
3754
                    [tuple_es(T)];
 
3755
                'let' ->
 
3756
                    [let_vars(T), [let_arg(T)], [let_body(T)]];
 
3757
                seq ->
 
3758
                    [[seq_arg(T)], [seq_body(T)]];
 
3759
                apply ->
 
3760
                    [[apply_op(T)], apply_args(T)];
 
3761
                call ->
 
3762
                    [[call_module(T)], [call_name(T)],
 
3763
                     call_args(T)];
 
3764
                primop ->
 
3765
                    [[primop_name(T)], primop_args(T)];
 
3766
                'case' ->
 
3767
                    [[case_arg(T)], case_clauses(T)];
 
3768
                clause ->
 
3769
                    [clause_pats(T), [clause_guard(T)],
 
3770
                     [clause_body(T)]];
 
3771
                alias ->
 
3772
                    [[alias_var(T)], [alias_pat(T)]];
 
3773
                'fun' ->
 
3774
                    [fun_vars(T), [fun_body(T)]];
 
3775
                'receive' ->
 
3776
                    [receive_clauses(T), [receive_timeout(T)],
 
3777
                     [receive_action(T)]];
 
3778
                'try' ->
 
3779
                    [[try_arg(T)], try_vars(T), [try_body(T)],
 
3780
                     try_evars(T), [try_handler(T)]];
 
3781
                'catch' ->
 
3782
                    [[catch_body(T)]];
 
3783
                letrec ->
 
3784
                    Es = unfold_tuples(letrec_defs(T)),
 
3785
                    [Es, [letrec_body(T)]];
 
3786
                module ->
 
3787
                    As = unfold_tuples(module_attrs(T)),
 
3788
                    Es = unfold_tuples(module_defs(T)),
 
3789
                    [[module_name(T)], module_exports(T), As, Es]
 
3790
            end
 
3791
    end.
 
3792
 
 
3793
 
 
3794
%% @spec update_tree(Old::cerl(), Groups::[[cerl()]]) -> cerl()
 
3795
%%
 
3796
%% @doc Creates a syntax tree with the given subtrees, and the same
 
3797
%% type and annotations as the <code>Old</code> node. This is
 
3798
%% equivalent to <code>ann_make_tree(get_ann(Node), type(Node),
 
3799
%% Groups)</code>, but potentially more efficient.
 
3800
%%
 
3801
%% @see update_tree/3
 
3802
%% @see ann_make_tree/3
 
3803
%% @see get_ann/1
 
3804
%% @see type/1
 
3805
 
 
3806
update_tree(Node, Gs) ->
 
3807
    ann_make_tree(get_ann(Node), type(Node), Gs).
 
3808
 
 
3809
 
 
3810
%% @spec update_tree(Old::cerl(), Type::atom(), Groups::[[cerl()]]) ->
 
3811
%%           cerl()
 
3812
%%
 
3813
%% @doc Creates a syntax tree with the given type and subtrees, and
 
3814
%% the same annotations as the <code>Old</code> node. This is
 
3815
%% equivalent to <code>ann_make_tree(get_ann(Node), Type,
 
3816
%% Groups)</code>, but potentially more efficient.
 
3817
%%
 
3818
%% @see update_tree/2
 
3819
%% @see ann_make_tree/3
 
3820
%% @see get_ann/1
 
3821
 
 
3822
update_tree(Node, Type, Gs) ->
 
3823
    ann_make_tree(get_ann(Node), Type, Gs).
 
3824
 
 
3825
 
 
3826
%% @spec make_tree(Type::atom(), Groups::[[cerl()]]) -> cerl()
 
3827
%%
 
3828
%% @doc Creates a syntax tree with the given type and subtrees.
 
3829
%% <code>Type</code> must be a node type name
 
3830
%% (cf. <code>type/1</code>) that does not denote a leaf node type
 
3831
%% (cf. <code>is_leaf/1</code>).  <code>Groups</code> must be a
 
3832
%% <em>nonempty</em> list of groups of syntax trees, representing the
 
3833
%% subtrees of a node of the given type, in left-to-right order as
 
3834
%% they would occur in the printed program text, grouped by category
 
3835
%% as done by <code>subtrees/1</code>.
 
3836
%%
 
3837
%% <p>The result of <code>ann_make_tree(get_ann(Node), type(Node),
 
3838
%% subtrees(Node))</code> (cf. <code>update_tree/2</code>) represents
 
3839
%% the same source code text as the original <code>Node</code>,
 
3840
%% assuming that <code>subtrees(Node)</code> yields a nonempty
 
3841
%% list. However, it does not necessarily have the exact same data
 
3842
%% representation as <code>Node</code>.</p>
 
3843
%%
 
3844
%% @see ann_make_tree/3
 
3845
%% @see type/1
 
3846
%% @see is_leaf/1
 
3847
%% @see subtrees/1
 
3848
%% @see update_tree/2
 
3849
 
 
3850
make_tree(Type, Gs) ->
 
3851
    ann_make_tree([], Type, Gs).
 
3852
 
 
3853
 
 
3854
%% @spec ann_make_tree(As::[term()], Type::atom(),
 
3855
%%                     Groups::[[cerl()]]) -> cerl()
 
3856
%%
 
3857
%% @doc Creates a syntax tree with the given annotations, type and
 
3858
%% subtrees. See <code>make_tree/2</code> for details.
 
3859
%%
 
3860
%% @see make_tree/2
 
3861
 
 
3862
ann_make_tree(As, values, [Es]) -> ann_c_values(As, Es);
 
3863
ann_make_tree(As, binary, [Ss]) -> ann_c_binary(As, Ss);
 
3864
ann_make_tree(As, bitstr, [[V],[S],[U],[T],[Fs]]) ->
 
3865
    ann_c_bitstr(As, V, S, U, T, Fs);
 
3866
ann_make_tree(As, cons, [[H], [T]]) -> ann_c_cons(As, H, T);
 
3867
ann_make_tree(As, tuple, [Es]) -> ann_c_tuple(As, Es);
 
3868
ann_make_tree(As, 'let', [Vs, [A], [B]]) -> ann_c_let(As, Vs, A, B);
 
3869
ann_make_tree(As, seq, [[A], [B]]) -> ann_c_seq(As, A, B);
 
3870
ann_make_tree(As, apply, [[Op], Es]) -> ann_c_apply(As, Op, Es);
 
3871
ann_make_tree(As, call, [[M], [N], Es]) -> ann_c_call(As, M, N, Es);
 
3872
ann_make_tree(As, primop, [[N], Es]) -> ann_c_primop(As, N, Es);
 
3873
ann_make_tree(As, 'case', [[A], Cs]) -> ann_c_case(As, A, Cs);
 
3874
ann_make_tree(As, clause, [Ps, [G], [B]]) -> ann_c_clause(As, Ps, G, B);
 
3875
ann_make_tree(As, alias, [[V], [P]]) -> ann_c_alias(As, V, P);
 
3876
ann_make_tree(As, 'fun', [Vs, [B]]) -> ann_c_fun(As, Vs, B);
 
3877
ann_make_tree(As, 'receive', [Cs, [T], [A]]) ->
 
3878
    ann_c_receive(As, Cs, T, A);
 
3879
ann_make_tree(As, 'try', [[E], Vs, [B], Evs, [H]]) ->
 
3880
    ann_c_try(As, E, Vs, B, Evs, H);
 
3881
ann_make_tree(As, 'catch', [[B]]) -> ann_c_catch(As, B);
 
3882
ann_make_tree(As, letrec, [Es, [B]]) ->
 
3883
    ann_c_letrec(As, fold_tuples(Es), B);
 
3884
ann_make_tree(As, module, [[N], Xs, Es, Ds]) ->
 
3885
    ann_c_module(As, N, Xs, fold_tuples(Es), fold_tuples(Ds)).
 
3886
 
 
3887
 
 
3888
%% ---------------------------------------------------------------------
 
3889
 
 
3890
%% @spec meta(Tree::cerl()) -> cerl()
 
3891
%%
 
3892
%% @doc Creates a meta-representation of a syntax tree. The result
 
3893
%% represents an Erlang expression "<code><em>MetaTree</em></code>"
 
3894
%% which, if evaluated, will yield a new syntax tree representing the
 
3895
%% same source code text as <code>Tree</code> (although the actual
 
3896
%% data representation may be different). The expression represented
 
3897
%% by <code>MetaTree</code> is <em>implementation independent</em>
 
3898
%% with regard to the data structures used by the abstract syntax tree
 
3899
%% implementation.
 
3900
%%
 
3901
%% <p>Any node in <code>Tree</code> whose node type is
 
3902
%% <code>var</code> (cf. <code>type/1</code>), and whose list of
 
3903
%% annotations (cf. <code>get_ann/1</code>) contains the atom
 
3904
%% <code>meta_var</code>, will remain unchanged in the resulting tree,
 
3905
%% except that exactly one occurrence of <code>meta_var</code> is
 
3906
%% removed from its annotation list.</p>
 
3907
%%
 
3908
%% <p>The main use of the function <code>meta/1</code> is to transform
 
3909
%% a data structure <code>Tree</code>, which represents a piece of
 
3910
%% program code, into a form that is <em>representation independent
 
3911
%% when printed</em>. E.g., suppose <code>Tree</code> represents a
 
3912
%% variable named "V". Then (assuming a function <code>print/1</code>
 
3913
%% for printing syntax trees), evaluating
 
3914
%% <code>print(abstract(Tree))</code> - simply using
 
3915
%% <code>abstract/1</code> to map the actual data structure onto a
 
3916
%% syntax tree representation - would output a string that might look
 
3917
%% something like "<code>{var, ..., 'V'}</code>", which is obviously
 
3918
%% dependent on the implementation of the abstract syntax trees. This
 
3919
%% could e.g. be useful for caching a syntax tree in a file. However,
 
3920
%% in some situations like in a program generator generator (with two
 
3921
%% "generator"), it may be unacceptable.  Using
 
3922
%% <code>print(meta(Tree))</code> instead would output a
 
3923
%% <em>representation independent</em> syntax tree generating
 
3924
%% expression; in the above case, something like
 
3925
%% "<code>cerl:c_var('V')</code>".</p>
 
3926
%%
 
3927
%% <p>The implementation tries to generate compact code with respect
 
3928
%% to literals and lists.</p>
 
3929
%%
 
3930
%% @see abstract/1
 
3931
%% @see type/1
 
3932
%% @see get_ann/1
 
3933
 
 
3934
meta(Node) ->
 
3935
    %% First of all we check for metavariables:
 
3936
    case type(Node) of
 
3937
        var ->
 
3938
            case lists:member(meta_var, get_ann(Node)) of
 
3939
                false ->
 
3940
                    meta_0(var, Node);
 
3941
                true ->
 
3942
                    %% A meta-variable: remove the first found
 
3943
                    %% 'meta_var' annotation, but otherwise leave
 
3944
                    %% the node unchanged.
 
3945
                    set_ann(Node, lists:delete(meta_var, get_ann(Node)))
 
3946
            end;
 
3947
        Type ->
 
3948
            meta_0(Type, Node)
 
3949
    end.
 
3950
 
 
3951
meta_0(Type, Node) ->
 
3952
    case get_ann(Node) of
 
3953
        [] ->
 
3954
            meta_1(Type, Node);
 
3955
        As ->
 
3956
            meta_call(set_ann, [meta_1(Type, Node), abstract(As)])
 
3957
    end.
 
3958
 
 
3959
meta_1(literal, Node) ->
 
3960
    %% We handle atomic literals separately, to get a bit
 
3961
    %% more compact code. For the rest, we use 'abstract'.
 
3962
    case concrete(Node) of
 
3963
        V when atom(V) ->
 
3964
            meta_call(c_atom, [Node]);
 
3965
        V when integer(V) ->
 
3966
            meta_call(c_int, [Node]);
 
3967
        V when float(V) ->
 
3968
            meta_call(c_float, [Node]);
 
3969
        [] ->
 
3970
            meta_call(c_nil, []);
 
3971
        _ ->
 
3972
            meta_call(abstract, [Node])
 
3973
    end;
 
3974
meta_1(var, Node) ->
 
3975
    %% A normal variable or function name.
 
3976
    meta_call(c_var, [abstract(var_name(Node))]);
 
3977
meta_1(values, Node) ->
 
3978
    meta_call(c_values,
 
3979
              [make_list(meta_list(values_es(Node)))]);
 
3980
meta_1(binary, Node) ->
 
3981
    meta_call(c_binary,
 
3982
              [make_list(meta_list(binary_segments(Node)))]);
 
3983
meta_1(bitstr, Node) ->
 
3984
    meta_call(c_bitstr,
 
3985
              [meta(bitstr_val(Node)),
 
3986
               meta(bitstr_size(Node)),
 
3987
               meta(bitstr_unit(Node)),
 
3988
               meta(bitstr_type(Node)),
 
3989
               meta(bitstr_flags(Node))]);
 
3990
meta_1(cons, Node) ->
 
3991
    %% The list is split up if some sublist has annotatations. If
 
3992
    %% we get exactly one element, we generate a 'c_cons' call
 
3993
    %% instead of 'make_list' to reconstruct the node.
 
3994
    case split_list(Node) of
 
3995
        {[H], none} ->
 
3996
            meta_call(c_cons, [meta(H), meta(c_nil())]);
 
3997
        {[H], Node1} ->
 
3998
            meta_call(c_cons, [meta(H), meta(Node1)]);
 
3999
        {L, none} ->
 
4000
            meta_call(make_list, [make_list(meta_list(L))]);
 
4001
        {L, Node1} ->
 
4002
            meta_call(make_list,
 
4003
                      [make_list(meta_list(L)), meta(Node1)])
 
4004
    end;
 
4005
meta_1(tuple, Node) ->
 
4006
    meta_call(c_tuple,
 
4007
              [make_list(meta_list(tuple_es(Node)))]);
 
4008
meta_1('let', Node) ->
 
4009
    meta_call(c_let,
 
4010
              [make_list(meta_list(let_vars(Node))),
 
4011
               meta(let_arg(Node)), meta(let_body(Node))]);
 
4012
meta_1(seq, Node) ->
 
4013
    meta_call(c_seq,
 
4014
              [meta(seq_arg(Node)), meta(seq_body(Node))]);
 
4015
meta_1(apply, Node) ->
 
4016
    meta_call(c_apply,
 
4017
              [meta(apply_op(Node)),
 
4018
               make_list(meta_list(apply_args(Node)))]);
 
4019
meta_1(call, Node) ->
 
4020
    meta_call(c_call,
 
4021
              [meta(call_module(Node)), meta(call_name(Node)),
 
4022
               make_list(meta_list(call_args(Node)))]);
 
4023
meta_1(primop, Node) ->
 
4024
    meta_call(c_primop,
 
4025
              [meta(primop_name(Node)),
 
4026
               make_list(meta_list(primop_args(Node)))]);
 
4027
meta_1('case', Node) ->
 
4028
    meta_call(c_case,
 
4029
              [meta(case_arg(Node)),
 
4030
               make_list(meta_list(case_clauses(Node)))]);
 
4031
meta_1(clause, Node) ->
 
4032
    meta_call(c_clause,
 
4033
              [make_list(meta_list(clause_pats(Node))),
 
4034
               meta(clause_guard(Node)),
 
4035
               meta(clause_body(Node))]);
 
4036
meta_1(alias, Node) ->
 
4037
    meta_call(c_alias,
 
4038
              [meta(alias_var(Node)), meta(alias_pat(Node))]);
 
4039
meta_1('fun', Node) ->
 
4040
    meta_call(c_fun,
 
4041
              [make_list(meta_list(fun_vars(Node))),
 
4042
               meta(fun_body(Node))]);
 
4043
meta_1('receive', Node) ->
 
4044
    meta_call(c_receive,
 
4045
              [make_list(meta_list(receive_clauses(Node))),
 
4046
               meta(receive_timeout(Node)),
 
4047
               meta(receive_action(Node))]);
 
4048
meta_1('try', Node) ->
 
4049
    meta_call(c_try,
 
4050
              [meta(try_arg(Node)),
 
4051
               make_list(meta_list(try_vars(Node))),
 
4052
               meta(try_body(Node)),
 
4053
               make_list(meta_list(try_evars(Node))),
 
4054
               meta(try_handler(Node))]);
 
4055
meta_1('catch', Node) ->
 
4056
    meta_call(c_catch, [meta(catch_body(Node))]);
 
4057
meta_1(letrec, Node) ->
 
4058
    meta_call(c_letrec,
 
4059
              [make_list([c_tuple([meta(N), meta(F)])
 
4060
                          || {N, F} <- letrec_defs(Node)]),
 
4061
               meta(letrec_body(Node))]);
 
4062
meta_1(module, Node) ->
 
4063
    meta_call(c_module,
 
4064
              [meta(module_name(Node)),
 
4065
               make_list(meta_list(module_exports(Node))),
 
4066
               make_list([c_tuple([meta(A), meta(V)])
 
4067
                          || {A, V} <- module_attrs(Node)]),
 
4068
               make_list([c_tuple([meta(N), meta(F)])
 
4069
                          || {N, F} <- module_defs(Node)])]).
 
4070
 
 
4071
meta_call(F, As) ->
 
4072
    c_call(c_atom(?MODULE), c_atom(F), As).
 
4073
 
 
4074
meta_list([T | Ts]) ->
 
4075
    [meta(T) | meta_list(Ts)];
 
4076
meta_list([]) ->
 
4077
    [].
 
4078
 
 
4079
split_list(Node) ->
 
4080
    split_list(set_ann(Node, []), []).
 
4081
 
 
4082
split_list(Node, L) ->
 
4083
    A = get_ann(Node),
 
4084
    case type(Node) of
 
4085
        cons when A == [] ->
 
4086
            split_list(cons_tl(Node), [cons_hd(Node) | L]);
 
4087
        nil when A == [] ->
 
4088
            {lists:reverse(L), none};
 
4089
        _ ->
 
4090
            {lists:reverse(L), Node}
 
4091
    end.
 
4092
 
 
4093
 
 
4094
%% ---------------------------------------------------------------------
 
4095
 
 
4096
%% General utilities
 
4097
 
 
4098
is_lit_list([#literal{} | Es]) ->
 
4099
    is_lit_list(Es);
 
4100
is_lit_list([_ | _]) ->
 
4101
    false;
 
4102
is_lit_list([]) ->
 
4103
    true.
 
4104
 
 
4105
lit_list_vals([#literal{val = V} | Es]) ->
 
4106
    [V | lit_list_vals(Es)];
 
4107
lit_list_vals([]) ->
 
4108
    [].
 
4109
 
 
4110
make_lit_list([V | Vs]) ->
 
4111
    [#literal{val = V} | make_lit_list(Vs)];
 
4112
make_lit_list([]) ->
 
4113
    [].
 
4114
 
 
4115
%% The following tests are the same as done by 'io_lib:char_list' and
 
4116
%% 'io_lib:printable_list', respectively, but for a single character.
 
4117
 
 
4118
is_char_value(V) when V >= $\000, V =< $\377 -> true;
 
4119
is_char_value(_) -> false.
 
4120
 
 
4121
is_print_char_value(V) when V >= $\040, V =< $\176 -> true;
 
4122
is_print_char_value(V) when V >= $\240, V =< $\377 -> true;
 
4123
is_print_char_value(V) when V =:= $\b -> true;
 
4124
is_print_char_value(V) when V =:= $\d -> true;
 
4125
is_print_char_value(V) when V =:= $\e -> true;
 
4126
is_print_char_value(V) when V =:= $\f -> true;
 
4127
is_print_char_value(V) when V =:= $\n -> true;
 
4128
is_print_char_value(V) when V =:= $\r -> true;
 
4129
is_print_char_value(V) when V =:= $\s -> true;
 
4130
is_print_char_value(V) when V =:= $\t -> true;
 
4131
is_print_char_value(V) when V =:= $\v -> true;
 
4132
is_print_char_value(V) when V =:= $\" -> true;
 
4133
is_print_char_value(V) when V =:= $\' -> true;
 
4134
is_print_char_value(V) when V =:= $\\ -> true;
 
4135
is_print_char_value(_) -> false.
 
4136
 
 
4137
is_char_list([V | Vs]) when integer(V) ->
 
4138
    case is_char_value(V) of
 
4139
        true ->
 
4140
            is_char_list(Vs);
 
4141
        false ->
 
4142
            false
 
4143
    end;
 
4144
is_char_list([]) ->
 
4145
    true;
 
4146
is_char_list(_) ->
 
4147
    false.
 
4148
 
 
4149
is_print_char_list([V | Vs]) when integer(V) ->
 
4150
    case is_print_char_value(V) of
 
4151
        true ->
 
4152
            is_print_char_list(Vs);
 
4153
        false ->
 
4154
            false
 
4155
    end;
 
4156
is_print_char_list([]) ->
 
4157
    true;
 
4158
is_print_char_list(_) ->
 
4159
    false.
 
4160
 
 
4161
unfold_tuples([{X, Y} | Ps]) ->
 
4162
    [X, Y | unfold_tuples(Ps)];
 
4163
unfold_tuples([]) ->
 
4164
    [].
 
4165
 
 
4166
fold_tuples([X, Y | Es]) ->
 
4167
    [{X, Y} | fold_tuples(Es)];
 
4168
fold_tuples([]) ->
 
4169
    [].