~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(erl_pp).
115
115
 
116
116
lattribute(module, {M,Vs}, _Hook) ->
117
117
    attr("module",[{var,0,pname(M)},
118
 
                   foldr(fun(V, C) -> {cons,0,{var,0,V},C} 
 
118
                   foldr(fun(V, C) -> {cons,0,{var,0,V},C}
119
119
                         end, {nil,0}, Vs)]);
120
120
lattribute(module, M, _Hook) ->
121
121
    attr("module", [{var,0,pname(M)}]);
140
140
ltype({ann_type,_Line,[V,T]}) ->
141
141
    typed(lexpr(V, none), T);
142
142
ltype({paren_type,_Line,[T]}) ->
143
 
    [$(,ltype(T),$)];    
 
143
    [$(,ltype(T),$)];
144
144
ltype({type,_Line,union,Ts}) ->
145
145
    {seq,[],[],[' |'],ltypes(Ts)};
146
146
ltype({type,_Line,list,[T]}) ->
153
153
    simple_type({atom,Line,tuple}, []);
154
154
ltype({type,_Line,tuple,Ts}) ->
155
155
    tuple_type(Ts, fun ltype/1);
156
 
ltype({type,_Line,record,[N|Fs]}) ->
 
156
ltype({type,_Line,record,[{atom,_,N}|Fs]}) ->
157
157
    record_type(N, Fs);
158
158
ltype({type,_Line,range,[_I1,_I2]=Es}) ->
159
159
    expr_list(Es, '..', fun lexpr/2, none);
161
161
    binary_type(I1, I2); % except binary()
162
162
ltype({type,_Line,'fun',[]}) ->
163
163
    leaf("fun()");
164
 
ltype({type,_Line,'fun',_}=FunType) ->
 
164
ltype({type,_,'fun',[{type,_,any},_]}=FunType) ->
 
165
    [fun_type(['fun',$(], FunType),$)];
 
166
ltype({type,_Line,'fun',[{type,_,product,_},_]}=FunType) ->
165
167
    [fun_type(['fun',$(], FunType),$)];
166
168
ltype({type,Line,T,Ts}) ->
167
169
    simple_type({atom,Line,T}, Ts);
168
170
ltype({remote_type,Line,[M,F,Ts]}) ->
169
171
    simple_type({remote,Line,M,F}, Ts);
170
172
ltype({atom,_,T}) ->
171
 
    %% Follow the convention to always quote atoms (in types):
172
 
    leaf([$',atom_to_list(T),$']);
 
173
    leaf(write(T));
173
174
ltype(E) ->
174
175
    lexpr(E, 0, none).
175
176
 
176
 
binary_type({integer,_,Int1}=I1, {integer,_,Int2}=I2) ->
177
 
    E1 = [[leaf("_:"),lexpr(I1, 0, none)] || Int1 =/= 0],
178
 
    E2 = [[leaf("_:_*"),lexpr(I2, 0, none)] || Int2 =/= 0],
 
177
binary_type(I1, I2) ->
 
178
    B = [[] || {integer,_,0} <- [I1]] =:= [],
 
179
    U = [[] || {integer,_,0} <- [I2]] =:= [],
 
180
    P = max_prec(),
 
181
    E1 = [[leaf("_:"),lexpr(I1, P, none)] || B],
 
182
    E2 = [[leaf("_:_*"),lexpr(I2, P, none)] || U],
179
183
    {seq,'<<','>>',[$,],E1++E2}.
180
184
 
181
 
record_type({atom,_,Name}, Fields) ->
 
185
record_type(Name, Fields) ->
182
186
    {first,[record_name(Name)],field_types(Fields)}.
183
187
 
184
188
field_types(Fs) ->
442
446
    Ol = leaf(format("~s ", [Op])),
443
447
    El = [Ol,lexpr(Arg, R, Hook)],
444
448
    maybe_paren(P, Prec, El);
445
 
lexpr({op,_,Op,Larg,Rarg}, Prec, Hook)  when Op =:= 'orelse'; 
 
449
lexpr({op,_,Op,Larg,Rarg}, Prec, Hook)  when Op =:= 'orelse';
446
450
                                             Op =:= 'andalso' ->
447
451
    %% Breaks lines since R12B.
448
452
    {L,P,R} = inop_prec(Op),
726
730
%%%   and indentation are inserted between IPs.
727
731
%%% - {first,I,IP2}: IP2 follows after I, and is output with an indentation
728
732
%%%   updated with the width of I.
729
 
%%% - {seq,Before,After,Separator,IPs}: a sequence of Is separated by 
730
 
%%%   Separator. Before is output before IPs, and the indentation of IPs 
 
733
%%% - {seq,Before,After,Separator,IPs}: a sequence of Is separated by
 
734
%%%   Separator. Before is output before IPs, and the indentation of IPs
731
735
%%%   is updated with the width of Before. After follows after IPs.
732
736
%%% - {force_nl,ExtraInfo,I}: fun-info (a comment) forces linebreak before I.
733
737
%%% - {prefer_nl,Sep,IPs}: forces linebreak between Is unlesss negative
734
738
%%%   indentation.
735
739
%%% - {string,S}: a string.
736
740
%%% - {hook,...}, {ehook,...}: hook expressions.
737
 
%%% 
 
741
%%%
738
742
%%% list, first, seq, force_nl, and prefer_nl all accept IPs, where each
739
743
%%% element is either an item or a tuple {step|cstep,I1,I2}. step means
740
744
%%% that I2 is output after linebreak and an incremented indentation.
760
764
    {CharsL,SizeL} = unz(CharsSizeL),
761
765
    {BCharsL,BSizeL} = unz1([BCharsSize]),
762
766
    Sizes = BSizeL ++ SizeL,
763
 
    NSepChars = if 
 
767
    NSepChars = if
764
768
                    is_list(Sep), Sep =/= [] ->
765
769
                        erlang:max(0, length(CharsL)-1);
766
770
                    true ->
875
879
    [$\n|spaces(I, T)].
876
880
 
877
881
same_line(I0, SizeL, NSepChars) ->
878
 
    try 
 
882
    try
879
883
        Size = lists:sum(SizeL) + NSepChars,
880
884
        true = incr(I0, Size) =< ?MAXLINE,
881
885
        {yes,Size}
955
959
-define(N_SPACES, 30).
956
960
 
957
961
spacetab() ->
958
 
    {[_|L],_} = mapfoldl(fun(_, A) -> {A,[$\s|A]} 
 
962
    {[_|L],_} = mapfoldl(fun(_, A) -> {A,[$\s|A]}
959
963
                         end, [], lists:seq(0, ?N_SPACES)),
960
 
    list_to_tuple(L).    
 
964
    list_to_tuple(L).
961
965
 
962
966
spaces(N, T) when N =< ?N_SPACES ->
963
967
    element(N, T);
965
969
    [element(?N_SPACES, T)|spaces(N-?N_SPACES, T)].
966
970
 
967
971
wordtable() ->
968
 
    L = [begin {leaf,Sz,S} = leaf(W), {S,Sz} end || 
 
972
    L = [begin {leaf,Sz,S} = leaf(W), {S,Sz} end ||
969
973
            W <- [" ->"," =","<<",">>","[]","after","begin","case","catch",
970
974
                  "end","fun","if","of","receive","try","when"," ::","..",
971
975
                  " |"]],