~ubuntu-branches/ubuntu/lucid/erlang/lucid-updates

« back to all changes in this revision

Viewing changes to lib/compiler/src/cerl_trees.erl

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
Tags: 1:13.b.3-dfsg-2ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
66
66
%% node has depth zero, the tree representing "<code>{foo,
67
67
%% bar}</code>" has depth one, etc.
68
68
 
 
69
-spec depth(cerl:cerl()) -> non_neg_integer().
 
70
 
69
71
depth(T) ->
70
72
    case subtrees(T) of
71
73
        [] ->
85
87
%%
86
88
%% @doc Returns the number of nodes in <code>Tree</code>.
87
89
 
 
90
-spec size(cerl:cerl()) -> non_neg_integer().
 
91
 
88
92
size(T) ->
89
93
    fold(fun (_, S) -> S + 1 end, 0, T).
90
94
 
101
105
%%
102
106
%% @see mapfold/3
103
107
 
 
108
-spec map(fun((cerl:cerl()) -> cerl:cerl()), cerl:cerl()) -> cerl:cerl().
 
109
 
104
110
map(F, T) ->
105
111
    F(map_1(F, T)).
106
112
 
111
117
                [_ | _] ->
112
118
                    update_c_cons(T, map(F, cons_hd(T)),
113
119
                                  map(F, cons_tl(T)));
114
 
                V when is_tuple(V), tuple_size(V) > 0 ->
 
120
                V when tuple_size(V) > 0 ->
115
121
                    update_c_tuple(T, map_list(F, tuple_es(T)));
116
122
                _ ->
117
123
                    T
207
213
%%
208
214
%% @see mapfold/3
209
215
 
 
216
-spec fold(fun((cerl:cerl(), term()) -> term()), term(), cerl:cerl()) -> term().
 
217
 
210
218
fold(F, S, T) ->
211
219
    F(T, fold_1(F, S, T)).
212
220
 
216
224
            case concrete(T) of
217
225
                [_ | _] ->
218
226
                    fold(F, fold(F, S, cons_hd(T)), cons_tl(T));
219
 
                V when is_tuple(V), tuple_size(V) > 0 ->
 
227
                V when tuple_size(V) > 0 ->
220
228
                    fold_list(F, S, tuple_es(T));
221
229
                _ ->
222
230
                    S
314
322
%% @see map/2
315
323
%% @see fold/3
316
324
 
 
325
-spec mapfold(fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}),
 
326
              term(), cerl:cerl()) -> {cerl:cerl(), term()}.
 
327
 
317
328
mapfold(F, S0, T) ->
318
329
    case type(T) of
319
330
        literal ->
322
333
                    {T1, S1} = mapfold(F, S0, cons_hd(T)),
323
334
                    {T2, S2} = mapfold(F, S1, cons_tl(T)),
324
335
                    F(update_c_cons(T, T1, T2), S2);
325
 
                V when is_tuple(V), tuple_size(V) > 0 ->
 
336
                V when tuple_size(V) > 0 ->
326
337
                    {Ts, S1} = mapfold_list(F, S0, tuple_es(T)),
327
338
                    F(update_c_tuple(T, Ts), S1);
328
339
                _ ->
445
456
%%
446
457
%% @see free_variables/1
447
458
 
 
459
-spec variables(cerl:cerl()) -> [cerl:var_name()].
 
460
 
448
461
variables(T) ->
449
462
    variables(T, false).
450
463
 
456
469
%%
457
470
%% @see variables/1
458
471
 
 
472
-spec free_variables(cerl:cerl()) -> [cerl:var_name()].
 
473
 
459
474
free_variables(T) ->
460
475
    variables(T, true).
461
476
 
614
629
%%
615
630
%% @equiv label(Tree, 0)
616
631
 
 
632
-spec label(cerl:cerl()) -> {cerl:cerl(), integer()}.
 
633
 
617
634
label(T) ->
618
635
    label(T, 0).
619
636
 
641
658
%% @see label/1
642
659
%% @see size/1
643
660
 
 
661
-spec label(cerl:cerl(), integer()) -> {cerl:cerl(), integer()}.
 
662
 
644
663
label(T, N) ->
645
664
    label(T, N, dict:new()).
646
665
 
800
819
filter_labels([]) ->
801
820
    [].
802
821
 
 
822
-spec get_label(cerl:cerl()) -> 'top' | integer().
 
823
 
803
824
get_label(T) ->
804
825
    case get_ann(T) of
805
826
        [{label, L} | _] -> L;