~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/stdlib/src/io_lib_format.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
558
558
 
559
559
string(S, none, _Adj, none, _Pad) -> S;
560
560
string(S, F, Adj, none, Pad) ->
561
 
    N = lists:flatlength(S),
562
 
    if N > F  -> flat_trunc(S, F);
563
 
       N =:= F -> S;
564
 
       true   -> adjust(S, chars(Pad, F-N), Adj)
565
 
    end;
 
561
    string_field(S, F, Adj, lists:flatlength(S), Pad);
566
562
string(S, none, _Adj, P, Pad) ->
567
 
    N = lists:flatlength(S),
568
 
    if N > P  -> flat_trunc(S, P);
569
 
       N =:= P -> S;
570
 
       true   -> [S|chars(Pad, P-N)]
571
 
    end;
572
 
string(S, F, Adj, F, Pad) ->
573
 
    string(S, none, Adj, F, Pad);
574
 
string(S, F, Adj, P, Pad) when F > P ->
575
 
    N = lists:flatlength(S),
576
 
    if N > F  -> flat_trunc(S, F);
577
 
       N =:= F -> S;
578
 
       N > P   -> adjust(flat_trunc(S, P), chars(Pad, F-P), Adj);
579
 
       N =:= P -> adjust(S, chars(Pad, F-P), Adj);
580
 
       true    -> adjust([S|chars(Pad, P-N)], chars(Pad, F-P), Adj)
 
563
    string_field(S, P, left, lists:flatlength(S), Pad);
 
564
string(S, F, Adj, P, Pad) when F >= P ->
 
565
    N = lists:flatlength(S),
 
566
    if F > P ->
 
567
            if N > P ->
 
568
                    adjust(flat_trunc(S, P), chars(Pad, F-P), Adj);
 
569
               N < P ->
 
570
                    adjust([S|chars(Pad, P-N)], chars(Pad, F-P), Adj);
 
571
               true -> % N == P
 
572
                    adjust(S, chars(Pad, F-P), Adj)
 
573
            end;
 
574
       true -> % F == P
 
575
            string_field(S, F, Adj, N, Pad)
581
576
    end.
582
577
 
 
578
string_field(S, F, _Adj, N, _Pad) when N > F ->
 
579
    flat_trunc(S, F);
 
580
string_field(S, F, Adj, N, Pad) when N < F ->
 
581
    adjust(S, chars(Pad, F-N), Adj);
 
582
string_field(S, _, _, _, _) -> % N == F
 
583
    S.
 
584
 
583
585
%% unprefixed_integer(Int, Field, Adjust, Base, PadChar, Lowercase)
584
586
%% -> [Char].
585
587
 
624
626
%%
625
627
 
626
628
adjust(Data, [], _) -> Data;
627
 
adjust(Data, Pad, left) -> [Data,Pad];
628
 
adjust(Data, Pad, right) -> [Pad,Data].
 
629
adjust(Data, Pad, left) -> [Data|Pad];
 
630
adjust(Data, Pad, right) -> [Pad|Data].
629
631
 
630
632
%% Flatten and truncate a deep list to at most N elements.
631
633