~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
73
73
-export([module/2,format_error/1]).
74
74
 
75
75
-import(lists, [reverse/1,map/2,member/2,foldl/3,foldr/3,mapfoldl/3,
76
 
                splitwith/2,any/2,keysearch/3]).
 
76
                splitwith/2,keysearch/3]).
77
77
-import(ordsets, [add_element/2,del_element/2,is_element/2,
78
78
                  union/1,union/2,intersection/2,subtract/2]).
79
79
 
644
644
    EmptyBindings = erl_eval:new_bindings(),
645
645
    EvalFun = fun({integer,_,I}, B) -> {value,I,B};
646
646
                 ({char,_,C}, B) -> {value,C,B};
647
 
                 ({float,_,F}, B) -> {value,F,B}
 
647
                 ({float,_,F}, B) -> {value,F,B};
 
648
                 ({atom,_,undefined}, B) -> {value,undefined,B}
648
649
              end,
649
650
    case eval_bits:expr_grp(Es, EmptyBindings, EvalFun) of
650
651
        {value,Bin,EmptyBindings} ->
662
663
    end,
663
664
    {value,{unit,Unit}} = keysearch(unit, 1, Opts),
664
665
    case {SzTerm,Val} of
 
666
        {{atom,_,undefined},{char,_,_}} ->
 
667
            %% UTF-8/16/32.
 
668
            ok;
 
669
        {{atom,_,undefined},{integer,_,_}} ->
 
670
            %% UTF-8/16/32.
 
671
            ok;
665
672
        {{integer,_,Sz},_} when Sz*Unit =< 256 ->
666
673
            %% Don't be cheap - always accept fields up to this size.
667
674
            ok;
707
714
    case {Type,E1} of
708
715
        {_,#c_var{}} -> ok;
709
716
        {integer,#c_literal{val=I}} when is_integer(I) -> ok;
 
717
        {utf8,#c_literal{val=I}} when is_integer(I) -> ok;
 
718
        {utf16,#c_literal{val=I}} when is_integer(I) -> ok;
 
719
        {utf32,#c_literal{val=I}} when is_integer(I) -> ok;
710
720
        {float,#c_literal{val=V}} when is_number(V) -> ok;
711
721
        {binary,#c_literal{val=V}} when is_bitstring(V) -> ok;
712
 
        {_,_} -> throw(bad_binary)
 
722
        {_,_} ->
 
723
            throw(bad_binary)
713
724
    end,
714
725
    {#c_bitstr{val=E1,size=Size1,
715
726
               unit=core_lib:make_literal(Unit),
1161
1172
 
1162
1173
%% pat_bin([BinElement], State) -> [BinSeg].
1163
1174
 
1164
 
pat_bin(Ps, St) -> map(fun(P) -> pat_segment(P, St) end, Ps).
 
1175
pat_bin(Ps, St) -> [pat_segment(P, St) || P <- Ps].
1165
1176
 
1166
1177
pat_segment({bin_element,_,Term,Size,[Type,{unit,Unit}|Flags]}, St) ->
1167
1178
    #c_bitstr{val=pattern(Term, St),size=pattern(Size, St),
1208
1219
 
1209
1220
%% pattern_list([P], State) -> [P].
1210
1221
 
1211
 
pattern_list(Ps, St) -> map(fun(P) -> pattern(P, St) end, Ps).
 
1222
pattern_list(Ps, St) -> [pattern(P, St) || P <- Ps].
1212
1223
 
1213
1224
%% first([A]) -> [A].
1214
1225
%% last([A]) -> A.