diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/beam_lib.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/binary.erl | 77 | ||||
| -rw-r--r-- | lib/stdlib/src/epp.erl | 329 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_anno.erl | 96 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 26 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 49 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_scan.erl | 267 | ||||
| -rw-r--r-- | lib/stdlib/src/escript.erl | 8 | ||||
| -rw-r--r-- | lib/stdlib/src/io.erl | 43 | ||||
| -rw-r--r-- | lib/stdlib/src/otp_internal.erl | 55 | ||||
| -rw-r--r-- | lib/stdlib/src/slave.erl | 23 | ||||
| -rw-r--r-- | lib/stdlib/src/supervisor.erl | 74 | 
12 files changed, 293 insertions, 756 deletions
| diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index cbbab088f4..6e00401dce 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -872,7 +872,7 @@ mandatory_chunks() ->  %%% can use it.  %%% ==================================================================== --record(state, {crypto_key_f :: crypto_fun()}). +-record(state, {crypto_key_f :: crypto_fun() | 'undefined'}).  -define(CRYPTO_KEY_SERVER, beam_lib__crypto_key_server). diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl index af00410572..fb0c395d70 100644 --- a/lib/stdlib/src/binary.erl +++ b/lib/stdlib/src/binary.erl @@ -20,7 +20,7 @@  -module(binary).  %%  %% Implemented in this module: --export([split/2,split/3,replace/3,replace/4]). +-export([replace/3,replace/4]).  -export_type([cp/0]). @@ -34,7 +34,8 @@           decode_unsigned/2, encode_unsigned/1, encode_unsigned/2,           first/1, last/1, list_to_bin/1, longest_common_prefix/1,           longest_common_suffix/1, match/2, match/3, matches/2, -         matches/3, part/2, part/3, referenced_byte_size/1]). +         matches/3, part/2, part/3, referenced_byte_size/1, +         split/2, split/3]).  -spec at(Subject, Pos) -> byte() when        Subject :: binary(), @@ -198,19 +199,13 @@ part(_, _, _) ->  referenced_byte_size(_) ->      erlang:nif_error(undef). -%%% End of BIFs. - -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% split -%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -  -spec split(Subject, Pattern) -> Parts when        Subject :: binary(),        Pattern :: binary() | [binary()] | cp(),        Parts :: [binary()]. -split(H,N) -> -    split(H,N,[]). +split(_, _) -> +    erlang:nif_error(undef).  -spec split(Subject, Pattern, Options) -> Parts when        Subject :: binary(), @@ -219,53 +214,10 @@ split(H,N) ->        Option :: {scope, part()} | trim | global | trim_all,        Parts :: [binary()]. -split(Haystack,Needles,Options) -> -    try -	{Part,Global,Trim,TrimAll} = -        get_opts_split(Options,{no,false,false,false}), -	Moptlist = case Part of -		       no -> -			   []; -		       {A,B} -> -			   [{scope,{A,B}}] -		   end, -	MList = if -		    Global -> -			binary:matches(Haystack,Needles,Moptlist); -		    true -> -			case binary:match(Haystack,Needles,Moptlist) of -			    nomatch -> []; -			    Match -> [Match] -			end -		end, -	do_split(Haystack,MList,0,Trim,TrimAll) -    catch -	_:_ -> -	    erlang:error(badarg) -    end. - -do_split(H,[],N,true,_) when N >= byte_size(H) -> -    []; -do_split(H,[],N,_,true) when N >= byte_size(H) -> -    []; -do_split(H,[],N,_,_) -> -    [binary:part(H,{N,byte_size(H)-N})]; -do_split(H,[{A,B}|T],N,Trim,TrimAll) -> -    case binary:part(H,{N,A-N}) of -	<<>> when TrimAll == true -> -	    do_split(H,T,A+B,Trim,TrimAll); -	<<>> -> -	    Rest =  do_split(H,T,A+B,Trim,TrimAll), -	    case {Trim, Rest} of -		{true,[]} -> -		    []; -		_ -> -		    [<<>> | Rest] -	    end; -	Oth -> -	    [Oth | do_split(H,T,A+B,Trim,TrimAll)] -    end. +split(_, _, _) -> +    erlang:nif_error(undef). +%%% End of BIFs.  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%  %% replace @@ -352,19 +304,6 @@ splitat(H,N,[I|T]) ->  %% Simple helper functions  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -get_opts_split([],{Part,Global,Trim,TrimAll}) -> -    {Part,Global,Trim,TrimAll}; -get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim,TrimAll}) -> -    get_opts_split(T,{{A,B},Global,Trim,TrimAll}); -get_opts_split([global | T],{Part,_Global,Trim,TrimAll}) -> -    get_opts_split(T,{Part,true,Trim,TrimAll}); -get_opts_split([trim | T],{Part,Global,_Trim,TrimAll}) -> -    get_opts_split(T,{Part,Global,true,TrimAll}); -get_opts_split([trim_all | T],{Part,Global,Trim,_TrimAll}) -> -    get_opts_split(T,{Part,Global,Trim,true}); -get_opts_split(_,_) -> -    throw(badopt). -  get_opts_replace([],{Part,Global,Insert}) ->      {Part,Global,Insert};  get_opts_replace([{scope,{A,B}} | T],{_Part,Global,Insert}) -> diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index d3124ac593..45f616bb02 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -40,7 +40,7 @@  -type ifdef() :: 'ifdef' | 'ifndef' | 'else'. --type name() :: {'atom', atom()}. +-type name() :: atom().  -type argspec() :: 'none'                       %No arguments                   | non_neg_integer().           %Number of arguments  -type tokens() :: [erl_scan:token()]. @@ -49,7 +49,8 @@  -define(DEFAULT_ENCODING, utf8).  %% Epp state record. --record(epp, {file :: file:io_device(),         %Current file +-record(epp, {file :: file:io_device() +                    | 'undefined',              %Current file  	      location=1,         		%Current location                delta=0 :: non_neg_integer(),     %Offset from Location (-file)                name="" :: file:name(),           %Current file name @@ -57,21 +58,14 @@                istk=[] :: [ifdef()],             %Ifdef stack                sstk=[] :: [#epp{}],              %State stack                path=[] :: [file:name()],         %Include-path -              macs = dict:new()                 %Macros (don't care locations) -                  :: dict:dict(name(), {argspec(), tokens()}), -              uses = dict:new()                 %Macro use structure -                  :: dict:dict(name(), [{argspec(), [used()]}]), +              macs = #{}		        %Macros (don't care locations) +	            :: #{name() => {argspec(), tokens()}}, +              uses = #{}			%Macro use structure +	            :: #{name() => [{argspec(), [used()]}]},                default_encoding = ?DEFAULT_ENCODING :: source_encoding(),  	      pre_opened = false :: boolean()  	     }). -%%% Note on representation: as tokens, both {var, Location, Name} and -%%% {atom, Location, Name} can occur as macro identifiers. However, keeping -%%% this distinction here is done for historical reasons only: previously, -%%% ?FOO and ?'FOO' were not the same, but now they are. Removing the -%%% distinction in the internal representation would simplify the code -%%% a little. -  %% open(Options)  %% open(FileName, IncludePath)  %% open(FileName, IncludePath, PreDefMacros) @@ -549,7 +543,8 @@ init_server(Pid, Name, Options, St0) ->  			 default_encoding=DefEncoding},              From = wait_request(St),              Anno = erl_anno:new(AtLocation), -            enter_file_reply(From, Name, Anno, AtLocation, code), +            enter_file_reply(From, file_name(Name), Anno, +			     AtLocation, code),              wait_req_scan(St);  	{error,E} ->  	    epp_reply(Pid, {error,E}) @@ -560,18 +555,18 @@ init_server(Pid, Name, Options, St0) ->  %%  FILE, LINE, MODULE as undefined, MACHINE and MACHINE value.  predef_macros(File) -> -     Machine = list_to_atom(erlang:system_info(machine)), -     Anno = line1(), -     dict:from_list([ -	{{atom,'FILE'}, 	      {none,[{string,Anno,File}]}}, -	{{atom,'LINE'},		      {none,[{integer,Anno,1}]}}, -	{{atom,'MODULE'},	      undefined}, -	{{atom,'MODULE_STRING'},      undefined}, -	{{atom,'BASE_MODULE'},	      undefined}, -	{{atom,'BASE_MODULE_STRING'}, undefined}, -	{{atom,'MACHINE'},	      {none,[{atom,Anno,Machine}]}}, -	{{atom,Machine},	      {none,[{atom,Anno,true}]}} -     ]). +    Machine = list_to_atom(erlang:system_info(machine)), +    Anno = line1(), +    Defs = [{'FILE', 	           {none,[{string,Anno,File}]}}, +	    {'LINE',		   {none,[{integer,Anno,1}]}}, +	    {'MODULE',	           undefined}, +	    {'MODULE_STRING',      undefined}, +	    {'BASE_MODULE',	   undefined}, +	    {'BASE_MODULE_STRING', undefined}, +	    {'MACHINE',	           {none,[{atom,Anno,Machine}]}}, +	    {Machine,	           {none,[{atom,Anno,true}]}} +	   ], +    maps:from_list(Defs).  %% user_predef(PreDefMacros, Macros) ->  %%	{ok,MacroDict} | {error,E} @@ -580,28 +575,21 @@ predef_macros(File) ->  user_predef([{M,Val,redefine}|Pdm], Ms) when is_atom(M) ->      Exp = erl_parse:tokens(erl_parse:abstract(Val)), -    user_predef(Pdm, dict:store({atom,M}, {none,Exp}, Ms)); +    user_predef(Pdm, Ms#{M=>{none,Exp}});  user_predef([{M,Val}|Pdm], Ms) when is_atom(M) -> -    case dict:find({atom,M}, Ms) of -	{ok,_Defs} when is_list(_Defs) -> %% User defined macros +    case Ms of +	#{M:=Defs} when is_list(Defs) -> +	     %% User defined macros.  	    {error,{redefine,M}}; -	{ok,_Def} -> %% Predefined macros +	#{M:=_Defs} -> +	    %% Predefined macros.  	    {error,{redefine_predef,M}}; -	error -> +	_ ->  	    Exp = erl_parse:tokens(erl_parse:abstract(Val)), -	    user_predef(Pdm, dict:store({atom,M}, [{none, {none,Exp}}], Ms)) +	    user_predef(Pdm, Ms#{M=>[{none,{none,Exp}}]})      end;  user_predef([M|Pdm], Ms) when is_atom(M) -> -    case dict:find({atom,M}, Ms) of -	{ok,_Defs} when is_list(_Defs) -> %% User defined macros -	    {error,{redefine,M}}; -	{ok,_Def} -> %% Predefined macros -	    {error,{redefine_predef,M}}; -	error -> -            A = line1(), -	    user_predef(Pdm, -	                dict:store({atom,M}, [{none, {none,[{atom,A,true}]}}], Ms)) -    end; +    user_predef([{M,true}|Pdm], Ms);  user_predef([Md|_Pdm], _Ms) -> {error,{bad,Md}};  user_predef([], Ms) -> {ok,Ms}. @@ -615,7 +603,9 @@ wait_request(St) ->      receive  	{epp_request,From,scan_erl_form} -> From;  	{epp_request,From,macro_defs} -> -	    epp_reply(From, dict:to_list(St#epp.macs)), +	    %% Return the old format to avoid any incompability issues. +	    Defs = [{{atom,K},V} || {K,V} <- maps:to_list(St#epp.macs)], +	    epp_reply(From, Defs),  	    wait_request(St);  	{epp_request,From,close} ->  	    close_file(St), @@ -667,7 +657,8 @@ enter_file(NewName, Inc, From, St) ->  enter_file2(NewF, Pname, From, St0, AtLocation) ->      Anno = erl_anno:new(AtLocation),      enter_file_reply(From, Pname, Anno, AtLocation, code), -    Ms = dict:store({atom,'FILE'}, {none,[{string,Anno,Pname}]}, St0#epp.macs), +    Ms0 = St0#epp.macs, +    Ms = Ms0#{'FILE':={none,[{string,Anno,Pname}]}},      %% update the head of the include path to be the directory of the new      %% source file, so that an included file can always include other files      %% relative to its current location (this is also how C does it); note @@ -688,7 +679,7 @@ enter_file_reply(From, Name, LocationAnno, AtLocation, Where) ->                 generated -> erl_anno:set_generated(true, Anno0)             end,      Rep = {ok, [{'-',Anno},{atom,Anno,file},{'(',Anno}, -		{string,Anno,file_name(Name)},{',',Anno}, +		{string,Anno,Name},{',',Anno},  		{integer,Anno,get_line(LocationAnno)},{')',LocationAnno},                  {dot,Anno}]},      epp_reply(From, Rep). @@ -719,9 +710,8 @@ leave_file(From, St) ->                           name2=OldName2} = OldSt,                      CurrLoc = add_line(OldLoc, Delta),                      Anno = erl_anno:new(CurrLoc), -		    Ms = dict:store({atom,'FILE'}, -				    {none,[{string,Anno,OldName2}]}, -				    St#epp.macs), +		    Ms0 = St#epp.macs, +		    Ms = Ms0#{'FILE':={none,[{string,Anno,OldName2}]}},                      NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses},  		    enter_file_reply(From, OldName, Anno, CurrLoc, code),                      case OldName2 =:= OldName of @@ -796,91 +786,48 @@ scan_toks(Toks0, From, St) ->      end.  scan_module([{'-',_Lh},{atom,_Lm,module},{'(',_Ll}|Ts], Ms) -> -    scan_module_1(Ts, [], Ms); +    scan_module_1(Ts, Ms);  scan_module([{'-',_Lh},{atom,_Lm,extends},{'(',_Ll}|Ts], Ms) -> -    scan_extends(Ts, [], Ms); +    scan_extends(Ts, Ms);  scan_module(_Ts, Ms) -> Ms. -scan_module_1([{atom,_,_}=A,{',',L}|Ts], As, Ms) -> +scan_module_1([{atom,_,_}=A,{',',L}|Ts], Ms) ->      %% Parameterized modules. -    scan_module_1([A,{')',L}|Ts], As, Ms); -scan_module_1([{atom,Ln,A},{')',_Lr}|_Ts], As, Ms0) -> -    Mod = lists:concat(lists:reverse([A|As])), -    Ms = dict:store({atom,'MODULE'}, -		     {none,[{atom,Ln,list_to_atom(Mod)}]}, Ms0), -    dict:store({atom,'MODULE_STRING'}, {none,[{string,Ln,Mod}]}, Ms); -scan_module_1([{atom,_Ln,A},{'.',_Lr}|Ts], As, Ms) -> -    scan_module_1(Ts, [".",A|As], Ms); -scan_module_1([{'.',_Lr}|Ts], As, Ms) -> -    scan_module_1(Ts, As, Ms); -scan_module_1(_Ts, _As, Ms) -> Ms. - -scan_extends([{atom,Ln,A},{')',_Lr}|_Ts], As, Ms0) -> -    Mod = lists:concat(lists:reverse([A|As])), -    Ms = dict:store({atom,'BASE_MODULE'}, -		     {none,[{atom,Ln,list_to_atom(Mod)}]}, Ms0), -    dict:store({atom,'BASE_MODULE_STRING'}, {none,[{string,Ln,Mod}]}, Ms); -scan_extends([{atom,_Ln,A},{'.',_Lr}|Ts], As, Ms) -> -    scan_extends(Ts, [".",A|As], Ms); -scan_extends([{'.',_Lr}|Ts], As, Ms) -> -    scan_extends(Ts, As, Ms); -scan_extends(_Ts, _As, Ms) -> Ms. +    scan_module_1([A,{')',L}|Ts], Ms); +scan_module_1([{atom,Ln,A}=ModAtom,{')',_Lr}|_Ts], Ms0) -> +    ModString = atom_to_list(A), +    Ms = Ms0#{'MODULE':={none,[ModAtom]}}, +    Ms#{'MODULE_STRING':={none,[{string,Ln,ModString}]}}; +scan_module_1(_Ts, Ms) -> Ms. + +scan_extends([{atom,Ln,A}=ModAtom,{')',_Lr}|_Ts], Ms0) -> +    ModString = atom_to_list(A), +    Ms = Ms0#{'BASE_MODULE':={none,[ModAtom]}}, +    Ms#{'BASE_MODULE_STRING':={none,[{string,Ln,ModString}]}}; +scan_extends(_Ts, Ms) -> Ms.  %% scan_define(Tokens, DefineToken, From, EppState) -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',_}=Comma|Toks], _Def, From, St) +scan_define([{'(',_Lp},{Type,_Lm,_}=Mac|Toks], Def, From, St)    when Type =:= atom; Type =:= var -> +    scan_define_1(Toks, Mac, Def, From, St); +scan_define(_Toks, Def, From, St) -> +    epp_reply(From, {error,{loc(Def),epp,{bad,define}}}), +    wait_req_scan(St). + +scan_define_1([{',',_}=Comma|Toks], Mac,_Def, From, St) ->      case catch macro_expansion(Toks, Comma) of          Expansion when is_list(Expansion) -> -            case dict:find({atom,M}, St#epp.macs) of -                {ok, Defs} when is_list(Defs) -> -                    %% User defined macros: can be overloaded -                    case proplists:is_defined(none, Defs) of -                        true -> -                            epp_reply(From, {error,{loc(Mac),epp,{redefine,M}}}), -                            wait_req_scan(St); -                        false -> -                            scan_define_cont(From, St, -                                             {atom, M}, -                                             {none, {none,Expansion}}) -                    end; -                {ok, _PreDef} -> -                    %% Predefined macros: cannot be overloaded -                    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), -                    wait_req_scan(St); -                error -> -                    scan_define_cont(From, St, -                                     {atom, M}, -                                     {none, {none,Expansion}}) -            end; +	    scan_define_2(none, {none,Expansion}, Mac, From, St);          {error,ErrL,What} ->              epp_reply(From, {error,{ErrL,epp,What}}),              wait_req_scan(St)      end; -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St) -  when Type =:= atom; Type =:= var -> +scan_define_1([{'(',_Lc}|Toks], Mac, Def, From, St) ->      case catch macro_pars(Toks, []) of -        {ok, {As,Me}} -> +        {ok,{As,_}=MacroDef} ->              Len = length(As), -            case dict:find({atom,M}, St#epp.macs) of -                {ok, Defs} when is_list(Defs) -> -                    %% User defined macros: can be overloaded -                    case proplists:is_defined(Len, Defs) of -                        true -> -                            epp_reply(From,{error,{loc(Mac),epp,{redefine,M}}}), -                            wait_req_scan(St); -                        false -> -                            scan_define_cont(From, St, {atom, M}, -                                             {Len, {As, Me}}) -                    end; -                {ok, _PreDef} -> -                    %% Predefined macros: cannot be overloaded -                    %% (There are currently no predefined F(...) macros.) -                    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), -                    wait_req_scan(St); -                error -> -                    scan_define_cont(From, St, {atom, M}, {Len, {As, Me}}) -            end; +	    scan_define_2(Len, MacroDef, Mac, From, St);  	{error,ErrL,What} ->              epp_reply(From, {error,{ErrL,epp,What}}),              wait_req_scan(St); @@ -888,10 +835,29 @@ scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St)              epp_reply(From, {error,{loc(Def),epp,{bad,define}}}),              wait_req_scan(St)      end; -scan_define(_Toks, Def, From, St) -> +scan_define_1(_Toks, _Mac, Def, From, St) ->      epp_reply(From, {error,{loc(Def),epp,{bad,define}}}),      wait_req_scan(St). +scan_define_2(Arity, Def, {_,_,Key}=Mac, From, #epp{macs=Ms}=St) -> +    case Ms of +	#{Key:=Defs} when is_list(Defs) -> +	    %% User defined macros: can be overloaded +	    case proplists:is_defined(Arity, Defs) of +		true -> +		    epp_reply(From, {error,{loc(Mac),epp,{redefine,Key}}}), +		    wait_req_scan(St); +		false -> +		    scan_define_cont(From, St, Key, Defs, Arity, Def) +	    end; +	#{Key:=_} -> +	    %% Predefined macros: cannot be overloaded +	    epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,Key}}}), +	    wait_req_scan(St); +	_ -> +	    scan_define_cont(From, St, Key, [], Arity, Def) +    end. +  %%% Detection of circular macro expansions (which would either keep  %%% the compiler looping forever, or run out of memory):  %%% When a macro is defined, we store the names of other macros it @@ -901,11 +867,17 @@ scan_define(_Toks, Def, From, St) ->  %%% the information from St#epp.uses is traversed, and if a circularity  %%% is detected, an error message is thrown. -scan_define_cont(F, St, M, {Arity, Def}) -> -    Ms = dict:append_list(M, [{Arity, Def}], St#epp.macs), -    try dict:append_list(M, [{Arity, macro_uses(Def)}], St#epp.uses) of +scan_define_cont(F, #epp{macs=Ms0}=St, M, Defs, Arity, Def) -> +    Ms = Ms0#{M=>[{Arity,Def}|Defs]}, +    try macro_uses(Def) of          U -> -            scan_toks(F, St#epp{uses=U, macs=Ms}) +	    Uses0 = St#epp.uses, +	    Val = [{Arity,U}|case Uses0 of +				 #{M:=UseList} -> UseList; +				 _ -> [] +			     end], +	    Uses = Uses0#{M=>Val}, +            scan_toks(F, St#epp{uses=Uses,macs=Ms})      catch          {error, Line, Reason} ->              epp_reply(F, {error,{Line,epp,Reason}}), @@ -923,23 +895,23 @@ macro_ref([{'?', _}, {'?', _} | Rest]) ->  macro_ref([{'?', _}, {atom, _, A}=Atom | Rest]) ->      Lm = loc(Atom),      Arity = count_args(Rest, Lm, A), -    [{{atom, A}, Arity} | macro_ref(Rest)]; +    [{A,Arity} | macro_ref(Rest)];  macro_ref([{'?', _}, {var, _, A}=Var | Rest]) ->      Lm = loc(Var),      Arity = count_args(Rest, Lm, A), -    [{{atom, A}, Arity} | macro_ref(Rest)]; +    [{A,Arity} | macro_ref(Rest)];  macro_ref([_Token | Rest]) ->      macro_ref(Rest).  %% scan_undef(Tokens, UndefToken, From, EppState)  scan_undef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _Undef, From, St) -> -    Macs = dict:erase({atom,M}, St#epp.macs), -    Uses = dict:erase({atom,M}, St#epp.uses), +    Macs = maps:remove(M, St#epp.macs), +    Uses = maps:remove(M, St#epp.uses),      scan_toks(From, St#epp{macs=Macs, uses=Uses});  scan_undef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _Undef, From,St) -> -    Macs = dict:erase({atom,M}, St#epp.macs), -    Uses = dict:erase({atom,M}, St#epp.uses), +    Macs = maps:remove(M, St#epp.macs), +    Uses = maps:remove(M, St#epp.uses),      scan_toks(From, St#epp{macs=Macs, uses=Uses});  scan_undef(_Toks, Undef, From, St) ->      epp_reply(From, {error,{loc(Undef),epp,{bad,undef}}}), @@ -1006,17 +978,17 @@ scan_include_lib(_Toks, Inc, From, St) ->  %%  Report a badly formed if[n]def test and then treat as undefined macro.  scan_ifdef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    scan_toks(From, St#epp{istk=[ifdef|St#epp.istk]}); -	error -> +	_ ->  	    skip_toks(From, St, [ifdef])      end;  scan_ifdef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    scan_toks(From, St#epp{istk=[ifdef|St#epp.istk]}); -	error -> +	_ ->  	    skip_toks(From, St, [ifdef])      end;  scan_ifdef(_Toks, IfDef, From, St) -> @@ -1024,17 +996,17 @@ scan_ifdef(_Toks, IfDef, From, St) ->      wait_req_skip(St, [ifdef]).  scan_ifndef([{'(',_Llp},{atom,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfnD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    skip_toks(From, St, [ifndef]); -	error -> +	_ ->  	    scan_toks(From, St#epp{istk=[ifndef|St#epp.istk]})      end;  scan_ifndef([{'(',_Llp},{var,_Lm,M},{')',_Lrp},{dot,_Ld}], _IfnD, From, St) -> -    case dict:find({atom,M}, St#epp.macs) of -	{ok,_Def} -> +    case St#epp.macs of +	#{M:=_Def} ->  	    skip_toks(From, St, [ifndef]); -	error -> +	_ ->  	    scan_toks(From, St#epp{istk=[ifndef|St#epp.istk]})      end;  scan_ifndef(_Toks, IfnDef, From, St) -> @@ -1102,7 +1074,8 @@ scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},             {dot,_Ld}], Tf, From, St) ->      Anno = erl_anno:new(Ln),      enter_file_reply(From, Name, Anno, loc(Tf), generated), -    Ms = dict:store({atom,'FILE'}, {none,[{string,line1(),Name}]}, St#epp.macs), +    Ms0 = St#epp.macs, +    Ms = Ms0#{'FILE':={none,[{string,line1(),Name}]}},      Locf = loc(Tf),      NewLoc = new_location(Ln, St#epp.location, Locf),      Delta = get_line(element(2, Tf))-Ln + St#epp.delta, @@ -1190,40 +1163,42 @@ macro_expansion([], Anno0) -> throw({error,loc(Anno0),premature_end}).  %%  Expand the macros in a list of tokens, making sure that an expansion  %%  gets the same location as the macro call. -expand_macros(Type, MacT, M, Toks, Ms0) -> -    %% (Type will always be 'atom') -    {Ms, U} = Ms0, +expand_macros(MacT, M, Toks, Ms0) -> +    {Ms,U} = Ms0,      Lm = loc(MacT),      Tinfo = element(2, MacT), -    case expand_macro1(Type, Lm, M, Toks, Ms) of +    case expand_macro1(Lm, M, Toks, Ms) of  	{ok,{none,Exp}} -> -	    check_uses([{{Type,M}, none}], [], U, Lm), -	    Toks1 = expand_macros(expand_macro(Exp, Tinfo, [], dict:new()), Ms0), +	    check_uses([{M,none}], [], U, Lm), +	    Toks1 = expand_macros(expand_macro(Exp, Tinfo, [], #{}), Ms0),  	    expand_macros(Toks1++Toks, Ms0);  	{ok,{As,Exp}} -> -	    check_uses([{{Type,M}, length(As)}], [], U, Lm), -	    {Bs,Toks1} = bind_args(Toks, Lm, M, As, dict:new()), +	    check_uses([{M,length(As)}], [], U, Lm), +	    {Bs,Toks1} = bind_args(Toks, Lm, M, As, #{}),  	    expand_macros(expand_macro(Exp, Tinfo, Toks1, Bs), Ms0)      end. -expand_macro1(Type, Lm, M, Toks, Ms) -> +expand_macro1(Lm, M, Toks, Ms) ->      Arity = count_args(Toks, Lm, M), -    case dict:find({Type,M}, Ms) of -        error -> %% macro not found -            throw({error,Lm,{undefined,M,Arity}}); -        {ok, undefined} -> %% Predefined macro without definition +    case Ms of +	#{M:=undefined} -> +	    %% Predefined macro without definition.              throw({error,Lm,{undefined,M,Arity}}); -        {ok, [{none, Def}]} -> -            {ok, Def}; -        {ok, Defs} when is_list(Defs) -> -            case proplists:get_value(Arity, Defs) of +	#{M:=[{none,Def}]} -> +            {ok,Def}; +	#{M:=Defs} when is_list(Defs) -> +	    case proplists:get_value(Arity, Defs) of                  undefined ->                      throw({error,Lm,{mismatch,M}});                  Def -> -                    {ok, Def} +                    {ok,Def}              end; -        {ok, PreDef} -> %% Predefined macro -            {ok, PreDef} +        #{M:=PreDef} -> +	    %% Predefined macro. +            {ok,PreDef}; +        _ -> +	    %% Macro not found. +            throw({error,Lm,{undefined,M,Arity}})      end.  check_uses([], _Anc, _U, _Lm) -> @@ -1231,7 +1206,7 @@ check_uses([], _Anc, _U, _Lm) ->  check_uses([M|Rest], Anc, U, Lm) ->      case lists:member(M, Anc) of  	true -> -	    {{_, Name},Arity} = M, +	    {Name,Arity} = M,  	    throw({error,Lm,{circular,Name,Arity}});  	false ->  	    L = get_macro_uses(M, U), @@ -1240,23 +1215,23 @@ check_uses([M|Rest], Anc, U, Lm) ->      end.  get_macro_uses({M,Arity}, U) -> -    case dict:find(M, U) of -	error -> -	    []; -	{ok, L} -> -	    proplists:get_value(Arity, L, proplists:get_value(none, L, [])) +    case U of +	#{M:=L} -> +	    proplists:get_value(Arity, L, proplists:get_value(none, L, [])); +	_ -> +	    []      end.  %% Macro expansion  %% Note: io:scan_erl_form() does not return comments or white spaces.  expand_macros([{'?',_Lq},{atom,_Lm,M}=MacT|Toks], Ms) -> -    expand_macros(atom, MacT, M, Toks, Ms); +    expand_macros(MacT, M, Toks, Ms);  %% Special macros  expand_macros([{'?',_Lq},{var,Lm,'LINE'}=Tok|Toks], Ms) ->      Line = erl_scan:line(Tok),      [{integer,Lm,Line}|expand_macros(Toks, Ms)];  expand_macros([{'?',_Lq},{var,_Lm,M}=MacT|Toks], Ms) -> -    expand_macros(atom, MacT, M, Toks, Ms); +    expand_macros(MacT, M, Toks, Ms);  %% Illegal macros  expand_macros([{'?',_Lq},Token|_Toks], _Ms) ->      T = case erl_scan:text(Token) of @@ -1295,7 +1270,7 @@ macro_args(_Toks, Lm, M, _As, _Bs) ->  store_arg(L, M, _A, [], _Bs) ->      throw({error,L,{mismatch,M}});  store_arg(_L, _M, A, Arg, Bs) -> -    dict:store(A, Arg, Bs). +    Bs#{A=>Arg}.  %% count_args(Tokens, MacroLine, MacroName)  %%  Count the number of arguments in a macro call. @@ -1368,19 +1343,17 @@ macro_arg([], _E, Arg) ->  %%  and then the macro arguments, i.e. simulate textual expansion.  expand_macro([{var,_Lv,V}|Ts], L, Rest, Bs) -> -    case dict:find(V, Bs) of -	{ok,Val} -> -	    %% lists:append(Val, expand_macro(Ts, L, Rest, Bs)); +    case Bs of +	#{V:=Val} ->  	    expand_arg(Val, Ts, L, Rest, Bs); -	error -> +	_ ->  	    [{var,L,V}|expand_macro(Ts, L, Rest, Bs)]      end;  expand_macro([{'?', _}, {'?', _}, {var,_Lv,V}|Ts], L, Rest, Bs) -> -    case dict:find(V, Bs) of -	{ok,Val} -> -	    %% lists:append(Val, expand_macro(Ts, L, Rest, Bs)); +    case Bs of +	#{V:=Val} ->              expand_arg(stringify(Val, L), Ts, L, Rest, Bs); -	error -> +	_ ->  	    [{var,L,V}|expand_macro(Ts, L, Rest, Bs)]      end;  expand_macro([T|Ts], L, Rest, Bs) -> diff --git a/lib/stdlib/src/erl_anno.erl b/lib/stdlib/src/erl_anno.erl index 143318aa55..d32c34dabd 100644 --- a/lib/stdlib/src/erl_anno.erl +++ b/lib/stdlib/src/erl_anno.erl @@ -33,7 +33,7 @@  -export_type([anno_term/0]). --define(LN(L), is_integer(L)). +-define(LN(L), is_integer(L), L >= 0).  -define(COL(C), (is_integer(C) andalso C >= 1)).  %% Location. @@ -52,13 +52,13 @@                      | {'record', record()}                      | {'text', string()}. --type anno() :: location() | [annotation(), ...]. +-opaque anno() :: location() | [annotation(), ...].  -type anno_term() :: term().  -type column() :: pos_integer().  -type generated() :: boolean().  -type filename() :: file:filename_all(). --type line() :: integer(). +-type line() :: non_neg_integer().  -type location() :: line() | {line(), column()}.  -type record() :: boolean().  -type text() :: string(). @@ -90,9 +90,13 @@ to_term(Anno) ->  -ifdef(DEBUG).  from_term(Term) when is_list(Term) ->      Term; +from_term(Line) when is_integer(Line), Line < 0 -> % Before OTP 19 +    set_generated(true, new(-Line));  from_term(Term) ->      [{location, Term}].  -else. +from_term(Line) when is_integer(Line), Line < 0 -> % Before OTP 19 +    set_generated(true, new(-Line));  from_term(Term) ->      Term.  -endif. @@ -198,18 +202,11 @@ file(Anno) ->        Anno :: anno().  generated(Line) when ?ALINE(Line) -> -    Line =< 0; +    false;  generated({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> -    Line =< 0; +    false;  generated(Anno) -> -    _ = anno_info(Anno, generated, false), -    {location, Location} = lists:keyfind(location, 1, Anno), -    case Location of -        {Line, _Column} -> -            Line =< 0; -        Line -> -            Line =< 0 -    end. +    anno_info(Anno, generated, false).  -spec line(Anno) -> line() when        Anno :: anno(). @@ -226,18 +223,11 @@ line(Anno) ->        Anno :: anno().  location(Line) when ?ALINE(Line) -> -    abs(Line); -location({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> -    {abs(Line), Column}; +    Line; +location({Line, Column}=Location) when ?ALINE(Line), ?ACOLUMN(Column) -> +    Location;  location(Anno) -> -    case anno_info(Anno, location) of -        Line when Line < 0 -> -            -Line; -        {Line, Column} when Line < 0 -> -            {-Line, Column}; -        Location -> -            Location -    end. +    anno_info(Anno, location).  -spec record(Anno) -> record() when        Anno :: anno(). @@ -270,31 +260,8 @@ set_file(File, Anno) ->        Generated :: generated(),        Anno :: anno(). -set_generated(true, Line) when ?ALINE(Line) -> -    -abs(Line); -set_generated(false, Line) when ?ALINE(Line) -> -    abs(Line); -set_generated(true, {Line, Column}) when ?ALINE(Line), -                                         ?ACOLUMN(Column) -> -    {-abs(Line),Column}; -set_generated(false, {Line, Column}) when ?ALINE(Line), -                                          ?ACOLUMN(Column) -> -    {abs(Line),Column};  set_generated(Generated, Anno) -> -    _ = set(generated, Generated, Anno), -    {location, Location} = lists:keyfind(location, 1, Anno), -    NewLocation = -        case Location of -            {Line, Column} when Generated -> -                {-abs(Line), Column}; -            {Line, Column} when not Generated -> -                {abs(Line), Column}; -            Line when Generated -> -                -abs(Line); -            Line when not Generated -> -                abs(Line) -        end, -    lists:keyreplace(location, 1, Anno, {location, NewLocation}). +    set(generated, Generated, Anno).  -spec set_line(Line, Anno) -> Anno when        Line :: line(), @@ -313,38 +280,17 @@ set_line(Line, Anno) ->        Anno :: anno().  set_location(Line, L) when ?ALINE(L), ?LLINE(Line) -> -    new_location(fix_line(Line, L)); +    new_location(Line);  set_location(Line, {L, Column}) when ?ALINE(L), ?ACOLUMN(Column),                                       ?LLINE(Line) -> -    new_location(fix_line(Line, L)); +    new_location(Line);  set_location({L, C}=Loc, Line) when ?ALINE(Line), ?LLINE(L), ?LCOLUMN(C) -> -    new_location(fix_location(Loc, Line)); +    new_location(Loc);  set_location({L, C}=Loc, {Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column),                                                ?LLINE(L), ?LCOLUMN(C) -> -    new_location(fix_location(Loc, Line)); +    new_location(Loc);  set_location(Location, Anno) -> -    _ = set(location, Location, Anno), -    {location, OldLocation} = lists:keyfind(location, 1, Anno), -    NewLocation = -        case {Location, OldLocation} of -            {{_Line, _Column}=Loc, {L, _C}} -> -                fix_location(Loc, L); -            {Line, {L, _C}} -> -                fix_line(Line, L); -            {{_Line, _Column}=Loc, L} -> -                fix_location(Loc, L); -            {Line, L} -> -                fix_line(Line, L) -        end, -    lists:keyreplace(location, 1, Anno, {location, NewLocation}). - -fix_location({Line, Column}, OldLine) -> -    {fix_line(Line, OldLine), Column}. - -fix_line(Line, OldLine) when OldLine < 0, Line > 0 -> -    -Line; -fix_line(Line, _OldLine) -> -    Line. +    set(location, Location, Anno).  -spec set_record(Record, Anno) -> Anno when        Record :: record(), @@ -383,7 +329,7 @@ set_anno(Item, Value, Anno) ->                      _ ->                          lists:keyreplace(Item, 1, Anno, {Item, Value})                  end, -            simplify(R) +            reset_simplify(R)      end.  reset(Anno, Item) -> diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 5678e7eebe..4a4019b8bd 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -31,12 +31,8 @@  -export([is_guard_expr/1]).  -export([bool_option/4,value_option/3,value_option/7]). --export([modify_line/2]). -  -import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]). --deprecated([{modify_line, 2, next_major_release}]). -  %% bool_option(OnOpt, OffOpt, Default, Options) -> boolean().  %% value_option(Flag, Default, Options) -> Value.  %% value_option(Flag, Default, OnOpt, OnVal, OffOpt, OffVal, Options) -> @@ -79,7 +75,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->  %%-define(DEBUGF(X,Y), io:format(X, Y)).  -define(DEBUGF(X,Y), void). --type line() :: erl_anno:line().     % a convenient alias +-type line() :: erl_anno:anno().     % a convenient alias  -type fa()   :: {atom(), arity()}.   % function+arity  -type ta()   :: {atom(), arity()}.   % type+arity @@ -238,6 +234,9 @@ format_error({removed, MFA, ReplacementMFA, Rel}) ->  		  "use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]);  format_error({removed, MFA, String}) when is_list(String) ->      io_lib:format("~s: ~s", [format_mfa(MFA), String]); +format_error({removed_type, MNA, ReplacementMNA, Rel}) -> +    io_lib:format("the type ~s was removed in ~s; use ~s instead", +                  [format_mna(MNA), Rel, format_mna(ReplacementMNA)]);  format_error({obsolete_guard, {F, A}}) ->      io_lib:format("~p/~p obsolete", [F, A]);  format_error({too_many_arguments,Arity}) -> @@ -416,6 +415,9 @@ format_mfa({M, F, A}) when is_integer(A) ->  format_mf(M, F, ArityString) when is_atom(M), is_atom(F) ->      atom_to_list(M) ++ ":" ++ atom_to_list(F) ++ "/" ++ ArityString. +format_mna({M, N, A}) when is_integer(A) -> +    atom_to_list(M) ++ ":" ++ atom_to_list(N) ++ gen_type_paren(A). +  format_where(L) when is_integer(L) ->      io_lib:format("(line ~p)", [L]);  format_where({L,C}) when is_integer(L), is_integer(C) -> @@ -3190,8 +3192,8 @@ handle_generator(P,E,Vt,Uvt,St0) ->  handle_bitstring_gen_pat({bin,_,Segments=[_|_]},St) ->      case lists:last(Segments) of          {bin_element,Line,{var,_,_},default,Flags} when is_list(Flags) -> -            case member(binary, Flags) orelse member(bits, Flags) -                                       orelse member(bitstring, Flags) of +            case member(binary, Flags) orelse member(bytes, Flags) +              orelse member(bits, Flags) orelse member(bitstring, Flags) of                  true ->                      add_error(Line, unsized_binary_in_bin_gen_pattern, St);                  false -> @@ -3485,13 +3487,6 @@ vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused].  copy_expr(Expr, Anno) ->      erl_parse:map_anno(fun(_A) -> Anno end, Expr). -%% modify_line(Form, Fun) -> Form -%% modify_line(Expression, Fun) -> Expression -%%  Applies Fun to each line number occurrence. - -modify_line(T, F0) -> -    erl_parse:map_anno(F0, T). -  %% Check a record_info call. We have already checked that it is not  %% shadowed by an import. @@ -3560,6 +3555,7 @@ deprecated_function(Line, M, F, As, St) ->  	    St      end. +-dialyzer({no_match, deprecated_type/5}).  deprecated_type(L, M, N, As, St) ->      NAs = length(As),      case otp_internal:obsolete_type(M, N, NAs) of @@ -3570,6 +3566,8 @@ deprecated_type(L, M, N, As, St) ->                  false ->                      St              end; +        {removed, Replacement, Rel} -> +            add_warning(L, {removed_type, {M,N,NAs}, Replacement, Rel}, St);          no ->              St      end. diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index e82282421e..ae42a8f0b1 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -525,11 +525,6 @@ Erlang code.  -export([type_inop_prec/1,type_preop_prec/1]).  -export([map_anno/2, fold_anno/3, mapfold_anno/3,           new_anno/1, anno_to_term/1, anno_from_term/1]). --export([set_line/2,get_attribute/2,get_attributes/1]). - --deprecated([{set_line, 2, next_major_release}, -             {get_attribute, 2, next_major_release}, -             {get_attributes, 1, next_major_release}]).  %% The following directive is needed for (significantly) faster compilation  %% of the generated .erl file by the HiPE compiler.  Please do not remove. @@ -795,31 +790,11 @@ record_fields([{match,_Am,{atom,Aa,A},Expr}|Fields]) ->      [{record_field,Aa,{atom,Aa,A},Expr}|record_fields(Fields)];  record_fields([{typed,Expr,TypeInfo}|Fields]) ->      [Field] = record_fields([Expr]), -    TypeInfo1 = -	case Expr of -	    {match, _, _, _} -> TypeInfo; %% If we have an initializer. -	    {atom, Aa, _} -> -                case has_undefined(TypeInfo) of -                    false -> -                        lift_unions(abstract2(undefined, Aa), TypeInfo); -                    true -> -                        TypeInfo -                end -	end, -    [{typed_record_field,Field,TypeInfo1}|record_fields(Fields)]; +    [{typed_record_field,Field,TypeInfo}|record_fields(Fields)];  record_fields([Other|_Fields]) ->      ret_err(?anno(Other), "bad record field");  record_fields([]) -> []. -has_undefined({atom,_,undefined}) -> -    true; -has_undefined({ann_type,_,[_,T]}) -> -    has_undefined(T); -has_undefined({type,_,union,Ts}) -> -    lists:any(fun has_undefined/1, Ts); -has_undefined(_) -> -    false. -  term(Expr) ->      try normalise(Expr)      catch _:_R -> ret_err(?anno(Expr), "bad attribute") @@ -1118,28 +1093,6 @@ type_preop_prec('-') -> {600,700};  type_preop_prec('bnot') -> {600,700};  type_preop_prec('#') -> {700,800}. -%%% [Experimental]. The parser just copies the attributes of the -%%% scanner tokens to the abstract format. This design decision has -%%% been hidden to some extent: use set_line() and get_attribute() to -%%% access the second element of (almost all) of the abstract format -%%% tuples. A typical use is to negate line numbers to prevent the -%%% compiler from emitting warnings and errors. The second element can -%%% (of course) be set to any value, but then these functions no -%%% longer apply. To get all present attributes as a property list -%%% get_attributes() should be used. - --compile({nowarn_deprecated_function,{erl_scan,set_attribute,3}}). -set_line(L, F) -> -    erl_scan:set_attribute(line, L, F). - --compile({nowarn_deprecated_function,{erl_scan,attributes_info,2}}). -get_attribute(L, Name) -> -    erl_scan:attributes_info(L, Name). - --compile({nowarn_deprecated_function,{erl_scan,attributes_info,1}}). -get_attributes(L) -> -    erl_scan:attributes_info(L). -  -spec map_anno(Fun, Abstr) -> NewAbstr when        Fun :: fun((Anno) -> Anno),        Anno :: erl_anno:anno(), diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index d2f53816b8..47223b129c 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -52,25 +52,15 @@  %%% External exports  -export([string/1,string/2,string/3,tokens/3,tokens/4, -         format_error/1,reserved_word/1, -         token_info/1,token_info/2, -         attributes_info/1,attributes_info/2,set_attribute/3]). +         format_error/1,reserved_word/1]).  -export([column/1,end_location/1,line/1,location/1,text/1,           category/1,symbol/1]). --deprecated([{attributes_info, 1, next_major_release}, -             {attributes_info, 2, next_major_release}, -             {set_attribute, 3, next_major_release}, -             {token_info, 1, next_major_release}, -             {token_info, 2, next_major_release}]). -  %%% Private  -export([continuation_location/1]).  -export_type([error_info/0, -              line/0, -              location/0,                options/0,                return_cont/0,                token/0, @@ -85,29 +75,18 @@  -define(ALINE(L), is_integer(L)).  -define(STRING(S), is_list(S)).  -define(RESWORDFUN(F), is_function(F, 1)). --define(SETATTRFUN(F), is_function(F, 1)).  -type category() :: atom(). --type column() :: pos_integer().                % Deprecated --type line() :: integer().                      % Deprecated --type location() :: line() | {line(),column()}. % Deprecated  -type resword_fun() :: fun((atom()) -> boolean()).  -type option() :: 'return' | 'return_white_spaces' | 'return_comments'                  | 'text' | {'reserved_word_fun', resword_fun()}.  -type options() :: option() | [option()].  -type symbol() :: atom() | float() | integer() | string(). --type info_line() :: integer() | term(). --type attributes_data() -       :: [{'column', column()} | {'line', info_line()} | {'text', string()}] -        |  {line(), column()}. -%% The fact that {line(),column()} is a possible attributes() type -%% is hidden. --type attributes() :: line() | attributes_data(). --type token() :: {category(), attributes(), symbol()} -               | {category(), attributes()}. +-type token() :: {category(), Anno :: erl_anno:anno(), symbol()} +               | {category(), Anno :: erl_anno:anno()}.  -type tokens() :: [token()].  -type error_description() :: term(). --type error_info() :: {location(), module(), error_description()}. +-type error_info() :: {erl_anno:location(), module(), error_description()}.  %%% Local record.  -record(erl_scan, @@ -136,8 +115,8 @@ format_error(Other) ->        String :: string(),        Return :: {'ok', Tokens :: tokens(), EndLocation}                | {'error', ErrorInfo :: error_info(), ErrorLocation}, -      EndLocation :: location(), -      ErrorLocation :: location(). +      EndLocation :: erl_anno:location(), +      ErrorLocation :: erl_anno:location().  string(String) ->      string(String, 1, []). @@ -145,9 +124,9 @@ string(String) ->        String :: string(),        Return :: {'ok', Tokens :: tokens(), EndLocation}                | {'error', ErrorInfo :: error_info(), ErrorLocation}, -      StartLocation :: location(), -      EndLocation :: location(), -      ErrorLocation :: location(). +      StartLocation :: erl_anno:location(), +      EndLocation :: erl_anno:location(), +      ErrorLocation :: erl_anno:location().  string(String, StartLocation) ->      string(String, StartLocation, []). @@ -156,9 +135,9 @@ string(String, StartLocation) ->        Options :: options(),        Return :: {'ok', Tokens :: tokens(), EndLocation}                | {'error', ErrorInfo :: error_info(), ErrorLocation}, -      StartLocation :: location(), -      EndLocation :: location(), -      ErrorLocation :: location(). +      StartLocation :: erl_anno:location(), +      EndLocation :: erl_anno:location(), +      ErrorLocation :: erl_anno:location().  string(String, Line, Options) when ?STRING(String), ?ALINE(Line) ->      string1(String, options(Options), Line, no_col, []);  string(String, {Line,Column}, Options) when ?STRING(String), @@ -167,20 +146,23 @@ string(String, {Line,Column}, Options) when ?STRING(String),      string1(String, options(Options), Line, Column, []).  -type char_spec() :: string() | 'eof'. --type cont_fun() :: fun((char_spec(), #erl_scan{}, line(), column(), +-type cont_fun() :: fun((char_spec(), #erl_scan{}, +                         erl_anno:line(), erl_anno:column(),                           tokens(), any()) -> any()).  -opaque return_cont() :: {erl_scan_continuation, -                          string(), column(), tokens(), line(), +                          string(), erl_anno:column(), tokens(), +                          erl_anno:line(),                            #erl_scan{}, any(), cont_fun()}. --type tokens_result() :: {'ok', Tokens :: tokens(), EndLocation :: location()} -                       | {'eof', EndLocation :: location()} +-type tokens_result() :: {'ok', Tokens :: tokens(), +                          EndLocation :: erl_anno:location()} +                       | {'eof', EndLocation :: erl_anno:location()}                         | {'error', ErrorInfo :: error_info(), -                          EndLocation :: location()}. +                          EndLocation :: erl_anno:location()}.  -spec tokens(Continuation, CharSpec, StartLocation) -> Return when        Continuation :: return_cont() | [],        CharSpec :: char_spec(), -      StartLocation :: location(), +      StartLocation :: erl_anno:location(),        Return :: {'done',Result :: tokens_result(),LeftOverChars :: char_spec()}                | {'more', Continuation1 :: return_cont()}.  tokens(Cont, CharSpec, StartLocation) -> @@ -189,7 +171,7 @@ tokens(Cont, CharSpec, StartLocation) ->  -spec tokens(Continuation, CharSpec, StartLocation, Options) -> Return when        Continuation :: return_cont() | [],        CharSpec :: char_spec(), -      StartLocation :: location(), +      StartLocation :: erl_anno:location(),        Options :: options(),        Return :: {'done',Result :: tokens_result(),LeftOverChars :: char_spec()}                | {'more', Continuation1 :: return_cont()}. @@ -257,155 +239,6 @@ symbol({_Category,_Anno,Symbol}) ->  symbol(T) ->      erlang:error(badarg, [T]). --type attribute_item() :: 'column' | 'length' | 'line' -                        | 'location' | 'text'. --type info_location() :: location() | term(). --type attribute_info() :: {'column', column()}| {'length', pos_integer()} -                        | {'line', info_line()} -                        | {'location', info_location()} -                        | {'text', string()}. --type token_item() :: 'category' | 'symbol' | attribute_item(). --type token_info() :: {'category', category()} | {'symbol', symbol()} -                    | attribute_info(). - --spec token_info(Token) -> TokenInfo when -      Token :: token(), -      TokenInfo :: [TokenInfoTuple :: token_info()]. -token_info(Token) -> -    Items = [category,column,length,line,symbol,text], % undefined order -    token_info(Token, Items). - --spec token_info(Token, TokenItem) -> TokenInfoTuple | 'undefined' when -                     Token :: token(), -                     TokenItem :: token_item(), -                     TokenInfoTuple :: token_info(); -                (Token, TokenItems) -> TokenInfo when -                     Token :: token(), -                     TokenItems :: [TokenItem :: token_item()], -                     TokenInfo :: [TokenInfoTuple :: token_info()]. -token_info(_Token, []) -> -    []; -token_info(Token, [Item|Items]) when is_atom(Item) -> -    case token_info(Token, Item) of -        undefined -> -            token_info(Token, Items); -        TokenInfo when is_tuple(TokenInfo) -> -            [TokenInfo|token_info(Token, Items)] -    end; -token_info({Category,_Attrs}, category=Item) -> -    {Item,Category}; -token_info({Category,_Attrs,_Symbol}, category=Item) -> -    {Item,Category}; -token_info({Category,_Attrs}, symbol=Item) -> -    {Item,Category}; -token_info({_Category,_Attrs,Symbol}, symbol=Item) -> -    {Item,Symbol}; -token_info({_Category,Attrs}, Item) -> -    attributes_info(Attrs, Item); -token_info({_Category,Attrs,_Symbol}, Item) -> -    attributes_info(Attrs, Item). - --spec attributes_info(Attributes) -> AttributesInfo when -      Attributes :: attributes(), -      AttributesInfo :: [AttributeInfoTuple :: attribute_info()]. -attributes_info(Attributes) -> -    Items = [column,length,line,text], % undefined order -    attributes_info(Attributes, Items). - --spec attributes_info -        (Attributes, AttributeItem) -> AttributeInfoTuple | 'undefined' when -             Attributes :: attributes(), -             AttributeItem :: attribute_item(), -             AttributeInfoTuple :: attribute_info(); -        (Attributes, AttributeItems) -> AttributeInfo when -             Attributes :: attributes(), -             AttributeItems :: [AttributeItem :: attribute_item()], -             AttributeInfo :: [AttributeInfoTuple :: attribute_info()]. -attributes_info(_Attrs, []) -> -    []; -attributes_info(Attrs, [A|As]) when is_atom(A) -> -    case attributes_info(Attrs, A) of -        undefined -> -            attributes_info(Attrs, As); -        AttributeInfo when is_tuple(AttributeInfo) -> -            [AttributeInfo|attributes_info(Attrs, As)] -    end; -attributes_info({Line,Column}, column=Item) when ?ALINE(Line), -                                                 ?COLUMN(Column) -> -    {Item,Column}; -attributes_info(Line, column) when ?ALINE(Line) -> -    undefined; -attributes_info(Attrs, column=Item) -> -    case attr_info(Attrs, Item) of -        undefined -> -            case erl_anno:column(Attrs) of -                undefined -> -                    undefined; -                Column -> -                    {Item,Column} -            end; -        T -> -            T -    end; -attributes_info(Attrs, length=Item) -> -    case attributes_info(Attrs, text) of -        undefined -> -            undefined; -        {text,Text} -> -            {Item,length(Text)} -    end; -attributes_info(Line, line=Item) when ?ALINE(Line) -> -    {Item,Line}; -attributes_info({Line,Column}, line=Item) when ?ALINE(Line), -                                               ?COLUMN(Column) -> -    {Item,Line}; -attributes_info(Attrs, line=Item) -> -    case attr_info(Attrs, Item) of -        undefined -> -            case attr_info(Attrs, location) of -                {location,{Line,_Column}} -> -                    {Item,Line}; -                {location,Line} -> -                    {Item,Line}; -                undefined -> -                    undefined -            end; -        T -> -            T -    end; -attributes_info({Line,Column}=Location, location=Item) when ?ALINE(Line), -                                                            ?COLUMN(Column) -> -    {Item,Location}; -attributes_info(Line, location=Item) when ?ALINE(Line) -> -    {Item,Line}; -attributes_info(Attrs, location=Item) -> -    {line,Line} = attributes_info(Attrs, line), -    case attributes_info(Attrs, column) of -        undefined -> -            %% If set_attribute() has assigned a term such as {17,42} -            %% to 'line', then Line will look like {Line,Column}. One -            %% should not use 'location' but 'line' and 'column' in -            %% such special cases. -            {Item,Line}; -        {column,Column} -> -            {Item,{Line,Column}} -    end; -attributes_info({Line,Column}, text) when ?ALINE(Line), ?COLUMN(Column) -> -    undefined; -attributes_info(Line, text) when ?ALINE(Line) -> -    undefined; -attributes_info(Attrs, text=Item) -> -    attr_info(Attrs, Item); -attributes_info(T1, T2) -> -    erlang:error(badarg, [T1,T2]). - --spec set_attribute(AttributeItem, Attributes, SetAttributeFun) -> Attributes when -      AttributeItem :: 'line', -      Attributes :: attributes(), -      SetAttributeFun :: fun((info_line()) -> info_line()). -set_attribute(Tag, Attributes, Fun) when ?SETATTRFUN(Fun) -> -    set_attr(Tag, Attributes, Fun). -  %%%  %%% Local functions  %%% @@ -471,62 +304,6 @@ expand_opt(return, Os) ->  expand_opt(O, Os) ->      [O|Os]. -attr_info(Attrs, Item) -> -    try lists:keyfind(Item, 1, Attrs) of -        {_Item, _Value} = T -> -            T; -        false -> -            undefined -    catch -	_:_ -> -            erlang:error(badarg, [Attrs, Item]) -    end. - --spec set_attr('line', attributes(), fun((line()) -> line())) -> attributes(). - -set_attr(line, Line, Fun) when ?ALINE(Line) -> -    Ln = Fun(Line), -    if -        ?ALINE(Ln) -> -            Ln; -        true -> -            [{line,Ln}] -    end; -set_attr(line, {Line,Column}, Fun) when ?ALINE(Line), ?COLUMN(Column) -> -    Ln = Fun(Line), -    if -        ?ALINE(Ln) -> -            {Ln,Column}; -        true -> -            [{line,Ln},{column,Column}] -    end; -set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) -> -    case lists:keyfind(Tag, 1, Attrs) of -        {line,Line} -> -            case lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}) of -                [{line,Ln}] when ?ALINE(Ln) -> -                    Ln; -                As -> -                    As -            end; -        false -> -            {location, Location} = lists:keyfind(location, 1, Attrs), -            Ln = case Location of -                     {Line,Column} when ?ALINE(Line), ?COLUMN(Column) -> -                         {Fun(Line),Column}; -                     _ -> -                         Fun(Location) -                 end, -            case lists:keyreplace(location, 1, Attrs, {location,Ln}) of -                [{location,Ln}] when ?ALINE(Ln) -> -                    Ln; -                As -> -                    As -            end -    end; -set_attr(T1, T2, T3) -> -    erlang:error(badarg, [T1,T2,T3]). -  tokens1(Cs, St, Line, Col, Toks, Fun, Any) when ?STRING(Cs); Cs =:= eof ->      case Fun(Cs, St, Line, Col, Toks, Any) of          {more,{Cs0,Ncol,Ntoks,Nline,Nany,Nfun}} -> diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 41b49f4a86..b8ce311c35 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -38,7 +38,7 @@  -record(state, {file         :: file:filename(),                  module       :: module(),                  forms_or_bin, -                source       :: source(), +                source       :: source() | 'undefined',                  n_errors     :: non_neg_integer(),                  mode         :: mode(),                  exports_main :: boolean(), @@ -49,9 +49,9 @@  -type emu_args() :: string().  -record(sections, {type, -		   shebang  :: shebang(), -		   comment  :: comment(), -		   emu_args :: emu_args(), +		   shebang  :: shebang() | 'undefined', +		   comment  :: comment() | 'undefined', +		   emu_args :: emu_args() | 'undefined',  		   body}).  -record(extract_options, {compile_source}). diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 284f2e5a2b..5dc8b4541e 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -631,41 +631,20 @@ io_requests(Pid, [], [Rs|Cont], Tail) ->  io_requests(_Pid, [], [], _Tail) ->       {false,[]}. - -bc_req(Pid,{Op,Enc,Param},MaybeConvert) -> -    case net_kernel:dflag_unicode_io(Pid) of -	true -> -	    {false,{Op,Enc,Param}}; -	false -> -	    {MaybeConvert,{Op,Param}} -    end; -bc_req(Pid,{Op,Enc,P,F},MaybeConvert) -> -    case net_kernel:dflag_unicode_io(Pid) of -	true -> -	    {false,{Op,Enc,P,F}}; -	false -> -	    {MaybeConvert,{Op,P,F}} -    end; -bc_req(Pid, {Op,Enc,M,F,A},MaybeConvert) -> +bc_req(Pid, Req0, MaybeConvert) ->      case net_kernel:dflag_unicode_io(Pid) of  	true -> -	    {false,{Op,Enc,M,F,A}}; +	    %% The most common case. A modern i/o server. +	    {false,Req0};  	false -> -	    {MaybeConvert,{Op,M,F,A}} -    end; -bc_req(Pid, {Op,Enc,P,M,F,A},MaybeConvert) -> -    case net_kernel:dflag_unicode_io(Pid) of -	true -> -	    {false,{Op,Enc,P,M,F,A}}; -	false -> -	    {MaybeConvert,{Op,P,M,F,A}} -    end; -bc_req(Pid,{Op,Enc},MaybeConvert) -> -    case net_kernel:dflag_unicode_io(Pid) of -	true -> -	    {false,{Op, Enc}}; -	false -> -	    {MaybeConvert,Op} +	    %% Backward compatibility only. Unlikely to ever happen. +	    case tuple_to_list(Req0) of +		[Op,_Enc] -> +		    {MaybeConvert,Op}; +		[Op,_Enc|T] -> +		    Req = list_to_tuple([Op|T]), +		    {MaybeConvert,Req} +	    end      end.  io_request(Pid, {write,Term}) -> diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 2d77888512..90ef364d1a 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -586,49 +586,40 @@ obsolete_1(asn1rt, utf8_list_to_binary, 1) ->  %% Added in OTP 18.  obsolete_1(core_lib, get_anno, 1) -> -    {deprecated,{cerl,get_ann,1}}; +    {removed,{cerl,get_ann,1},"19"};  obsolete_1(core_lib, set_anno, 2) -> -    {deprecated,{cerl,set_ann,2}}; +    {removed,{cerl,set_ann,2},"19"};  obsolete_1(core_lib, is_literal, 1) -> -    {deprecated,{cerl,is_literal,1}}; +    {removed,{cerl,is_literal,1},"19"};  obsolete_1(core_lib, is_literal_list, 1) -> -    {deprecated,"deprecated; use lists:all(fun cerl:is_literal/1, L)" +    {removed,"removed; use lists:all(fun cerl:is_literal/1, L)"       " instead"};  obsolete_1(core_lib, literal_value, 1) -> -    {deprecated,{core_lib,concrete,1}}; +    {removed,{core_lib,concrete,1},"19"};  obsolete_1(erl_scan, set_attribute, 3) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_anno:set_line/2 instead"}; +    {removed,{erl_anno,set_line,2},"19.0"};  obsolete_1(erl_scan, attributes_info, 1) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_anno:{column,line,location,text}/1 instead"};  obsolete_1(erl_scan, attributes_info, 2) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_anno:{column,line,location,text}/1 instead"};  obsolete_1(erl_scan, token_info, 1) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_scan:{category,column,line,location,symbol,text}/1 instead"};  obsolete_1(erl_scan, token_info, 2) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_scan:{category,column,line,location,symbol,text}/1 instead"};  obsolete_1(erl_parse, set_line, 2) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_anno:set_line/2 instead"}; +    {removed,{erl_anno,set_line,2},"19.0"};  obsolete_1(erl_parse, get_attributes, 1) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_anno:{column,line,location,text}/1 instead"};  obsolete_1(erl_parse, get_attribute, 2) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use " +    {removed,"removed in 19.0; use "       "erl_anno:{column,line,location,text}/1 instead"};  obsolete_1(erl_lint, modify_line, 2) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_parse:map_anno/2 instead"}; +    {removed,{erl_parse,map_anno,2},"19.0"};  obsolete_1(ssl, negotiated_next_protocol, 1) ->      {deprecated,{ssl,negotiated_protocol,1}}; @@ -698,26 +689,24 @@ is_snmp_agent_function(_,		      _) -> false.  -spec obsolete_type(module(), atom(), arity()) ->  	'no' | {tag(), string()} | {tag(), mfas(), release()}. +-dialyzer({no_match, obsolete_type/3}).  obsolete_type(Module, Name, NumberOfVariables) ->      case obsolete_type_1(Module, Name, NumberOfVariables) of -%% 	{deprecated=Tag,{_,_,_}=Replacement} -> -%% 	    {Tag,Replacement,"in a future release"}; +	{deprecated=Tag,{_,_,_}=Replacement} -> +	    {Tag,Replacement,"in a future release"};  	{_,String}=Ret when is_list(String) ->  	    Ret; -%% 	{_,_,_}=Ret -> -%% 	    Ret; +	{_,_,_}=Ret -> +	    Ret;  	no ->  	    no      end.  obsolete_type_1(erl_scan,column,0) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_anno:column() instead"}; +    {removed,{erl_anno,column,0},"19.0"};  obsolete_type_1(erl_scan,line,0) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_anno:line() instead"}; +    {removed,{erl_anno,line,0},"19.0"};  obsolete_type_1(erl_scan,location,0) -> -    {deprecated, -     "deprecated (will be removed in OTP 19); use erl_anno:location() instead"}; +    {removed,{erl_anno,location,0},"19.0"};  obsolete_type_1(_,_,_) ->      no. diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index 24fc8ce204..4e629a5e56 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -289,10 +289,7 @@ register_unique_name(Number) ->  %% no need to use rsh.  mk_cmd(Host, Name, Args, Waiter, Prog0) -> -    Prog = case os:type() of -	       {ose,_} -> mk_ose_prog(Prog0); -	       _ -> quote_progname(Prog0) -	   end, +    Prog = quote_progname(Prog0),      BasicCmd = lists:concat([Prog,  			     " -detached -noinput -master ", node(),  			     " ", long_or_short(), Name, "@", Host, @@ -312,24 +309,6 @@ mk_cmd(Host, Name, Args, Waiter, Prog0) ->  	    end      end. -%% On OSE we have to pass the beam arguments directory to the slave -%% process. To find out what arguments that should be passed on we -%% make an assumption. All arguments after the last "--" should be -%% skipped. So given these arguments: -%%     -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' -- -name test@localhost -%% we send -%%     -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' -- -%% to the slave with whatever other args that are added in mk_cmd. -mk_ose_prog(Prog) -> -    SkipTail = fun("--",[]) -> -		       ["--"]; -		  (_,[]) -> -		       []; -		  (Arg,Args) -> -		       [Arg," "|Args] -	       end, -    [Prog,tl(lists:foldr(SkipTail,[],erlang:system_info(emu_args)))]. -  %% This is an attempt to distinguish between spaces in the program  %% path and spaces that separate arguments. The program is quoted to  %% allow spaces in the path. diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 92a0c29011..23f3aaee1f 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% Licensed under the Apache License, Version 2.0 (the "License");  %% you may not use this file except in compliance with the License. @@ -107,11 +107,13 @@  -define(SET, sets:set).  -record(state, {name, -		strategy               :: strategy(), +		strategy               :: strategy() | 'undefined',  		children = []          :: [child_rec()], -		dynamics               :: ?DICT(pid(), list()) | ?SET(pid()), -		intensity              :: non_neg_integer(), -		period                 :: pos_integer(), +                dynamics               :: {'dict', ?DICT(pid(), list())} +                                        | {'set', ?SET(pid())} +                                        | 'undefined', +		intensity              :: non_neg_integer() | 'undefined', +		period                 :: pos_integer() | 'undefined',  		restarts = [],  	        module,  	        args}). @@ -577,7 +579,7 @@ handle_cast({try_again_restart,Pid}, #state{children=[Child]}=State)    when ?is_simple(State) ->      RT = Child#child.restart_type,      RPid = restarting(Pid), -    case dynamic_child_args(RPid, dynamics_db(RT, State#state.dynamics)) of +    case dynamic_child_args(RPid, RT, State#state.dynamics) of  	{ok, Args} ->  	    {M, F, _} = Child#child.mfargs,  	    NChild = Child#child{pid = RPid, mfargs = {M, F, Args}}, @@ -735,7 +737,7 @@ handle_start_child(Child, State) ->  restart_child(Pid, Reason, #state{children = [Child]} = State) when ?is_simple(State) ->      RestartType = Child#child.restart_type, -    case dynamic_child_args(Pid, dynamics_db(RestartType, State#state.dynamics)) of +    case dynamic_child_args(Pid, RestartType, State#state.dynamics) of  	{ok, Args} ->  	    {M, F, _} = Child#child.mfargs,  	    NChild = Child#child{pid = Pid, mfargs = {M, F, Args}}, @@ -812,14 +814,16 @@ restart(simple_one_for_one, Child, State) ->  					       State#state.dynamics)),      case do_start_child_i(M, F, A) of  	{ok, Pid} -> -	    NState = State#state{dynamics = ?DICTS:store(Pid, A, Dynamics)}, +            DynamicsDb = {dict, ?DICTS:store(Pid, A, Dynamics)}, +	    NState = State#state{dynamics = DynamicsDb},  	    {ok, NState};  	{ok, Pid, _Extra} -> -	    NState = State#state{dynamics = ?DICTS:store(Pid, A, Dynamics)}, +            DynamicsDb = {dict, ?DICTS:store(Pid, A, Dynamics)}, +	    NState = State#state{dynamics = DynamicsDb},  	    {ok, NState};  	{error, Error} -> -	    NState = State#state{dynamics = ?DICTS:store(restarting(OldPid), A, -							Dynamics)}, +            DynamicsDb = {dict, ?DICTS:store(restarting(OldPid), A, Dynamics)}, +	    NState = State#state{dynamics = DynamicsDb},  	    report_error(start_error, Error, Child, State#state.name),  	    {try_again, NState}      end; @@ -1102,31 +1106,32 @@ save_child(Child, #state{children = Children} = State) ->      State#state{children = [Child |Children]}.  save_dynamic_child(temporary, Pid, _, #state{dynamics = Dynamics} = State) -> -    State#state{dynamics = ?SETS:add_element(Pid, dynamics_db(temporary, Dynamics))}; +    DynamicsDb = dynamics_db(temporary, Dynamics), +    State#state{dynamics = {set, ?SETS:add_element(Pid, DynamicsDb)}};  save_dynamic_child(RestartType, Pid, Args, #state{dynamics = Dynamics} = State) -> -    State#state{dynamics = ?DICTS:store(Pid, Args, dynamics_db(RestartType, Dynamics))}. +    DynamicsDb = dynamics_db(RestartType, Dynamics), +    State#state{dynamics = {dict, ?DICTS:store(Pid, Args, DynamicsDb)}}.  dynamics_db(temporary, undefined) ->      ?SETS:new();  dynamics_db(_, undefined) ->      ?DICTS:new(); -dynamics_db(_,Dynamics) -> -    Dynamics. - -dynamic_child_args(Pid, Dynamics) -> -    case ?SETS:is_set(Dynamics) of -        true -> -            {ok, undefined}; -        false -> -            ?DICTS:find(Pid, Dynamics) -    end. +dynamics_db(_, {_Tag, DynamicsDb}) -> +    DynamicsDb. + +dynamic_child_args(_Pid, temporary, _DynamicsDb) -> +    {ok, undefined}; +dynamic_child_args(Pid, _RT, {dict, DynamicsDb}) -> +    ?DICTS:find(Pid, DynamicsDb); +dynamic_child_args(_Pid, _RT, undefined) -> +    error.  state_del_child(#child{pid = Pid, restart_type = temporary}, State) when ?is_simple(State) ->      NDynamics = ?SETS:del_element(Pid, dynamics_db(temporary, State#state.dynamics)), -    State#state{dynamics = NDynamics}; +    State#state{dynamics = {set, NDynamics}};  state_del_child(#child{pid = Pid, restart_type = RType}, State) when ?is_simple(State) ->      NDynamics = ?DICTS:erase(Pid, dynamics_db(RType, State#state.dynamics)), -    State#state{dynamics = NDynamics}; +    State#state{dynamics = {dict, NDynamics}};  state_del_child(Child, State) ->      NChildren = del_child(Child#child.name, State#state.children),      State#state{children = NChildren}. @@ -1160,19 +1165,19 @@ split_child(_, [], After) ->  get_child(Name, State) ->      get_child(Name, State, false). +  get_child(Pid, State, AllowPid) when AllowPid, is_pid(Pid) ->      get_dynamic_child(Pid, State);  get_child(Name, State, _) ->      lists:keysearch(Name, #child.name, State#state.children).  get_dynamic_child(Pid, #state{children=[Child], dynamics=Dynamics}) -> -    DynamicsDb = dynamics_db(Child#child.restart_type, Dynamics), -    case is_dynamic_pid(Pid, DynamicsDb) of +    case is_dynamic_pid(Pid, Dynamics) of  	true ->  	    {value, Child#child{pid=Pid}};  	false ->  	    RPid = restarting(Pid), -	    case is_dynamic_pid(RPid, DynamicsDb) of +	    case is_dynamic_pid(RPid, Dynamics) of  		true ->  		    {value, Child#child{pid=RPid}};  		false -> @@ -1183,13 +1188,12 @@ get_dynamic_child(Pid, #state{children=[Child], dynamics=Dynamics}) ->  	    end      end. -is_dynamic_pid(Pid, Dynamics) -> -    case ?SETS:is_set(Dynamics) of -	true -> -	    ?SETS:is_element(Pid, Dynamics); -	false -> -	    ?DICTS:is_key(Pid, Dynamics) -    end. +is_dynamic_pid(Pid, {dict, Dynamics}) -> +    ?DICTS:is_key(Pid, Dynamics); +is_dynamic_pid(Pid, {set, Dynamics}) -> +    ?SETS:is_element(Pid, Dynamics); +is_dynamic_pid(_Pid, undefined) -> +    false.  replace_child(Child, State) ->      Chs = do_replace_child(Child, State#state.children), | 
