~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/core_pp.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 Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: core_pp.erl,v 1.1 2008/12/17 09:53:42 mikpe Exp $
 
17
%%
 
18
%% Purpose : Core Erlang (naive) prettyprinter
 
19
 
 
20
-module(core_pp).
 
21
 
 
22
-export([format/1]).
 
23
 
 
24
-include("core_parse.hrl").
 
25
 
 
26
%% ====================================================================== %%
 
27
%% format(Node) -> Text
 
28
%%      Node = coreErlang()
 
29
%%      Text = string() | [Text]
 
30
%%
 
31
%%      Prettyprint-formats (naively) an abstract Core Erlang syntax
 
32
%%      tree.
 
33
 
 
34
-record(ctxt, {class = term,
 
35
               indent = 0,
 
36
               item_indent = 2,
 
37
               body_indent = 4,
 
38
               tab_width = 8,
 
39
               line = 0}).
 
40
 
 
41
format(Node) -> case catch format(Node, #ctxt{}) of
 
42
                    {'EXIT',_} -> io_lib:format("~p",[Node]);
 
43
                    Other -> Other
 
44
                end.
 
45
 
 
46
maybe_anno(Node, Fun, Ctxt) ->
 
47
    As = core_lib:get_anno(Node),
 
48
    case get_line(As) of
 
49
        none ->
 
50
            maybe_anno(Node, Fun, Ctxt, As);
 
51
        Line ->
 
52
            if  Line > Ctxt#ctxt.line ->
 
53
                    [io_lib:format("%% Line ~w",[Line]),
 
54
                     nl_indent(Ctxt),
 
55
                     maybe_anno(Node, Fun, Ctxt#ctxt{line = Line}, As)
 
56
                    ];
 
57
                true ->
 
58
                    maybe_anno(Node, Fun, Ctxt, As)
 
59
            end
 
60
    end.
 
61
 
 
62
maybe_anno(Node, Fun, Ctxt, As) ->
 
63
    case strip_line(As) of
 
64
        [] ->
 
65
            Fun(Node, Ctxt);
 
66
        List ->
 
67
            Ctxt1 = add_indent(Ctxt, 2),
 
68
            Ctxt2 = add_indent(Ctxt1, 3),
 
69
            ["( ",
 
70
             Fun(Node, Ctxt1),
 
71
             nl_indent(Ctxt1),
 
72
             "-| ",format_1(core_lib:make_literal(List), Ctxt2)," )"
 
73
            ]
 
74
    end.
 
75
 
 
76
strip_line([A | As]) when integer(A) ->
 
77
    strip_line(As);
 
78
strip_line([A | As]) ->
 
79
    [A | strip_line(As)];
 
80
strip_line([]) ->
 
81
    [].
 
82
 
 
83
get_line([L | _As]) when integer(L) ->
 
84
    L;
 
85
get_line([_ | As]) ->
 
86
    get_line(As);
 
87
get_line([]) ->
 
88
    none.
 
89
 
 
90
format(Node, Ctxt) ->
 
91
    maybe_anno(Node, fun format_1/2, Ctxt).
 
92
 
 
93
format_1(#c_char{val=C}, _) -> io_lib:write_char(C);
 
94
format_1(#c_int{val=I}, _) -> integer_to_list(I);
 
95
format_1(#c_float{val=F}, _) -> float_to_list(F);
 
96
format_1(#c_atom{val=A}, _) -> core_atom(A);
 
97
format_1(#c_nil{}, _) -> "[]";
 
98
format_1(#c_string{val=S}, _) -> io_lib:write_string(S);
 
99
format_1(#c_var{name=V}, _) ->
 
100
    %% Internal variable names may be:
 
101
    %%     - atoms representing proper Erlang variable names, or
 
102
    %%     any atoms that may be printed without single-quoting
 
103
    %%     - nonnegative integers.
 
104
    %% It is important that when printing variables, no two names
 
105
    %% should ever map to the same string.
 
106
    if atom(V) ->
 
107
            S = atom_to_list(V),
 
108
            case S of
 
109
                [C | _] when C >= $A, C =< $Z ->
 
110
                    %% Ordinary uppercase-prefixed names are
 
111
                    %% printed just as they are.
 
112
                    S;
 
113
                [$_ | _] ->
 
114
                    %% Already "_"-prefixed names are prefixed
 
115
                    %% with "_X", e.g. '_foo' => '_X_foo', to
 
116
                    %% avoid generating things like "____foo" upon
 
117
                    %% repeated writing and reading of code.
 
118
                    %% ("_X_X_X_foo" is better.)
 
119
                    [$_, $X | S];
 
120
                _ ->
 
121
                    %% Plain atoms are prefixed with a single "_".
 
122
                    %% E.g. foo => "_foo".
 
123
                    [$_ | S]
 
124
            end;
 
125
       integer(V) ->
 
126
            %% Integers are also simply prefixed with "_".
 
127
            [$_ | integer_to_list(V)]
 
128
    end;
 
129
format_1(#c_binary{segments=Segs}, Ctxt) ->
 
130
    ["#{",
 
131
     format_vseq(Segs, "", ",", add_indent(Ctxt, 2),
 
132
                 fun format_bitstr/2),
 
133
     "}#"
 
134
    ];
 
135
format_1(#c_tuple{es=Es}, Ctxt) ->
 
136
    [${,
 
137
     format_hseq(Es, ",", add_indent(Ctxt, 1), fun format/2),
 
138
     $}
 
139
    ];
 
140
format_1(#c_cons{hd=H,tl=T}, Ctxt) ->
 
141
    Txt = ["["|format(H, add_indent(Ctxt, 1))],
 
142
    [Txt|format_list_tail(T, add_indent(Ctxt, width(Txt, Ctxt)))];
 
143
format_1(#c_values{es=Es}, Ctxt) ->
 
144
    format_values(Es, Ctxt);
 
145
format_1(#c_alias{var=V,pat=P}, Ctxt) ->
 
146
    Txt = [format(V, Ctxt)|" = "],
 
147
    [Txt|format(P, add_indent(Ctxt, width(Txt, Ctxt)))];
 
148
format_1(#c_let{vars=Vs,arg=A,body=B}, Ctxt) ->
 
149
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
150
    ["let ",
 
151
     format_values(Vs, add_indent(Ctxt, 4)),
 
152
     " =",
 
153
     nl_indent(Ctxt1),
 
154
     format(A, Ctxt1),
 
155
     nl_indent(Ctxt),
 
156
     "in  "
 
157
     | format(B, add_indent(Ctxt, 4))
 
158
    ];
 
159
format_1(#c_letrec{defs=Fs,body=B}, Ctxt) ->
 
160
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
161
    ["letrec",
 
162
     nl_indent(Ctxt1),
 
163
     format_funcs(Fs, Ctxt1),
 
164
     nl_indent(Ctxt),
 
165
     "in  "
 
166
     | format(B, add_indent(Ctxt, 4))
 
167
    ];
 
168
format_1(#c_seq{arg=A,body=B}, Ctxt) ->
 
169
    Ctxt1 = add_indent(Ctxt, 4),
 
170
    ["do  ",
 
171
     format(A, Ctxt1),
 
172
     nl_indent(Ctxt1)
 
173
     | format(B, Ctxt1)
 
174
    ];
 
175
format_1(#c_case{arg=A,clauses=Cs}, Ctxt) ->
 
176
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.item_indent),
 
177
    ["case ",
 
178
     format(A, add_indent(Ctxt, 5)),
 
179
     " of",
 
180
     nl_indent(Ctxt1),
 
181
     format_clauses(Cs, Ctxt1),
 
182
     nl_indent(Ctxt)
 
183
     | "end"
 
184
    ];
 
185
format_1(#c_receive{clauses=Cs,timeout=T,action=A}, Ctxt) ->
 
186
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.item_indent),
 
187
    ["receive",
 
188
     nl_indent(Ctxt1),
 
189
     format_clauses(Cs, Ctxt1),
 
190
     nl_indent(Ctxt),
 
191
     "after ",
 
192
     format(T, add_indent(Ctxt, 6)),
 
193
     " ->",
 
194
     nl_indent(Ctxt1),
 
195
     format(A, Ctxt1)
 
196
    ];
 
197
format_1(#c_fname{id=I,arity=A}, _) ->
 
198
    [core_atom(I),$/,integer_to_list(A)];
 
199
format_1(#c_fun{vars=Vs,body=B}, Ctxt) ->
 
200
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
201
    ["fun (",
 
202
     format_hseq(Vs, ",", add_indent(Ctxt, 5), fun format/2),
 
203
     ") ->",
 
204
     nl_indent(Ctxt1)
 
205
     | format(B, Ctxt1)
 
206
    ];
 
207
format_1(#c_apply{op=O,args=As}, Ctxt0) ->
 
208
    Ctxt1 = add_indent(Ctxt0, 6),               %"apply "
 
209
    Op = format(O, Ctxt1),
 
210
    Ctxt2 = add_indent(Ctxt0, 4),
 
211
    ["apply ",Op,
 
212
     nl_indent(Ctxt2),
 
213
     $(,format_hseq(As, ", ", add_indent(Ctxt2, 1), fun format/2),$)
 
214
    ];
 
215
format_1(#c_call{module=M,name=N,args=As}, Ctxt0) ->
 
216
    Ctxt1 = add_indent(Ctxt0, 5),               %"call "
 
217
    Mod = format(M, Ctxt1),
 
218
    Ctxt2 = add_indent(Ctxt1, width(Mod, Ctxt1)+1),
 
219
    Name = format(N, Ctxt2),
 
220
    Ctxt3 = add_indent(Ctxt0, 4),
 
221
    ["call ",Mod,":",Name,
 
222
     nl_indent(Ctxt3),
 
223
     $(,format_hseq(As, ", ", add_indent(Ctxt3, 1), fun format/2),$)
 
224
    ];
 
225
format_1(#c_primop{name=N,args=As}, Ctxt0) ->
 
226
    Ctxt1 = add_indent(Ctxt0, 7),               %"primop "
 
227
    Name = format(N, Ctxt1),
 
228
    Ctxt2 = add_indent(Ctxt0, 4),
 
229
    ["primop ",Name,
 
230
     nl_indent(Ctxt2),
 
231
     $(,format_hseq(As, ", ", add_indent(Ctxt2, 1), fun format/2),$)
 
232
    ];
 
233
format_1(#c_catch{body=B}, Ctxt) ->
 
234
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
235
    ["catch",
 
236
     nl_indent(Ctxt1),
 
237
     format(B, Ctxt1)
 
238
    ];
 
239
format_1(#c_try{arg=E,vars=Vs,body=B,evars=Evs,handler=H}, Ctxt) ->
 
240
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
241
    ["try",
 
242
     nl_indent(Ctxt1),
 
243
     format(E, Ctxt1),
 
244
     nl_indent(Ctxt),
 
245
     "of ",
 
246
     format_values(Vs, add_indent(Ctxt, 3)),
 
247
     " ->",
 
248
     nl_indent(Ctxt1),
 
249
     format(B, Ctxt1),
 
250
     nl_indent(Ctxt),
 
251
     "catch ",
 
252
     format_values(Evs, add_indent(Ctxt, 6)),
 
253
     " ->",
 
254
     nl_indent(Ctxt1)
 
255
     | format(H, Ctxt1)
 
256
    ];
 
257
format_1(#c_def{name=N,val=V}, Ctxt) ->
 
258
    Ctxt1 = add_indent(set_class(Ctxt, expr), Ctxt#ctxt.body_indent),
 
259
    [format(N, Ctxt),
 
260
     " =",
 
261
     nl_indent(Ctxt1)
 
262
     | format(V, Ctxt1)
 
263
    ];
 
264
format_1(#c_module{name=N,exports=Es,attrs=As,defs=Ds}, Ctxt) ->
 
265
    Mod = ["module ", format(N, Ctxt)],
 
266
    [Mod," [",
 
267
     format_vseq(Es,
 
268
                 "", ",",
 
269
                 add_indent(set_class(Ctxt, term), width(Mod, Ctxt)+2),
 
270
                 fun format/2),
 
271
     "]",
 
272
     nl_indent(Ctxt),
 
273
     "    attributes [",
 
274
     format_vseq(As,
 
275
                 "", ",",
 
276
                 add_indent(set_class(Ctxt, def), 16),
 
277
                 fun format/2),
 
278
     "]",
 
279
     nl_indent(Ctxt),
 
280
     format_funcs(Ds, Ctxt),
 
281
     nl_indent(Ctxt)
 
282
     | "end"
 
283
    ];
 
284
format_1(Type, _) ->
 
285
    ["** Unsupported type: ",
 
286
     io_lib:write(Type)
 
287
     | " **"
 
288
    ].
 
289
 
 
290
format_funcs(Fs, Ctxt) ->
 
291
    format_vseq(Fs,
 
292
                "", "",
 
293
                set_class(Ctxt, def),
 
294
                fun format/2).
 
295
 
 
296
format_values(Vs, Ctxt) ->
 
297
    [$<,
 
298
     format_hseq(Vs, ",", add_indent(Ctxt, 1), fun format/2),
 
299
     $>].
 
300
 
 
301
format_bitstr(#c_bitstr{val=V,size=S,unit=U,type=T,flags=Fs}, Ctxt0) ->
 
302
    Vs = [S, U, T, Fs],
 
303
    Ctxt1 = add_indent(Ctxt0, 2),
 
304
    Val = format(V, Ctxt1),
 
305
    Ctxt2 = add_indent(Ctxt1, width(Val, Ctxt1) + 2),
 
306
    ["#<", Val, ">(", format_hseq(Vs,",", Ctxt2, fun format/2), $)].
 
307
 
 
308
format_clauses(Cs, Ctxt) ->
 
309
    format_vseq(Cs, "", "", set_class(Ctxt, clause),
 
310
                fun format_clause/2).
 
311
 
 
312
format_clause(Node, Ctxt) ->
 
313
    maybe_anno(Node, fun format_clause_1/2, Ctxt).
 
314
 
 
315
format_clause_1(#c_clause{pats=Ps,guard=G,body=B}, Ctxt) ->
 
316
    Ptxt = format_values(Ps, Ctxt),
 
317
    Ctxt2 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
318
    [Ptxt,
 
319
     " when ",
 
320
     format_guard(G, add_indent(set_class(Ctxt, expr),
 
321
                                 width(Ptxt, Ctxt) + 6)),
 
322
     " ->",
 
323
     nl_indent(Ctxt2)
 
324
     | format(B, set_class(Ctxt2, expr))
 
325
    ].
 
326
 
 
327
format_guard(Node, Ctxt) ->
 
328
    maybe_anno(Node, fun format_guard_1/2, Ctxt).
 
329
 
 
330
format_guard_1(#c_call{module=M,name=N,args=As}, Ctxt0) ->
 
331
    Ctxt1 = add_indent(Ctxt0, 5),               %"call "
 
332
    Mod = format(M, Ctxt1),
 
333
    Ctxt2 = add_indent(Ctxt1, width(Mod, Ctxt1)+1),
 
334
    Name = format(N, Ctxt2),
 
335
    Ctxt3 = add_indent(Ctxt0, 4),
 
336
    ["call ",Mod,":",Name,
 
337
     nl_indent(Ctxt3),
 
338
     $(,format_vseq(As, "",",", add_indent(Ctxt3, 1), fun format_guard/2),$)
 
339
    ];
 
340
format_guard_1(E, Ctxt) -> format_1(E, Ctxt).   %Anno already done
 
341
 
 
342
%% format_hseq([Thing], Separator, Context, Fun) -> Txt.
 
343
%%  Format a sequence horizontally on the same line with Separator between.
 
344
 
 
345
format_hseq([H], _, Ctxt, Fun) ->
 
346
    Fun(H, Ctxt);
 
347
format_hseq([H|T], Sep, Ctxt, Fun) ->
 
348
    Txt = [Fun(H, Ctxt)|Sep],
 
349
    Ctxt1 = add_indent(Ctxt, width(Txt, Ctxt)),
 
350
    [Txt|format_hseq(T, Sep, Ctxt1, Fun)];
 
351
format_hseq([], _, _, _) -> "".
 
352
 
 
353
%% format_vseq([Thing], LinePrefix, LineSuffix, Context, Fun) -> Txt.
 
354
%%  Format a sequence vertically in indented lines adding LinePrefix
 
355
%%  to the beginning of each line and LineSuffix to the end of each
 
356
%%  line.  No prefix on the first line or suffix on the last line.
 
357
 
 
358
format_vseq([H], _Pre, _Suf, Ctxt, Fun) ->
 
359
    Fun(H, Ctxt);
 
360
format_vseq([H|T], Pre, Suf, Ctxt, Fun) ->
 
361
    [Fun(H, Ctxt),Suf,nl_indent(Ctxt),Pre|
 
362
     format_vseq(T, Pre, Suf, Ctxt, Fun)];
 
363
format_vseq([], _, _, _, _) -> "".
 
364
 
 
365
format_list_tail(#c_nil{anno=[]}, _) -> "]";
 
366
format_list_tail(#c_cons{anno=[],hd=H,tl=T}, Ctxt) ->
 
367
    Txt = [$,|format(H, Ctxt)],
 
368
    Ctxt1 = add_indent(Ctxt, width(Txt, Ctxt)),
 
369
    [Txt|format_list_tail(T, Ctxt1)];
 
370
format_list_tail(Tail, Ctxt) ->
 
371
    ["|",format(Tail, add_indent(Ctxt, 1)),"]"].
 
372
 
 
373
indent(Ctxt) -> indent(Ctxt#ctxt.indent, Ctxt).
 
374
 
 
375
indent(N, _) when N =< 0 -> "";
 
376
indent(N, Ctxt) ->
 
377
    T = Ctxt#ctxt.tab_width,
 
378
    string:chars($\t, N div T, string:chars($\s, N rem T)).
 
379
 
 
380
nl_indent(Ctxt) -> [$\n|indent(Ctxt)].
 
381
 
 
382
 
 
383
unindent(T, Ctxt) ->
 
384
    unindent(T, Ctxt#ctxt.indent, Ctxt, []).
 
385
 
 
386
unindent(T, N, _, C) when N =< 0 ->
 
387
    [T|C];
 
388
unindent([$\s|T], N, Ctxt, C) ->
 
389
    unindent(T, N - 1, Ctxt, C);
 
390
unindent([$\t|T], N, Ctxt, C) ->
 
391
    Tab = Ctxt#ctxt.tab_width,
 
392
    if N >= Tab ->
 
393
            unindent(T, N - Tab, Ctxt, C);
 
394
       true ->
 
395
            unindent([string:chars($\s, Tab - N)|T], 0, Ctxt, C)
 
396
    end;
 
397
unindent([L|T], N, Ctxt, C) when list(L) ->
 
398
    unindent(L, N, Ctxt, [T|C]);
 
399
unindent([H|T], _, _, C) ->
 
400
    [H|[T|C]];
 
401
unindent([], N, Ctxt, [H|T]) ->
 
402
    unindent(H, N, Ctxt, T);
 
403
unindent([], _, _, []) -> [].
 
404
 
 
405
 
 
406
width(Txt, Ctxt) ->
 
407
    case catch width(Txt, 0, Ctxt, []) of
 
408
        {'EXIT',_} -> exit({bad_text,Txt});
 
409
        Other -> Other
 
410
    end.
 
411
 
 
412
width([$\t|T], A, Ctxt, C) ->
 
413
    width(T, A + Ctxt#ctxt.tab_width, Ctxt, C);
 
414
width([$\n|T], _, Ctxt, C) ->
 
415
    width(unindent([T|C], Ctxt), Ctxt);
 
416
width([H|T], A, Ctxt, C) when list(H) ->
 
417
    width(H, A, Ctxt, [T|C]);
 
418
width([_|T], A, Ctxt, C) ->
 
419
    width(T, A + 1, Ctxt, C);
 
420
width([], A, Ctxt, [H|T]) ->
 
421
    width(H, A, Ctxt, T);
 
422
width([], A, _, []) -> A.
 
423
 
 
424
add_indent(Ctxt, Dx) ->
 
425
    Ctxt#ctxt{indent = Ctxt#ctxt.indent + Dx}.
 
426
 
 
427
set_class(Ctxt, Class) ->
 
428
    Ctxt#ctxt{class = Class}.
 
429
 
 
430
core_atom(A) -> io_lib:write_string(atom_to_list(A), $').