~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
35
35
               indent = 0,
36
36
               item_indent = 2,
37
37
               body_indent = 4,
38
 
               tab_width = 8}).
 
38
               tab_width = 8,
 
39
               line = 0}).
39
40
 
40
 
format(Node) -> format(Node, #ctxt{});
41
41
format(Node) -> case catch format(Node, #ctxt{}) of
42
42
                    {'EXIT',_} -> io_lib:format("~p",[Node]);
43
43
                    Other -> Other
44
44
                end.
45
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([{file,_File} | As]) ->
 
79
    strip_line(As);
 
80
strip_line([A | As]) ->
 
81
    [A | strip_line(As)];
 
82
strip_line([]) ->
 
83
    [].
 
84
 
 
85
get_line([L | _As]) when integer(L) ->
 
86
    L;
 
87
get_line([_ | As]) ->
 
88
    get_line(As);
 
89
get_line([]) ->
 
90
    none.
 
91
 
46
92
format(Node, Ctxt) ->
47
 
    case core_lib:get_anno(Node) of
48
 
        [] ->
49
 
            format_1(Node, Ctxt);
50
 
        List ->
51
 
            Ctxt1 = ctxt_bump_indent(Ctxt, 2),
52
 
            Ctxt2 = ctxt_bump_indent(Ctxt1, 3),
53
 
            ["( ",
54
 
             format_1(Node, Ctxt1),
55
 
             nl_indent(Ctxt1),
56
 
             "-| ",format_1(core_lib:make_literal(List), Ctxt2)," )"
57
 
            ]
58
 
    end.
 
93
    maybe_anno(Node, fun format_1/2, Ctxt).
59
94
 
60
95
format_1(#c_char{val=C}, _) -> io_lib:write_char(C);
61
96
format_1(#c_int{val=I}, _) -> integer_to_list(I);
93
128
            %% Integers are also simply prefixed with "_".
94
129
            [$_ | integer_to_list(V)]
95
130
    end;
96
 
format_1(#c_binary{segs=Segs}, Ctxt) ->
97
 
    ["#<",
98
 
     format_hseq(Segs, ",", ctxt_bump_indent(Ctxt, 2), fun format_bin_seg/2),
99
 
     ">#"
 
131
format_1(#c_binary{segments=Segs}, Ctxt) ->
 
132
    ["#{",
 
133
     format_vseq(Segs, "", ",", add_indent(Ctxt, 2),
 
134
                 fun format_bitstr/2),
 
135
     "}#"
100
136
    ];
101
137
format_1(#c_tuple{es=Es}, Ctxt) ->
102
138
    [${,
103
 
     format_hseq(Es, ",", ctxt_bump_indent(Ctxt, 1), fun format/2),
 
139
     format_hseq(Es, ",", add_indent(Ctxt, 1), fun format/2),
104
140
     $}
105
141
    ];
106
142
format_1(#c_cons{hd=H,tl=T}, Ctxt) ->
107
 
    Txt = ["["|format(H, ctxt_bump_indent(Ctxt, 1))],
108
 
    [Txt|format_list_tail(T, ctxt_bump_indent(Ctxt, width(Txt, Ctxt)))];
 
143
    Txt = ["["|format(H, add_indent(Ctxt, 1))],
 
144
    [Txt|format_list_tail(T, add_indent(Ctxt, width(Txt, Ctxt)))];
109
145
format_1(#c_values{es=Es}, Ctxt) ->
110
146
    format_values(Es, Ctxt);
111
147
format_1(#c_alias{var=V,pat=P}, Ctxt) ->
112
148
    Txt = [format(V, Ctxt)|" = "],
113
 
    [Txt|format(P, ctxt_bump_indent(Ctxt, width(Txt, Ctxt)))];
114
 
format_1(#c_let{vars=Vs,arg=A,body=B}, Ctxt) ->
115
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
116
 
    ["let ",
117
 
     format_values(Vs, ctxt_bump_indent(Ctxt, 4)),
118
 
     " =",
119
 
     nl_indent(Ctxt1),
120
 
     format(A, Ctxt1),
121
 
     nl_indent(Ctxt),
122
 
     "in  "
123
 
     | format(B, ctxt_bump_indent(Ctxt, 4))
124
 
    ];
 
149
    [Txt|format(P, add_indent(Ctxt, width(Txt, Ctxt)))];
 
150
format_1(#c_let{vars=Vs0,arg=A,body=B}, Ctxt) ->
 
151
    Vs = [core_lib:set_anno(V, []) || V <- Vs0],
 
152
    case is_simple_term(A) of
 
153
        false ->
 
154
            Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
155
            ["let ",
 
156
             format_values(Vs, add_indent(Ctxt, 4)),
 
157
             " =",
 
158
             nl_indent(Ctxt1),
 
159
             format(A, Ctxt1),
 
160
             nl_indent(Ctxt),
 
161
             "in  "
 
162
             | format(B, add_indent(Ctxt, 4))
 
163
            ];
 
164
        true ->
 
165
            Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
 
166
            ["let ",
 
167
             format_values(Vs, add_indent(Ctxt, 4)),
 
168
             " = ",
 
169
             format(core_lib:set_anno(A, []), Ctxt1),
 
170
             nl_indent(Ctxt),
 
171
             "in  "
 
172
             | format(B, add_indent(Ctxt, 4))
 
173
            ]
 
174
    end;
125
175
format_1(#c_letrec{defs=Fs,body=B}, Ctxt) ->
126
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
176
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
127
177
    ["letrec",
128
178
     nl_indent(Ctxt1),
129
179
     format_funcs(Fs, Ctxt1),
130
180
     nl_indent(Ctxt),
131
181
     "in  "
132
 
     | format(B, ctxt_bump_indent(Ctxt, 4))
 
182
     | format(B, add_indent(Ctxt, 4))
133
183
    ];
134
184
format_1(#c_seq{arg=A,body=B}, Ctxt) ->
135
 
    Ctxt1 = ctxt_bump_indent(Ctxt, 4),
 
185
    Ctxt1 = add_indent(Ctxt, 4),
136
186
    ["do  ",
137
187
     format(A, Ctxt1),
138
188
     nl_indent(Ctxt1)
139
189
     | format(B, Ctxt1)
140
190
    ];
141
191
format_1(#c_case{arg=A,clauses=Cs}, Ctxt) ->
142
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent),
 
192
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.item_indent),
143
193
    ["case ",
144
 
     format(A, ctxt_bump_indent(Ctxt, 5)),
 
194
     format(A, add_indent(Ctxt, 5)),
145
195
     " of",
146
196
     nl_indent(Ctxt1),
147
197
     format_clauses(Cs, Ctxt1),
149
199
     | "end"
150
200
    ];
151
201
format_1(#c_receive{clauses=Cs,timeout=T,action=A}, Ctxt) ->
152
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent),
 
202
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.item_indent),
153
203
    ["receive",
154
204
     nl_indent(Ctxt1),
155
205
     format_clauses(Cs, Ctxt1),
156
206
     nl_indent(Ctxt),
157
207
     "after ",
158
 
     format(T, ctxt_bump_indent(Ctxt, 6)),
 
208
     format(T, add_indent(Ctxt, 6)),
159
209
     " ->",
160
210
     nl_indent(Ctxt1),
161
211
     format(A, Ctxt1)
163
213
format_1(#c_fname{id=I,arity=A}, _) ->
164
214
    [core_atom(I),$/,integer_to_list(A)];
165
215
format_1(#c_fun{vars=Vs,body=B}, Ctxt) ->
166
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
216
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
167
217
    ["fun (",
168
 
     format_hseq(Vs, ",", ctxt_bump_indent(Ctxt, 5), fun format/2),
 
218
     format_hseq(Vs, ",", add_indent(Ctxt, 5), fun format/2),
169
219
     ") ->",
170
220
     nl_indent(Ctxt1)
171
221
     | format(B, Ctxt1)
172
222
    ];
173
223
format_1(#c_apply{op=O,args=As}, Ctxt0) ->
174
 
    Ctxt1 = ctxt_bump_indent(Ctxt0, 6),         %"apply "
 
224
    Ctxt1 = add_indent(Ctxt0, 6),               %"apply "
175
225
    Op = format(O, Ctxt1),
176
 
    Ctxt2 = ctxt_bump_indent(Ctxt0, 4),
 
226
    Ctxt2 = add_indent(Ctxt0, 4),
177
227
    ["apply ",Op,
178
228
     nl_indent(Ctxt2),
179
 
     $(,format_hseq(As, ", ", ctxt_bump_indent(Ctxt2, 1), fun format/2),$)
 
229
     $(,format_hseq(As, ", ", add_indent(Ctxt2, 1), fun format/2),$)
180
230
    ];
181
231
format_1(#c_call{module=M,name=N,args=As}, Ctxt0) ->
182
 
    Ctxt1 = ctxt_bump_indent(Ctxt0, 5),         %"call "
 
232
    Ctxt1 = add_indent(Ctxt0, 5),               %"call "
183
233
    Mod = format(M, Ctxt1),
184
 
    Ctxt2 = ctxt_bump_indent(Ctxt1, width(Mod, Ctxt1)+1),
 
234
    Ctxt2 = add_indent(Ctxt1, width(Mod, Ctxt1)+1),
185
235
    Name = format(N, Ctxt2),
186
 
    Ctxt3 = ctxt_bump_indent(Ctxt0, 4),
 
236
    Ctxt3 = add_indent(Ctxt0, 4),
187
237
    ["call ",Mod,":",Name,
188
238
     nl_indent(Ctxt3),
189
 
     $(,format_hseq(As, ", ", ctxt_bump_indent(Ctxt3, 1), fun format/2),$)
 
239
     $(,format_hseq(As, ", ", add_indent(Ctxt3, 1), fun format/2),$)
190
240
    ];
191
241
format_1(#c_primop{name=N,args=As}, Ctxt0) ->
192
 
    Ctxt1 = ctxt_bump_indent(Ctxt0, 7),         %"primop "
 
242
    Ctxt1 = add_indent(Ctxt0, 7),               %"primop "
193
243
    Name = format(N, Ctxt1),
194
 
    Ctxt2 = ctxt_bump_indent(Ctxt0, 4),
 
244
    Ctxt2 = add_indent(Ctxt0, 4),
195
245
    ["primop ",Name,
196
246
     nl_indent(Ctxt2),
197
 
     $(,format_hseq(As, ", ", ctxt_bump_indent(Ctxt2, 1), fun format/2),$)
 
247
     $(,format_hseq(As, ", ", add_indent(Ctxt2, 1), fun format/2),$)
198
248
    ];
199
249
format_1(#c_catch{body=B}, Ctxt) ->
200
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
250
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
201
251
    ["catch",
202
252
     nl_indent(Ctxt1),
203
253
     format(B, Ctxt1)
204
254
    ];
205
255
format_1(#c_try{arg=E,vars=Vs,body=B,evars=Evs,handler=H}, Ctxt) ->
206
 
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
256
    Ctxt1 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
207
257
    ["try",
208
258
     nl_indent(Ctxt1),
209
259
     format(E, Ctxt1),
210
260
     nl_indent(Ctxt),
211
261
     "of ",
212
 
     format_values(Vs, ctxt_bump_indent(Ctxt, 3)),
 
262
     format_values(Vs, add_indent(Ctxt, 3)),
213
263
     " ->",
214
264
     nl_indent(Ctxt1),
215
265
     format(B, Ctxt1),
216
266
     nl_indent(Ctxt),
217
267
     "catch ",
218
 
     format_values(Evs, ctxt_bump_indent(Ctxt, 6)),
 
268
     format_values(Evs, add_indent(Ctxt, 6)),
219
269
     " ->",
220
270
     nl_indent(Ctxt1)
221
271
     | format(H, Ctxt1)
222
272
    ];
223
273
format_1(#c_def{name=N,val=V}, Ctxt) ->
224
 
    Ctxt1 = ctxt_set_bump(Ctxt, expr, Ctxt#ctxt.body_indent),
 
274
    Ctxt1 = add_indent(set_class(Ctxt, expr), Ctxt#ctxt.body_indent),
225
275
    [format(N, Ctxt),
226
276
     " =",
227
277
     nl_indent(Ctxt1)
232
282
    [Mod," [",
233
283
     format_vseq(Es,
234
284
                 "", ",",
235
 
                 ctxt_set_bump(Ctxt, term, width(Mod, Ctxt)+2),
 
285
                 add_indent(set_class(Ctxt, term), width(Mod, Ctxt)+2),
236
286
                 fun format/2),
237
287
     "]",
238
288
     nl_indent(Ctxt),
239
289
     "    attributes [",
240
290
     format_vseq(As,
241
291
                 "", ",",
242
 
                 ctxt_set_bump(Ctxt, def, 16),
 
292
                 add_indent(set_class(Ctxt, def), 16),
243
293
                 fun format/2),
244
294
     "]",
245
295
     nl_indent(Ctxt),
256
306
format_funcs(Fs, Ctxt) ->
257
307
    format_vseq(Fs,
258
308
                "", "",
259
 
                ctxt_set_class(Ctxt, def),
 
309
                set_class(Ctxt, def),
260
310
                fun format/2).
261
311
 
262
312
format_values(Vs, Ctxt) ->
263
313
    [$<,
264
 
     format_hseq(Vs, ",", ctxt_bump_indent(Ctxt, 1), fun format/2),
 
314
     format_hseq(Vs, ",", add_indent(Ctxt, 1), fun format/2),
265
315
     $>].
266
316
 
267
 
format_bin_seg(#c_bin_seg{val=V,size=S,unit=U,type=T,flags=Fs}, Ctxt0) ->
268
 
    Vtxt = format(V, Ctxt0),
269
 
    Ctxt1 = ctxt_bump_indent(Ctxt0, width(Vtxt, Ctxt0)+1), %":"
270
 
    Stxt = format(S, Ctxt1),
271
 
    [Vtxt,$:,Stxt,
272
 
     if  U == 1 -> "";                          %This is default
273
 
         true -> [$*|io_lib:write(U)]
274
 
     end,
275
 
     $:,core_atom(T),
276
 
     lists:map(fun (F) -> [$-|core_atom(F)] end, Fs)
277
 
    ].
 
317
format_bitstr(#c_bitstr{val=V,size=S,unit=U,type=T,flags=Fs}, Ctxt0) ->
 
318
    Vs = [S, U, T, Fs],
 
319
    Ctxt1 = add_indent(Ctxt0, 2),
 
320
    Val = format(V, Ctxt1),
 
321
    Ctxt2 = add_indent(Ctxt1, width(Val, Ctxt1) + 2),
 
322
    ["#<", Val, ">(", format_hseq(Vs,",", Ctxt2, fun format/2), $)].
278
323
 
279
324
format_clauses(Cs, Ctxt) ->
280
 
    format_vseq(Cs, "", "", ctxt_set_class(Ctxt, clause),
 
325
    format_vseq(Cs, "", "", set_class(Ctxt, clause),
281
326
                fun format_clause/2).
282
327
 
283
 
format_clause(#c_clause{pats=Ps,guard=G,body=B}, Ctxt) ->
 
328
format_clause(Node, Ctxt) ->
 
329
    maybe_anno(Node, fun format_clause_1/2, Ctxt).
 
330
 
 
331
format_clause_1(#c_clause{pats=Ps,guard=G,body=B}, Ctxt) ->
284
332
    Ptxt = format_values(Ps, Ctxt),
285
 
    Ctxt2 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
333
    Ctxt2 = add_indent(Ctxt, Ctxt#ctxt.body_indent),
286
334
    [Ptxt,
287
335
     " when ",
288
 
     format_guard(G, ctxt_set_bump(Ctxt, expr, width(Ptxt, Ctxt) + 6)),
 
336
     format_guard(G, add_indent(set_class(Ctxt, expr),
 
337
                                 width(Ptxt, Ctxt) + 6)),
289
338
     " ->",
290
339
     nl_indent(Ctxt2)
291
 
     | format(B, ctxt_set_class(Ctxt2, expr))
 
340
     | format(B, set_class(Ctxt2, expr))
292
341
    ].
293
342
 
294
343
format_guard(Node, Ctxt) ->
295
 
    case core_lib:get_anno(Node) of
296
 
        [] -> format_guard_1(Node, Ctxt);
297
 
        List ->
298
 
            Ctxt1 = ctxt_bump_indent(Ctxt, 2),
299
 
            Ctxt2 = ctxt_bump_indent(Ctxt1, 3),
300
 
            ["( ",
301
 
             format_guard_1(Node, Ctxt1),
302
 
             nl_indent(Ctxt1),
303
 
             "-| ",format_1(core_lib:make_literal(List), Ctxt2)," )"
304
 
            ]
305
 
    end.
 
344
    maybe_anno(Node, fun format_guard_1/2, Ctxt).
306
345
 
307
346
format_guard_1(#c_call{module=M,name=N,args=As}, Ctxt0) ->
308
 
    Ctxt1 = ctxt_bump_indent(Ctxt0, 5),         %"call "
 
347
    Ctxt1 = add_indent(Ctxt0, 5),               %"call "
309
348
    Mod = format(M, Ctxt1),
310
 
    Ctxt2 = ctxt_bump_indent(Ctxt1, width(Mod, Ctxt1)+1),
 
349
    Ctxt2 = add_indent(Ctxt1, width(Mod, Ctxt1)+1),
311
350
    Name = format(N, Ctxt2),
312
 
    Ctxt3 = ctxt_bump_indent(Ctxt0, 4),
 
351
    Ctxt3 = add_indent(Ctxt0, 4),
313
352
    ["call ",Mod,":",Name,
314
353
     nl_indent(Ctxt3),
315
 
     $(,format_vseq(As, "",",", ctxt_bump_indent(Ctxt3, 1), fun format_guard/2),$)
 
354
     $(,format_vseq(As, "",",", add_indent(Ctxt3, 1), fun format_guard/2),$)
316
355
    ];
317
356
format_guard_1(E, Ctxt) -> format_1(E, Ctxt).   %Anno already done
318
357
 
323
362
    Fun(H, Ctxt);
324
363
format_hseq([H|T], Sep, Ctxt, Fun) ->
325
364
    Txt = [Fun(H, Ctxt)|Sep],
326
 
    Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt, Ctxt)),
 
365
    Ctxt1 = add_indent(Ctxt, width(Txt, Ctxt)),
327
366
    [Txt|format_hseq(T, Sep, Ctxt1, Fun)];
328
367
format_hseq([], _, _, _) -> "".
329
368
 
342
381
format_list_tail(#c_nil{anno=[]}, _) -> "]";
343
382
format_list_tail(#c_cons{anno=[],hd=H,tl=T}, Ctxt) ->
344
383
    Txt = [$,|format(H, Ctxt)],
345
 
    Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt, Ctxt)),
 
384
    Ctxt1 = add_indent(Ctxt, width(Txt, Ctxt)),
346
385
    [Txt|format_list_tail(T, Ctxt1)];
347
386
format_list_tail(Tail, Ctxt) ->
348
 
    ["|",format(Tail, ctxt_bump_indent(Ctxt, 1)),"]"].
 
387
    ["|",format(Tail, add_indent(Ctxt, 1)),"]"].
349
388
 
350
389
indent(Ctxt) -> indent(Ctxt#ctxt.indent, Ctxt).
351
390
 
398
437
    width(H, A, Ctxt, T);
399
438
width([], A, _, []) -> A.
400
439
 
401
 
ctxt_bump_indent(Ctxt, Dx) ->
 
440
add_indent(Ctxt, Dx) ->
402
441
    Ctxt#ctxt{indent = Ctxt#ctxt.indent + Dx}.
403
442
 
404
 
ctxt_set_class(Ctxt, Class) ->
 
443
set_class(Ctxt, Class) ->
405
444
    Ctxt#ctxt{class = Class}.
406
445
 
407
 
ctxt_set_bump(Ctxt, Class, Dx) ->
408
 
    Ctxt#ctxt{class=Class,indent=Ctxt#ctxt.indent + Dx}.
409
 
 
410
446
core_atom(A) -> io_lib:write_string(atom_to_list(A), $').
 
447
 
 
448
 
 
449
is_simple_term(#c_values{es=Es}) ->
 
450
    length(Es) < 3 andalso lists:all(fun is_simple_term/1, Es);
 
451
is_simple_term(#c_tuple{es=Es}) ->
 
452
    length(Es) < 4 andalso lists:all(fun is_simple_term/1, Es);
 
453
is_simple_term(#c_var{}) -> true;
 
454
is_simple_term(#c_string{}) -> false;
 
455
is_simple_term(Term) -> core_lib:is_atomic(Term).