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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/io_lib_format.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:
36
36
%%  and it also splits the handling of the control characters into two
37
37
%%  parts.
38
38
 
39
 
fwrite(Format, Args) when atom(Format) ->
 
39
fwrite(Format, Args) when is_atom(Format) ->
40
40
    fwrite(atom_to_list(Format), Args);
41
41
fwrite(Format, Args) ->
42
42
    Cs = collect(Format, Args),
74
74
precision(Fmt, Args) ->
75
75
    {none,Fmt,Args}.
76
76
 
77
 
field_value([$*|Fmt], [A|Args]) when integer(A) ->
 
77
field_value([$*|Fmt], [A|Args]) when is_integer(A) ->
78
78
    {A,Fmt,Args};
79
 
field_value([C|Fmt], Args) when C >= $0, C =< $9 ->
 
79
field_value([C|Fmt], Args) when is_integer(C), C >= $0, C =< $9 ->
80
80
    field_value([C|Fmt], Args, 0);
81
81
field_value(Fmt, Args) ->
82
82
    {none,Fmt,Args}.
83
83
 
84
 
field_value([C|Fmt], Args, F) when C >= $0, C =< $9 ->
 
84
field_value([C|Fmt], Args, F) when is_integer(C), C >= $0, C =< $9 ->
85
85
    field_value(Fmt, Args, 10*F + (C - $0));
86
86
field_value(Fmt, Args, F) ->            %Default case
87
87
    {F,Fmt,Args}.
