diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/epp.erl | 16 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_eval.erl | 8 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_expand_records.erl | 26 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 21 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_tar.erl | 38 | ||||
| -rw-r--r-- | lib/stdlib/src/filelib.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/maps.erl | 18 | 
8 files changed, 97 insertions, 37 deletions
| diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 9b506b0a44..5f8637c118 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1121,8 +1121,20 @@ skip_toks(From, St, [I|Sis]) ->  	    skip_toks(From, St#epp{location=Cl}, Sis);  	{ok,_Toks,Cl} ->  	    skip_toks(From, St#epp{location=Cl}, [I|Sis]); -	{error,_E,Cl} -> -	    skip_toks(From, St#epp{location=Cl}, [I|Sis]); +	{error,E,Cl} -> +	    case E of +		{_,file_io_server,invalid_unicode} -> +		    %% The compiler needs to know that there was +		    %% invalid unicode characters in the file +		    %% (and there is no point in continuing anyway +		    %% since io server process has terminated). +		    epp_reply(From, {error,E}), +		    leave_file(wait_request(St), St); +		_ -> +		    %% Some other invalid token, such as a bad floating +		    %% point number. Just ignore it. +		    skip_toks(From, St#epp{location=Cl}, [I|Sis]) +	    end;  	{eof,Cl} ->  	    leave_file(From, St#epp{location=Cl,istk=[I|Sis]});  	{error,_E} -> diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index acde3ad5d6..3cfedfee97 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -244,17 +244,17 @@ expr({record,_,_,Name,_}, _Bs, _Lf, _Ef, _RBs) ->      erlang:raise(error, {undef_record,Name}, stacktrace());  %% map -expr({map,_, Binding,Es}, Bs0, Lf, Ef, RBs) -> -    {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, RBs), +expr({map,_,Binding,Es}, Bs0, Lf, Ef, RBs) -> +    {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, none),      case Map0 of          #{} -> -            {Vs,Bs} = eval_map_fields(Es, Bs1, Lf, Ef), +            {Vs,Bs2} = eval_map_fields(Es, Bs0, Lf, Ef),              Map1 = lists:foldl(fun ({map_assoc,K,V}, Mi) ->                                         maps:put(K, V, Mi);                                     ({map_exact,K,V}, Mi) ->                                         maps:update(K, V, Mi)                                 end, Map0, Vs), -            ret_expr(Map1, Bs, RBs); +            ret_expr(Map1, merge_bindings(Bs2, Bs1), RBs);          _ ->              erlang:raise(error, {badarg,Map0}, stacktrace())      end; diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 57e768ba9d..c74f68647f 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2005-2012. All Rights Reserved. +%% Copyright Ericsson AB 2005-2014. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -38,6 +38,8 @@                   checked_ra=[]        % successfully accessed records                  }). +-define(REC_OFFSET, 100000000). % A hundred millions. Also in v3_core. +  -spec(module(AbsForms, CompileOptions) -> AbsForms when        AbsForms :: [erl_parse:abstract_form()],        CompileOptions :: [compile:option()]). @@ -144,10 +146,11 @@ pattern({map_field_exact,Line,K0,V0}, St0) ->  %%    {{struct,Line,Tag,TPs},TPsvs,St1};  pattern({record_index,Line,Name,Field}, St) ->      {index_expr(Line, Field, Name, record_fields(Name, St)),St}; -pattern({record,Line,Name,Pfs}, St0) -> +pattern({record,Line0,Name,Pfs}, St0) ->      Fs = record_fields(Name, St0),      {TMs,St1} = pattern_list(pattern_fields(Fs, Pfs), St0), -    {{tuple,Line,[{atom,Line,Name} | TMs]},St1}; +    Line = record_offset(Line0, St1), +    {{tuple,Line,[{atom,Line0,Name} | TMs]},St1};  pattern({bin,Line,Es0}, St0) ->      {Es1,St1} = pattern_bin(Es0, St0),      {{bin,Line,Es1},St1}; @@ -329,8 +332,9 @@ expr({map_field_exact,Line,K0,V0}, St0) ->  expr({record_index,Line,Name,F}, St) ->      I = index_expr(Line, F, Name, record_fields(Name, St)),      expr(I, St); -expr({record,Line,Name,Is}, St) -> -    expr({tuple,Line,[{atom,Line,Name} |  +expr({record,Line0,Name,Is}, St) -> +    Line = record_offset(Line0, St), +    expr({tuple,Line,[{atom,Line0,Name} |                        record_inits(record_fields(Name, St), Is)]},           St);  expr({record_field,Line,R,Name,F}, St) -> @@ -582,8 +586,9 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->              I = index_expr(F, Fs, 2),              P = record_pattern(2, I, Var, length(Fs)+1, Line, [{atom,Line,Name}]),              NLine = neg_line(Line), +            RLine = record_offset(NLine, St),  	    E = {'case',NLine,R, -		     [{clause,NLine,[{tuple,NLine,P}],[],[Var]}, +		     [{clause,NLine,[{tuple,RLine,P}],[],[Var]},  		      {clause,NLine,[{var,NLine,'_'}],[],  		       [{call,NLine,{remote,NLine,  				    {atom,NLine,erlang}, @@ -836,7 +841,7 @@ optimize_is_record(H0, G0, #exprec{compile=Opts}) ->  	[] ->  	    {H0,G0};  	Rs0 -> -	    case lists:member(no_is_record_optimization, Opts) of +	    case lists:member(dialyzer, Opts) of % no_is_record_optimization  		true ->  		    {H0,G0};  		false -> @@ -961,3 +966,10 @@ opt_remove_2(A, _) -> A.  neg_line(L) ->      erl_parse:set_line(L, fun(Line) -> -abs(Line) end). + +record_offset(L, St) -> +    case lists:member(dialyzer, St#exprec.compile) of +        true when L >= 0 -> L+?REC_OFFSET; +        true when L < 0  -> L-?REC_OFFSET; +        false -> L +    end. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 7c064ce902..39cc03cf7a 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -1046,9 +1046,10 @@ check_undefined_types(#lint{usage=Usage,types=Def}=St0) ->      Used = Usage#usage.used_types,      UTAs = dict:fetch_keys(Used),      Undef = [{TA,dict:fetch(TA, Used)} || -		TA <- UTAs, +		{T,_}=TA <- UTAs,  		not dict:is_key(TA, Def), -		not is_default_type(TA)], +		not is_default_type(TA), +                not is_newly_introduced_var_arity_type(T)],      foldl(fun ({TA,L}, St) ->  		  add_error(L, {undefined_type,TA}, St)  	  end, St0, Undef). diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 1dc5fc52a7..e1ae3b7aea 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -848,10 +848,12 @@ build_fun(Line, Cs) ->      end.  check_clauses(Cs, Name, Arity) -> -     mapl(fun ({clause,L,N,As,G,B}) when N =:= Name, length(As) =:= Arity -> -		 {clause,L,As,G,B}; -	     ({clause,L,_N,_As,_G,_B}) -> -		 ret_err(L, "head mismatch") end, Cs). +    [case C of +         {clause,L,N,As,G,B} when N =:= Name, length(As) =:= Arity -> +             {clause,L,As,G,B}; +         {clause,L,_N,_As,_G,_B} -> +             ret_err(L, "head mismatch") +     end || C <- Cs].  build_try(L,Es,Scs,{Ccs,As}) ->      {'try',L,Es,Scs,Ccs,As}. @@ -861,17 +863,6 @@ ret_err(L, S) ->      {location,Location} = get_attribute(L, location),      return_error(Location, S). -%% mapl(F,List) -%% an alternative map which always maps from left to right -%% and makes it possible to interrupt the mapping with throw on -%% the first occurence from left as expected. -%% can be removed when the jam machine (and all other machines) -%% uses the standardized (Erlang 5.0) evaluation order (from left to right) -mapl(F, [H|T]) -> -	V = F(H), -	[V | mapl(F,T)]; -mapl(_, []) -> -	[].  %%  Convert between the abstract form of a term and a term. diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index 40b48d7999..acf7a5cd40 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -381,7 +381,12 @@ to_octal(Int, Count, Result) ->      to_octal(Int div 8, Count-1, [Int rem 8 + $0|Result]).  to_string(Str0, Count) -> -    Str = list_to_binary(Str0), +    Str = case file:native_name_encoding() of +	      utf8 -> +		  unicode:characters_to_binary(Str0); +	      latin1 -> +		  list_to_binary(Str0) +	  end,      case byte_size(Str) of  	Size when Size < Count ->  	    [Str|zeroes(Count-Size)]; @@ -392,9 +397,17 @@ to_string(Str0, Count) ->  pad_file(File) ->      {ok,Position} = file:position(File, {cur,0}), -    %% There must be at least one empty record at the end of the file. -    Zeros = zeroes(?block_size - (Position rem ?block_size)), -    file:write(File, Zeros). +    %% There must be at least two zero records at the end. +    Fill = case ?block_size - (Position rem ?block_size) of +	       Fill0 when Fill0 < 2*?record_size -> +		   %% We need to another block here to ensure that there +		   %% are at least two zero records at the end. +		   Fill0 + ?block_size; +	       Fill0 -> +		   %% Large enough. +		   Fill0 +	   end, +    file:write(File, zeroes(Fill)).  split_filename(Name) when length(Name) =< ?th_name_len ->      {"", Name}; @@ -608,7 +621,22 @@ typeflag(Bin) ->  %% Get the name of the file from the prefix and name fields of the  %% tar header. -get_name(Bin) -> +get_name(Bin0) -> +    List0 = get_name_raw(Bin0), +    case file:native_name_encoding() of +	utf8 -> +	    Bin = list_to_binary(List0), +	    case unicode:characters_to_list(Bin) of +		{error,_,_} -> +		    List0; +		List when is_list(List) -> +		    List +	    end; +	latin1 -> +	    List0 +    end. + +get_name_raw(Bin) ->      Name = from_string(Bin, ?th_name, ?th_name_len),      case binary_to_list(Bin, ?th_prefix+1, ?th_prefix+1) of  	[0] -> diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index a266daa084..c0921e4cf1 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -488,7 +488,7 @@ badpattern(Reason) ->      error({badpattern,Reason}).  eval_read_file_info(File, file) -> -    file:read_file_info(File); +    file:read_link_info(File);  eval_read_file_info(File, erl_prim_loader) ->      case erl_prim_loader:read_file_info(File) of  	error -> {error, erl_prim_loader}; diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl index fd6d56fa47..4ef1638e6d 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -23,7 +23,8 @@  	fold/3,  	map/2,  	size/1, -	without/2 +    without/2, +    get/3      ]). @@ -142,6 +143,21 @@ values(_) -> erlang:nif_error(undef).  %%% End of BIFs +-spec get(Key, Map, Default) -> Value | Default when +        Key :: term(), +        Map :: map(), +        Value :: term(), +        Default :: term(). + +get(Key, Map, Default) -> +    case maps:find(Key, Map) of +        {ok, Value} -> +            Value; +        error -> +            Default +    end. + +  -spec fold(Fun,Init,Map) -> Acc when      Fun :: fun((K, V, AccIn) -> AccOut),      Init :: term(), | 
