~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/v3_kernel_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: v3_kernel_pp.erl,v 1.1 2008/12/17 09:53:43 mikpe Exp $
 
17
%%
 
18
%% Purpose : Kernel Erlang (naive) prettyprinter
 
19
 
 
20
-module(v3_kernel_pp).
 
21
 
 
22
-include("v3_kernel.hrl").
 
23
 
 
24
-export([format/1]).
 
25
 
 
26
%% These are "internal" structures in sys_kernel which are here for
 
27
%% debugging purposes.
 
28
-record(iset, {anno=[],vars,arg,body}).
 
29
-record(ifun, {anno=[],vars,body}).
 
30
 
 
31
%% ====================================================================== %%
 
32
%% format(Node) -> Text
 
33
%%      Node = coreErlang()
 
34
%%      Text = string() | [Text]
 
35
%%
 
36
%%      Prettyprint-formats (naively) an abstract Core Erlang syntax
 
37
%%      tree.
 
38
 
 
39
-record(ctxt, {indent = 0,
 
40
               item_indent = 2,
 
41
               body_indent = 2,
 
42
               tab_width = 8}).
 
43
 
 
44
canno(Cthing) -> element(2, Cthing).
 
45
 
 
46
format(Node) -> format(Node, #ctxt{}).
 
47
 
 
48
format(Node, Ctxt) ->
 
49
    case canno(Node) of
 
50
        [] ->
 
51
            format_1(Node, Ctxt);
 
52
        List ->
 
53
            format_anno(List, Ctxt, fun (Ctxt1) -> format_1(Node, Ctxt1) end)
 
54
    end.
 
55
 
 
56
format_anno(Anno, Ctxt, ObjFun) ->
 
57
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
58
    ["( ",
 
59
     ObjFun(Ctxt1),
 
60
     nl_indent(Ctxt1),
 
61
     "-| ",io_lib:write(Anno),
 
62
     " )"].
 
63
 
 
64
%% format_1(Kexpr, Context) -> string().
 
65
 
 
66
format_1(#k_atom{val=A}, _Ctxt) -> core_atom(A);
 
67
%%format_1(#k_char{val=C}, _Ctxt) -> io_lib:write_char(C);
 
68
format_1(#k_float{val=F}, _Ctxt) -> float_to_list(F);
 
69
format_1(#k_int{val=I}, _Ctxt) -> integer_to_list(I);
 
70
format_1(#k_nil{}, _Ctxt) -> "[]";
 
71
format_1(#k_string{val=S}, _Ctxt) -> io_lib:write_string(S);
 
72
format_1(#k_var{name=V}, _Ctxt) ->
 
73
    if atom(V) ->
 
74
            case atom_to_list(V) of
 
75
                [$_|Cs] -> "_X" ++ Cs;
 
76
                [C|Cs] when C >= $A, C =< $Z -> [C|Cs];
 
77
                Cs -> [$_|Cs]
 
78
            end;
 
79
       integer(V) -> [$_|integer_to_list(V)]
 
80
    end;
 
81
format_1(#k_cons{hd=H,tl=T}, Ctxt) ->
 
82
    Txt = ["["|format(H, ctxt_bump_indent(Ctxt, 1))],
 
83
    [Txt|format_list_tail(T, ctxt_bump_indent(Ctxt, width(Txt, Ctxt)))];
 
84
format_1(#k_tuple{es=Es}, Ctxt) ->
 
85
    [${,
 
86
     format_hseq(Es, ",", ctxt_bump_indent(Ctxt, 1), fun format/2),
 
87
     $}
 
88
    ];
 
89
format_1(#k_binary{segs=S}, Ctxt) ->
 
90
    ["#<",format(S, ctxt_bump_indent(Ctxt, 2)),">#"];
 
91
format_1(#k_bin_seg{}=S, Ctxt) ->
 
92
    [format_bin_seg_1(S, Ctxt),
 
93
     format_bin_seg(S#k_bin_seg.next, ctxt_bump_indent(Ctxt, 2))];
 
94
format_1(#k_bin_end{}, _Ctxt) -> "#<>#";
 
95
format_1(#k_local{name=N,arity=A}, Ctxt) ->
 
96
    "local " ++ format_fa_pair({N,A}, Ctxt);
 
97
format_1(#k_remote{mod=M,name=N,arity=A}, _Ctxt) ->
 
98
    %% This is for our internal translator.
 
99
    io_lib:format("remote ~s:~s/~w", [format(M),format(N),A]);
 
100
format_1(#k_internal{name=N,arity=A}, Ctxt) ->
 
101
    "internal " ++ format_fa_pair({N,A}, Ctxt);
 
102
format_1(#k_seq{arg=A,body=B}, Ctxt) ->
 
103
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
104
    ["do",
 
105
     nl_indent(Ctxt1),
 
106
     format(A, Ctxt1),
 
107
     nl_indent(Ctxt),
 
108
     "then",
 
109
     nl_indent(Ctxt)
 
110
     | format(B, Ctxt)
 
111
    ];
 
112
format_1(#k_match{vars=Vs,body=Bs,ret=Rs}, Ctxt) ->
 
113
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent),
 
114
    ["match ",
 
115
     format_hseq(Vs, ",", ctxt_bump_indent(Ctxt, 6), fun format/2),
 
116
     nl_indent(Ctxt1),
 
117
     format(Bs, Ctxt1),
 
118
     nl_indent(Ctxt),
 
119
     "end",
 
120
     format_ret(Rs, Ctxt1)
 
121
    ];
 
122
format_1(#k_alt{first=O,then=T}, Ctxt) ->
 
123
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent),
 
124
    ["alt",
 
125
     nl_indent(Ctxt1),
 
126
     format(O, Ctxt1),
 
127
     nl_indent(Ctxt1),
 
128
     format(T, Ctxt1)];
 
129
format_1(#k_select{var=V,types=Cs}, Ctxt) ->
 
130
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
131
    ["select ",
 
132
     format(V, Ctxt),
 
133
     nl_indent(Ctxt1),
 
134
     format_vseq(Cs, "", "", Ctxt1, fun format/2)
 
135
    ];
 
136
format_1(#k_type_clause{type=T,values=Cs}, Ctxt) ->
 
137
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
138
    ["type ",
 
139
     io_lib:write(T),
 
140
     nl_indent(Ctxt1),
 
141
     format_vseq(Cs, "", "", Ctxt1, fun format/2)
 
142
    ];
 
143
format_1(#k_val_clause{val=Val,body=B}, Ctxt) ->
 
144
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
145
    [format(Val, Ctxt),
 
146
     " ->",
 
147
     nl_indent(Ctxt1)
 
148
     | format(B, Ctxt1)
 
149
    ];
 
150
format_1(#k_guard{clauses=Gs}, Ctxt) ->
 
151
    Ctxt1 = ctxt_bump_indent(Ctxt, 5),
 
152
    ["when ",
 
153
     nl_indent(Ctxt1),
 
154
     format_vseq(Gs, "", "", Ctxt1, fun format/2)];
 
155
format_1(#k_guard_clause{guard=G,body=B}, Ctxt) ->
 
156
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
157
    [format(G, Ctxt),
 
158
     nl_indent(Ctxt),
 
159
     "->",
 
160
     nl_indent(Ctxt1)
 
161
     | format(B, Ctxt1)
 
162
    ];
 
163
format_1(#k_call{op=Op,args=As,ret=Rs}, Ctxt) ->
 
164
    Txt = ["call (",format(Op, ctxt_bump_indent(Ctxt, 6)),$)],
 
165
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
166
    [Txt,format_args(As, Ctxt1),
 
167
     format_ret(Rs, Ctxt1)
 
168
    ];
 
169
format_1(#k_enter{op=Op,args=As}, Ctxt) ->
 
170
    Txt = ["enter (",format(Op, ctxt_bump_indent(Ctxt, 7)),$)],
 
171
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
172
    [Txt,format_args(As, Ctxt1)];
 
173
format_1(#k_bif{op=Op,args=As,ret=Rs}, Ctxt) ->
 
174
    Txt = ["bif (",format(Op, ctxt_bump_indent(Ctxt, 5)),$)],
 
175
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
176
    [Txt,format_args(As, Ctxt1),
 
177
     format_ret(Rs, Ctxt1)
 
178
    ];
 
179
format_1(#k_test{op=Op,args=As}, Ctxt) ->
 
180
    Txt = ["test (",format(Op, ctxt_bump_indent(Ctxt, 6)),$)],
 
181
    Ctxt1 = ctxt_bump_indent(Ctxt, 2),
 
182
    [Txt,format_args(As, Ctxt1)];
 
183
format_1(#k_put{arg=A,ret=Rs}, Ctxt) ->
 
184
    [format(A, Ctxt),
 
185
     format_ret(Rs, ctxt_bump_indent(Ctxt, 1))
 
186
    ];
 
187
format_1(#k_try{arg=A,vars=Vs,body=B,evars=Evs,handler=H,ret=Rs}, Ctxt) ->
 
188
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
189
    ["try",
 
190
     nl_indent(Ctxt1),
 
191
     format(A, Ctxt1),
 
192
     nl_indent(Ctxt),
 
193
     "of ",
 
194
     format_hseq(Vs, ", ", ctxt_bump_indent(Ctxt, 3), fun format/2),
 
195
     nl_indent(Ctxt1),
 
196
     format(B, Ctxt1),
 
197
     nl_indent(Ctxt),
 
198
     "catch ",
 
199
     format_hseq(Evs, ", ", ctxt_bump_indent(Ctxt, 6), fun format/2),
 
200
     nl_indent(Ctxt1),
 
201
     format(H, Ctxt1),
 
202
     nl_indent(Ctxt),
 
203
     "end",
 
204
     format_ret(Rs, Ctxt1)
 
205
    ];
 
206
format_1(#k_catch{body=B,ret=Rs}, Ctxt) ->
 
207
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
208
    ["catch",
 
209
     nl_indent(Ctxt1),
 
210
     format(B, Ctxt1),
 
211
     nl_indent(Ctxt),
 
212
     "end",
 
213
     format_ret(Rs, Ctxt1)
 
214
    ];
 
215
format_1(#k_receive{var=V,body=B,timeout=T,action=A,ret=Rs}, Ctxt) ->
 
216
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.item_indent),
 
217
    ["receive ",
 
218
     format(V, Ctxt),
 
219
     nl_indent(Ctxt1),
 
220
     format(B, Ctxt1),
 
221
     nl_indent(Ctxt),
 
222
     "after ",
 
223
     format(T, ctxt_bump_indent(Ctxt, 6)),
 
224
     " ->",
 
225
     nl_indent(Ctxt1),
 
226
     format(A, Ctxt1),
 
227
     nl_indent(Ctxt),
 
228
     "end",
 
229
     format_ret(Rs, Ctxt1)
 
230
    ];
 
231
format_1(#k_receive_accept{}, _Ctxt) -> "receive_accept";
 
232
format_1(#k_receive_next{}, _Ctxt) -> "receive_next";
 
233
format_1(#k_break{args=As}, Ctxt) ->
 
234
    ["<",
 
235
     format_hseq(As, ",", ctxt_bump_indent(Ctxt, 1), fun format/2),
 
236
     ">"
 
237
    ];
 
238
format_1(#k_return{args=As}, Ctxt) ->
 
239
    ["<<",
 
240
     format_hseq(As, ",", ctxt_bump_indent(Ctxt, 1), fun format/2),
 
241
     ">>"
 
242
    ];
 
243
format_1(#k_fdef{func=F,arity=A,vars=Vs,body=B}, Ctxt) ->
 
244
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
245
    ["fdef ",
 
246
     format_fa_pair({F,A}, ctxt_bump_indent(Ctxt, 5)),
 
247
     format_args(Vs, ctxt_bump_indent(Ctxt, 14)),
 
248
     " =",
 
249
     nl_indent(Ctxt1),
 
250
     format(B, Ctxt1)
 
251
    ];
 
252
format_1(#k_mdef{name=N,exports=Es,attributes=As,body=B}, Ctxt) ->
 
253
    ["module ",
 
254
     format(#k_atom{val=N}, ctxt_bump_indent(Ctxt, 7)),
 
255
     nl_indent(Ctxt),
 
256
     "export [",
 
257
     format_vseq(Es,
 
258
                 "", ",",
 
259
                 ctxt_bump_indent(Ctxt, 8),
 
260
                 fun format_fa_pair/2),
 
261
     "]",
 
262
     nl_indent(Ctxt),
 
263
     "attributes [",
 
264
     format_vseq(As,
 
265
                 "", ",",
 
266
                 ctxt_bump_indent(Ctxt, 12),
 
267
                 fun format_attribute/2),
 
268
     "]",
 
269
     nl_indent(Ctxt),
 
270
     format_vseq(B,
 
271
                 "", "",
 
272
                 Ctxt,
 
273
                 fun format/2),
 
274
     nl_indent(Ctxt)
 
275
     | "end"
 
276
    ];
 
277
%% Internal sys_kernel structures.
 
278
format_1(#iset{vars=Vs,arg=A,body=B}, Ctxt) ->
 
279
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
280
    ["set <",
 
281
     format_hseq(Vs, ", ", ctxt_bump_indent(Ctxt, 5), fun format/2),
 
282
     "> =",
 
283
     nl_indent(Ctxt1),
 
284
     format(A, Ctxt1),
 
285
     nl_indent(Ctxt),
 
286
     "in  "
 
287
     | format(B, ctxt_bump_indent(Ctxt, 2))
 
288
    ];
 
289
format_1(#ifun{vars=Vs,body=B}, Ctxt) ->
 
290
    Ctxt1 = ctxt_bump_indent(Ctxt, Ctxt#ctxt.body_indent),
 
291
    ["fun ",
 
292
     format_args(Vs, ctxt_bump_indent(Ctxt, 4)),
 
293
     " ->",
 
294
     nl_indent(Ctxt1)
 
295
     | format(B, Ctxt1)
 
296
    ];
 
297
format_1(Type, _Ctxt) ->
 
298
    ["** Unsupported type: ",
 
299
     io_lib:write(Type)
 
300
     | " **"
 
301
    ].
 
302
 
 
303
%% format_ret([RetVar], Context) -> Txt.
 
304
%%  Format the return vars of kexpr.
 
305
 
 
306
format_ret(Rs, Ctxt) ->
 
307
    [" >> ",
 
308
     "<",
 
309
     format_hseq(Rs, ",", ctxt_bump_indent(Ctxt, 5), fun format/2),
 
310
     ">"].
 
311
 
 
312
%% format_args([Arg], Context) -> Txt.
 
313
%%  Format arguments.
 
314
 
 
315
format_args(As, Ctxt) ->
 
316
  [$(,format_hseq(As, ", ", ctxt_bump_indent(Ctxt, 1), fun format/2),$)].
 
317
 
 
318
%% format_hseq([Thing], Separator, Context, Fun) -> Txt.
 
319
%%  Format a sequence horizontally.
 
320
 
 
321
format_hseq([H], _Sep, Ctxt, Fun) ->
 
322
    Fun(H, Ctxt);
 
323
format_hseq([H|T], Sep, Ctxt, Fun) ->
 
324
    Txt = [Fun(H, Ctxt)|Sep],
 
325
    Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt, Ctxt)),
 
326
    [Txt|format_hseq(T, Sep, Ctxt1, Fun)];
 
327
format_hseq([], _, _, _) -> "".
 
328
 
 
329
%% format_vseq([Thing], LinePrefix, LineSuffix, Context, Fun) -> Txt.
 
330
%%  Format a sequence vertically.
 
331
 
 
332
format_vseq([H], _Pre, _Suf, Ctxt, Fun) ->
 
333
    Fun(H, Ctxt);
 
334
format_vseq([H|T], Pre, Suf, Ctxt, Fun) ->
 
335
    [Fun(H, Ctxt),Suf,nl_indent(Ctxt),Pre|
 
336
     format_vseq(T, Pre, Suf, Ctxt, Fun)];
 
337
format_vseq([], _, _, _, _) -> "".
 
338
 
 
339
format_fa_pair({F,A}, _Ctxt) -> [core_atom(F),$/,integer_to_list(A)].
 
340
 
 
341
%% format_attribute({Name,Val}, Context) -> Txt.
 
342
 
 
343
format_attribute({Name,Val}, Ctxt) when list(Val) ->
 
344
    Txt = format(#k_atom{val=Name}, Ctxt),
 
345
    Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt,Ctxt)+4),
 
346
    [Txt," = ",
 
347
     $[,format_vseq(Val, "", ",", Ctxt1,
 
348
                    fun (A, _C) -> io_lib:write(A) end),$]
 
349
    ];
 
350
format_attribute({Name,Val}, Ctxt) ->
 
351
    Txt = format(#k_atom{val=Name}, Ctxt),
 
352
    [Txt," = ",io_lib:write(Val)].
 
353
 
 
354
format_list_tail(#k_nil{anno=[]}, _Ctxt) -> "]";
 
355
format_list_tail(#k_cons{anno=[],hd=H,tl=T}, Ctxt) ->
 
356
    Txt = [$,|format(H, Ctxt)],
 
357
    Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt, Ctxt)),
 
358
    [Txt|format_list_tail(T, Ctxt1)];
 
359
format_list_tail(Tail, Ctxt) ->
 
360
    ["|",format(Tail, ctxt_bump_indent(Ctxt, 1)), "]"].
 
361
 
 
362
format_bin_seg(#k_bin_end{anno=[]}, _Ctxt) -> "";
 
363
format_bin_seg(#k_bin_seg{anno=[],next=N}=Seg, Ctxt) ->
 
364
    Txt = [$,|format_bin_seg_1(Seg, Ctxt)],
 
365
    [Txt|format_bin_seg(N, ctxt_bump_indent(Ctxt, width(Txt, Ctxt)))];
 
366
format_bin_seg(Seg, Ctxt) ->
 
367
    ["|",format(Seg, ctxt_bump_indent(Ctxt, 2))].
 
368
 
 
369
format_bin_seg_1(#k_bin_seg{size=S,unit=U,type=T,flags=Fs,seg=Seg}, Ctxt) ->
 
370
    [format(Seg, Ctxt),
 
371
     ":",format(S, Ctxt),"*",io_lib:write(U),
 
372
     ":",io_lib:write(T),
 
373
     lists:map(fun (F) -> [$-,io_lib:write(F)] end, Fs)
 
374
    ].
 
375
 
 
376
% format_bin_elements(#k_binary_cons{hd=H,tl=T,size=S,info=I}, Ctxt) ->
 
377
%     A = canno(T),
 
378
%     Fe = fun (Eh, Es, Ei, Ct) ->
 
379
%                [format(Eh, Ct),":",format(Es, Ct),"/",io_lib:write(Ei)]
 
380
%        end,
 
381
%     case T of
 
382
%       #k_zero_binary{} when A == [] ->
 
383
%           Fe(H, S, I, Ctxt);
 
384
%       #k_binary_cons{} when A == [] ->
 
385
%           Txt = [Fe(H, S, I, Ctxt)|","],
 
386
%           Ctxt1 = ctxt_bump_indent(Ctxt, width(Txt, Ctxt)),
 
387
%           [Txt|format_bin_elements(T, Ctxt1)];
 
388
%       _ ->
 
389
%           Txt = [Fe(H, S, I, Ctxt)|"|"],
 
390
%           [Txt|format(T, ctxt_bump_indent(Ctxt, width(Txt, Ctxt)))]
 
391
%     end.
 
392
 
 
393
indent(Ctxt) -> indent(Ctxt#ctxt.indent, Ctxt).
 
394
 
 
395
indent(N, _Ctxt) when N =< 0 -> "";
 
396
indent(N, Ctxt) ->
 
397
    T = Ctxt#ctxt.tab_width,
 
398
    string:chars($\t, N div T, string:chars($\s, N rem T)).
 
399
 
 
400
nl_indent(Ctxt) -> [$\n|indent(Ctxt)].
 
401
 
 
402
 
 
403
unindent(T, Ctxt) ->
 
404
    unindent(T, Ctxt#ctxt.indent, Ctxt, []).
 
405
 
 
406
unindent(T, N, _Ctxt, C) when N =< 0 ->
 
407
    [T|C];
 
408
unindent([$\s|T], N, Ctxt, C) ->
 
409
    unindent(T, N - 1, Ctxt, C);
 
410
unindent([$\t|T], N, Ctxt, C) ->
 
411
    Tab = Ctxt#ctxt.tab_width,
 
412
    if N >= Tab ->
 
413
            unindent(T, N - Tab, Ctxt, C);
 
414
       true ->
 
415
            unindent([string:chars($\s, Tab - N)|T], 0, Ctxt, C)
 
416
    end;
 
417
unindent([L|T], N, Ctxt, C) when list(L) ->
 
418
    unindent(L, N, Ctxt, [T|C]);
 
419
unindent([H|T], _N, _Ctxt, C) ->
 
420
    [H|[T|C]];
 
421
unindent([], N, Ctxt, [H|T]) ->
 
422
    unindent(H, N, Ctxt, T);
 
423
unindent([], _, _, []) -> [].
 
424
 
 
425
 
 
426
width(Txt, Ctxt) ->
 
427
    width(Txt, 0, Ctxt, []).
 
428
 
 
429
width([$\t|T], A, Ctxt, C) ->
 
430
    width(T, A + Ctxt#ctxt.tab_width, Ctxt, C);
 
431
width([$\n|T], _A, Ctxt, C) ->
 
432
    width(unindent([T|C], Ctxt), Ctxt);
 
433
width([H|T], A, Ctxt, C) when list(H) ->
 
434
    width(H, A, Ctxt, [T|C]);
 
435
width([_|T], A, Ctxt, C) ->
 
436
    width(T, A + 1, Ctxt, C);
 
437
width([], A, Ctxt, [H|T]) ->
 
438
    width(H, A, Ctxt, T);
 
439
width([], A, _, []) -> A.
 
440
 
 
441
ctxt_bump_indent(Ctxt, Dx) ->
 
442
    Ctxt#ctxt{indent=Ctxt#ctxt.indent + Dx}.
 
443
 
 
444
core_atom(A) -> io_lib:write_string(atom_to_list(A), $').