110
110
collect_cc([$+|Fmt], [A|Args]) -> {$+,[A],Fmt,Args};
111
111
collect_cc([$#|Fmt], [A|Args]) -> {$#,[A],Fmt,Args};
112
112
collect_cc([$c|Fmt], [A|Args]) -> {$c,[A],Fmt,Args};
113
 
collect_cc([$~|Fmt], Args) -> {$~,[],Fmt,Args};
114
 
collect_cc([$n|Fmt], Args) -> {$n,[],Fmt,Args};
 
113
collect_cc([$~|Fmt], Args) when is_list(Args) -> {$~,[],Fmt,Args};
 
114
collect_cc([$n|Fmt], Args) when is_list(Args) -> {$n,[],Fmt,Args};
115
115
collect_cc([$i|Fmt], [A|Args]) -> {$i,[A],Fmt,Args}.
116
116
 
117
117
%% pcount([ControlC]) -> Count.
151
151
 
152
152
indentation([$\n|Cs], _I) -> indentation(Cs, 0);
153
153
indentation([$\t|Cs], I) -> indentation(Cs, ((I + 8) div 8) * 8);
154
 
indentation([C|Cs], I) when integer(C) ->
 
154
indentation([C|Cs], I) when is_integer(C) ->
155
155
    indentation(Cs, I+1);
156
156
indentation([C|Cs], I) ->
157
157
    indentation(Cs, indentation(C, I));
173
173
    print(A, Depth, F, Adj, P, Pad, I);
174
174
control($s, [A], F, Adj, P, Pad, _I) when atom(A) ->
175
175
    string(atom_to_list(A), F, Adj, P, Pad);
176
 
control($s, [L], F, Adj, P, Pad, _I) ->
177
 
    true = io_lib:deep_char_list(L),            %Check if L a character list
 
176
control($s, [L0], F, Adj, P, Pad, _I) ->
 
177
    L = iolist_to_chars(L0),
178
178
    string(L, F, Adj, P, Pad);
179
179
control($e, [A], F, Adj, P, Pad, _I) when float(A) ->
180
180
    fwrite_e(A, F, Adj, P, Pad);
213
213
%% Default integer base
214
214
base(none) ->
215
215
    10;
216
 
base(B) ->
 
216
base(B) when is_integer(B) ->
217
217
    B.
218
218
 
219
219
%% term(TermList, Field, Adjust, Precision, PadChar)
224
224
term(T, none, _Adj, none, _Pad) -> T;
225
225
term(T, none, Adj, P, Pad) -> term(T, P, Adj, P, Pad);
226
226
term(T, F, Adj, P0, Pad) ->
227
 
    L = lists:flat_length(T),
 
227
    L = lists:flatlength(T),
228
228
    P = case P0 of none -> min(L, F); _ -> P0 end,
229
229
    if
230
230
        L > P ->
270
270
    {[$.|Cs],C};
271
271
float_man([D|Ds], I, Dc) ->
272
272
    case float_man(Ds, I-1, Dc) of
273
 
        {Cs,true} when D == $9 -> {[$0|Cs],true};
 
273
        {Cs,true} when D =:= $9 -> {[$0|Cs],true};
274
274
        {Cs,true} -> {[D+1|Cs],false};
275
275
        {Cs,false} -> {[D|Cs],false}
276
276
    end;
281
281
float_man([_|_], 0) -> {[],false};
282
282
float_man([D|Ds], Dc) ->
283
283
    case float_man(Ds, Dc-1) of
284
 
        {Cs,true} when D == $9 -> {[$0|Cs],true};
 
284
        {Cs,true} when D =:= $9 -> {[$0|Cs],true};
285
285
        {Cs,true} -> {[D+1|Cs],false}; 
286
286
        {Cs,false} -> {[D|Cs],false}
287
287
    end;
330
330
 
331
331
%% fwrite_g(Float)
332
332
%% fwrite_g(Float, Field, Adjust, Precision, PadChar)
333
 
%%  Use the f form if Float is > 0.1 and < 10^4, else the e form.
 
333
%%  Use the f form if Float is >= 0.1 and < 1.0e4, 
 
334
%%  and the prints correctly in the f form, else the e form.
334
335
%%  Precision always means the # of significant digits.
335
336
 
336
337
fwrite_g(Fl) ->
338
339
 
339
340
fwrite_g(Fl, F, Adj, none, Pad) ->
340
341
    fwrite_g(Fl, F, Adj, 6, Pad);
341
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 0.1 ->
342
 
    fwrite_e(Fl, F, Adj, P, Pad);
343
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 1.0 ->
344
 
    fwrite_f(Fl, F, Adj, P, Pad);
345
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 10.0 ->
346
 
    fwrite_f(Fl, F, Adj, P-1, Pad);
347
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 100.0 ->
348
 
    fwrite_f(Fl, F, Adj, P-2, Pad);
349
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 1000.0 ->
350
 
    fwrite_f(Fl, F, Adj, P-3, Pad);
351
 
fwrite_g(Fl, F, Adj, P, Pad) when abs(Fl) < 10000.0 ->
352
 
    fwrite_f(Fl, F, Adj, P-4, Pad);
353
 
fwrite_g(Fl, F, Adj, P, Pad) ->
354
 
    fwrite_e(Fl, F, Adj, P, Pad).
 
342
fwrite_g(Fl, F, Adj, P, Pad) when P >= 1 ->
 
343
    A = abs(Fl),
 
344
    E = if A < 1.0e-1 -> -2;
 
345
           A < 1.0e0  -> -1;
 
346
           A < 1.0e1  -> 0;
 
347
           A < 1.0e2  -> 1;
 
348
           A < 1.0e3  -> 2;
 
349
           A < 1.0e4  -> 3;
 
350
           true       -> fwrite_f
 
351
        end,
 
352
    if  P =< 1, E =:= -1;
 
353
        P-1 > E, E >= -1 ->
 
354
            fwrite_f(Fl, F, Adj, P-1-E, Pad);
 
355
        P =< 1 ->
 
356
            fwrite_e(Fl, F, Adj, 2, Pad);
 
357
        true ->
 
358
            fwrite_e(Fl, F, Adj, P, Pad)
 
359
    end.
 
360
 
 
361
 
 
362
%% iolist_to_chars(iolist()) -> deep_char_list()
 
363
 
 
364
iolist_to_chars([C|Cs]) when is_integer(C), C >= $\000, C =< $\377 ->
 
365
    [C | iolist_to_chars(Cs)];
 
366
iolist_to_chars([I|Cs]) ->
 
367
    [iolist_to_chars(I) | iolist_to_chars(Cs)];
 
368
iolist_to_chars([]) ->
 
369
    [];
 
370
iolist_to_chars(B) when is_binary(B) ->
 
371
    binary_to_list(B).
355
372
 
356
373
%% string(String, Field, Adjust, Precision, PadChar)
357
374
 
358
375
string(S, none, _Adj, none, _Pad) -> S;
359
376
string(S, F, Adj, none, Pad) ->
360
 
    N = lists:flat_length(S),
 
377
    N = lists:flatlength(S),
361
378
    if N > F  -> flat_trunc(S, F);
362
379
       N == F -> S;
363
380
       true   -> adjust(S, chars(Pad, F-N), Adj)
364
381
    end;
365
382
string(S, none, _Adj, P, Pad) ->
366
 
    N = lists:flat_length(S),
 
383
    N = lists:flatlength(S),
367
384
    if N > P  -> flat_trunc(S, P);
368
385
       N == P -> S;
369
386
       true   -> [S|chars(Pad, P-N)]
371
388
string(S, F, Adj, F, Pad) ->
372
389
    string(S, none, Adj, F, Pad);
373
390
string(S, F, Adj, P, Pad) when F > P ->
374
 
    N = lists:flat_length(S),
 
391
    N = lists:flatlength(S),
375
392
    if N > F  -> flat_trunc(S, F);
376
393
       N == F -> S;
377
394
       N > P  -> adjust(flat_trunc(S, P), chars(Pad, F-P), Adj);
455
472
    [C,C];
456
473
chars(C, 3) ->
457
474
    [C,C,C];
458
 
chars(C, N) when integer(N), (N band 1) == 0 ->
 
475
chars(C, N) when is_integer(N), (N band 1) =:= 0 ->
459
476
    S = chars(C, N bsr 1),
460
477
    [S|S];
461
 
chars(C, N) when integer(N) ->
 
478
chars(C, N) when is_integer(N) ->
462
479
    S = chars(C, N bsr 1),
463
480
    [C,S|S].
464
481
 
472
489
cond_lowercase(String,false) ->
473
490
    String.
474
491
 
475
 
lowercase([H|T]) when integer(H), H >= $A, H =< $Z ->
 
492
lowercase([H|T]) when is_integer(H), H >= $A, H =< $Z ->
476
493
    [(H-$A+$a)|lowercase(T)];
477
494
lowercase([H|T]) ->
478
495
    [H|lowercase(T)];