diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/edlin.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 14 | ||||
-rw-r--r-- | lib/stdlib/src/erl_pp.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/erl_scan.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/filelib.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/gen_event.erl | 48 | ||||
-rw-r--r-- | lib/stdlib/src/gen_fsm.erl | 49 | ||||
-rw-r--r-- | lib/stdlib/src/gen_server.erl | 51 | ||||
-rw-r--r-- | lib/stdlib/src/maps.erl | 17 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 14 | ||||
-rw-r--r-- | lib/stdlib/src/proc_lib.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/src/shell.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 2 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 4 |
14 files changed, 133 insertions, 98 deletions
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index be9a4f5107..b3bc5f6d92 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -390,7 +390,7 @@ do_op(end_of_line, Bef, [C|Aft], Rs) -> do_op(end_of_line, Bef, [], Rs) -> {{Bef,[]},Rs}; do_op(ctlu, Bef, Aft, Rs) -> - put(kill_buffer, Bef), + put(kill_buffer, reverse(Bef)), {{[], Aft}, [{delete_chars, -length(Bef)} | Rs]}; do_op(beep, Bef, Aft, Rs) -> {{Bef,Aft},[beep|Rs]}; diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index e1ae3b7aea..1d4a2a1fef 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -753,6 +753,9 @@ attribute_farity({cons,L,H,T}) -> attribute_farity({tuple,L,Args0}) -> Args = attribute_farity_list(Args0), {tuple,L,Args}; +attribute_farity({map,L,Args0}) -> + Args = attribute_farity_map(Args0), + {map,L,Args}; attribute_farity({op,L,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) -> {tuple,L,[Name,Arity]}; attribute_farity(Other) -> Other. @@ -760,6 +763,10 @@ attribute_farity(Other) -> Other. attribute_farity_list(Args) -> [attribute_farity(A) || A <- Args]. +%% It is not meaningful to have farity keys. +attribute_farity_map(Args) -> + [{Op,L,K,attribute_farity(V)} || {Op,L,K,V} <- Args]. + -spec error_bad_decl(integer(), attributes()) -> no_return(). error_bad_decl(L, S) -> @@ -954,7 +961,9 @@ abstract([H|T], L, none=E) -> abstract(List, L, E) when is_list(List) -> abstract_list(List, [], L, E); abstract(Tuple, L, E) when is_tuple(Tuple) -> - {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)}. + {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)}; +abstract(Map, L, E) when is_map(Map) -> + {map,L,abstract_map_fields(maps:to_list(Map),L,E)}. abstract_list([H|T], String, L, E) -> case is_integer(H) andalso H >= 0 andalso E(H) of @@ -979,6 +988,9 @@ abstract_tuple_list([H|T], L, E) -> abstract_tuple_list([], _L, _E) -> []. +abstract_map_fields(Fs,L,E) -> + [{map_field_assoc,L,abstract(K,L,E),abstract(V,L,E)}||{K,V}<-Fs]. + abstract_byte(Byte, L) when is_integer(Byte) -> {bin_element, L, {integer, L, Byte}, default, default}; abstract_byte(Bits, L) -> diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 82bc2c1460..1fd6d2a8df 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -300,7 +300,15 @@ map_pair_types(Fs) -> tuple_type(Fs, fun map_pair_type/1). map_pair_type({type,_Line,map_field_assoc,Ktype,Vtype}) -> - {seq,[],[]," =>",[ltype(Ktype),ltype(Vtype)]}. + map_assoc_typed(ltype(Ktype), Vtype). + +map_assoc_typed(B, {type,_,union,Ts}) -> + {first,[B,$\s],{seq,[],[],[],map_assoc_union_type(Ts)}}; +map_assoc_typed(B, Type) -> + {list,[{cstep,[B," =>"],ltype(Type)}]}. + +map_assoc_union_type([T|Ts]) -> + [[leaf("=> "),ltype(T)] | ltypes(Ts, fun union_elem/1)]. record_type(Name, Fields) -> {first,[record_name(Name)],field_types(Fields)}. diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index ae59d5f44f..6fd6bb888b 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1075,7 +1075,7 @@ scan_number([$#|Cs]=Cs0, St, Line, Col, Toks, Ncs0) -> Ncs = lists:reverse(Ncs0), case catch list_to_integer(Ncs) of B when B >= 2, B =< 1+$Z-$A+10 -> - Bcs = ?STR(St, Ncs++[$#]), + Bcs = Ncs++[$#], scan_based_int(Cs, St, Line, Col, Toks, {B,[],Bcs}); B -> Len = length(Ncs), @@ -1108,7 +1108,7 @@ scan_based_int(Cs, St, Line, Col, Toks, {B,Ncs0,Bcs}) -> Ncs = lists:reverse(Ncs0), case catch erlang:list_to_integer(Ncs, B) of N when is_integer(N) -> - tok3(Cs, St, Line, Col, Toks, integer, ?STR(St, Bcs++Ncs), N); + tok3(Cs, St, Line, Col, Toks, integer, Bcs++Ncs, N); _ -> Len = length(Bcs)+length(Ncs), Ncol = incr_column(Col, Len), diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index 9efbe8da20..daae1fd2d2 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -371,7 +371,7 @@ compile_wildcard(Pattern, Cwd0) -> [Root|Rest] = filename:split(Pattern), case filename:pathtype(Root) of relative -> - Cwd = filename:join([Cwd0]), + Cwd = prepare_base(Cwd0), compile_wildcard_2([Root|Rest], {cwd,Cwd}); _ -> compile_wildcard_2(Rest, {root,0,Root}) diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index d39dd89d3a..469acdc37c 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -49,8 +49,6 @@ -import(error_logger, [error_msg/2]). --define(reply(X), From ! {element(2,Tag), X}). - -record(handler, {module :: atom(), id = false, state, @@ -249,49 +247,49 @@ handle_msg(Msg, Parent, ServerName, MSL, Debug) -> {notify, Event} -> {Hib,MSL1} = server_notify(Event, handle_event, MSL, ServerName), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, {sync_notify, Event}} -> + {_From, Tag, {sync_notify, Event}} -> {Hib, MSL1} = server_notify(Event, handle_event, MSL, ServerName), - ?reply(ok), + reply(Tag, ok), loop(Parent, ServerName, MSL1, Debug, Hib); {'EXIT', From, Reason} -> MSL1 = handle_exit(From, Reason, MSL, ServerName), loop(Parent, ServerName, MSL1, Debug, false); - {From, Tag, {call, Handler, Query}} -> + {_From, Tag, {call, Handler, Query}} -> {Hib, Reply, MSL1} = server_call(Handler, Query, MSL, ServerName), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, {add_handler, Handler, Args}} -> + {_From, Tag, {add_handler, Handler, Args}} -> {Hib, Reply, MSL1} = server_add_handler(Handler, Args, MSL), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, {add_sup_handler, Handler, Args, SupP}} -> + {_From, Tag, {add_sup_handler, Handler, Args, SupP}} -> {Hib, Reply, MSL1} = server_add_sup_handler(Handler, Args, MSL, SupP), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, {delete_handler, Handler, Args}} -> + {_From, Tag, {delete_handler, Handler, Args}} -> {Reply, MSL1} = server_delete_handler(Handler, Args, MSL, ServerName), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, false); - {From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} -> + {_From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} -> {Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, ServerName), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2, + {_From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2, Sup}} -> {Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, Sup, ServerName), - ?reply(Reply), + reply(Tag, Reply), loop(Parent, ServerName, MSL1, Debug, Hib); - {From, Tag, stop} -> + {_From, Tag, stop} -> catch terminate_server(normal, Parent, MSL, ServerName), - ?reply(ok); - {From, Tag, which_handlers} -> - ?reply(the_handlers(MSL)), + reply(Tag, ok); + {_From, Tag, which_handlers} -> + reply(Tag, the_handlers(MSL)), loop(Parent, ServerName, MSL, Debug, false); - {From, Tag, get_modules} -> - ?reply(get_modules(MSL)), + {_From, Tag, get_modules} -> + reply(Tag, get_modules(MSL)), loop(Parent, ServerName, MSL, Debug, false); Other -> {Hib, MSL1} = server_notify(Other, handle_info, MSL, ServerName), @@ -303,6 +301,10 @@ terminate_server(Reason, Parent, MSL, ServerName) -> do_unlink(Parent, MSL), exit(Reason). +reply({From, Ref}, Msg) -> + From ! {Ref, Msg}, + ok. + %% unlink the supervisor process of all supervised handlers. %% We do not want a handler supervisor to EXIT due to the %% termination of the event manager (server). diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index e914f7d0b2..5afe3e8b09 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -594,7 +594,8 @@ reply(Name, {To, Tag}, Reply, Debug, StateName) -> terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> case catch Mod:terminate(Reason, StateName, StateData) of {'EXIT', R} -> - error_info(R, Name, Msg, StateName, StateData, Debug), + FmtStateData = format_status(terminate, Mod, get(), StateData), + error_info(R, Name, Msg, StateName, FmtStateData, Debug), exit(R); _ -> case Reason of @@ -605,17 +606,7 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> {shutdown,_}=Shutdown -> exit(Shutdown); _ -> - FmtStateData = - case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [get(), StateData], - case catch Mod:format_status(terminate, Args) of - {'EXIT', _} -> StateData; - Else -> Else - end; - _ -> - StateData - end, + FmtStateData = format_status(terminate, Mod, get(), StateData), error_info(Reason,Name,Msg,StateName,FmtStateData,Debug), exit(Reason) end @@ -680,21 +671,29 @@ format_status(Opt, StatusData) -> Header = gen:format_status_header("Status for state machine", Name), Log = sys:get_debug(log, Debug, []), - DefaultStatus = [{data, [{"StateData", StateData}]}], - Specfic = - case erlang:function_exported(Mod, format_status, 2) of - true -> - case catch Mod:format_status(Opt,[PDict,StateData]) of - {'EXIT', _} -> DefaultStatus; - StatusList when is_list(StatusList) -> StatusList; - Else -> [Else] - end; - _ -> - DefaultStatus - end, + Specfic = format_status(Opt, Mod, PDict, StateData), + Specfic = case format_status(Opt, Mod, PDict, StateData) of + S when is_list(S) -> S; + S -> [S] + end, [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}, {"Logged events", Log}, {"StateName", StateName}]} | Specfic]. + +format_status(Opt, Mod, PDict, State) -> + DefStatus = case Opt of + terminate -> State; + _ -> [{data, [{"StateData", State}]}] + end, + case erlang:function_exported(Mod, format_status, 2) of + true -> + case catch Mod:format_status(Opt, [PDict, State]) of + {'EXIT', _} -> DefStatus; + Else -> Else + end; + _ -> + DefStatus + end. diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 202a931fae..dadfe56b3d 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -720,7 +720,8 @@ print_event(Dev, Event, Name) -> terminate(Reason, Name, Msg, Mod, State, Debug) -> case catch Mod:terminate(Reason, State) of {'EXIT', R} -> - error_info(R, Name, Msg, State, Debug), + FmtState = format_status(terminate, Mod, get(), State), + error_info(R, Name, Msg, FmtState, Debug), exit(R); _ -> case Reason of @@ -731,17 +732,7 @@ terminate(Reason, Name, Msg, Mod, State, Debug) -> {shutdown,_}=Shutdown -> exit(Shutdown); _ -> - FmtState = - case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [get(), State], - case catch Mod:format_status(terminate, Args) of - {'EXIT', _} -> State; - Else -> Else - end; - _ -> - State - end, + FmtState = format_status(terminate, Mod, get(), State), error_info(Reason, Name, Msg, FmtState, Debug), exit(Reason) end @@ -875,23 +866,29 @@ name_to_pid(Name) -> %%----------------------------------------------------------------- format_status(Opt, StatusData) -> [PDict, SysState, Parent, Debug, [Name, State, Mod, _Time]] = StatusData, - Header = gen:format_status_header("Status for generic server", - Name), + Header = gen:format_status_header("Status for generic server", Name), Log = sys:get_debug(log, Debug, []), - DefaultStatus = [{data, [{"State", State}]}], - Specfic = - case erlang:function_exported(Mod, format_status, 2) of - true -> - case catch Mod:format_status(Opt, [PDict, State]) of - {'EXIT', _} -> DefaultStatus; - StatusList when is_list(StatusList) -> StatusList; - Else -> [Else] - end; - _ -> - DefaultStatus - end, + Specfic = case format_status(Opt, Mod, PDict, State) of + S when is_list(S) -> S; + S -> [S] + end, [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}, {"Logged events", Log}]} | Specfic]. + +format_status(Opt, Mod, PDict, State) -> + DefStatus = case Opt of + terminate -> State; + _ -> [{data, [{"State", State}]}] + end, + case erlang:function_exported(Mod, format_status, 2) of + true -> + case catch Mod:format_status(Opt, [PDict, State]) of + {'EXIT', _} -> DefStatus; + Else -> Else + end; + _ -> + DefStatus + end. diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl index 4ef1638e6d..ba4d6a5c87 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -24,6 +24,7 @@ map/2, size/1, without/2, + with/2, get/3 ]). @@ -133,10 +134,10 @@ to_list(_) -> erlang:nif_error(undef). update(_,_,_) -> erlang:nif_error(undef). --spec values(Map) -> Keys when +-spec values(Map) -> Values when Map :: map(), - Keys :: [Key], - Key :: term(). + Values :: [Value], + Value :: term(). values(_) -> erlang:nif_error(undef). @@ -201,3 +202,13 @@ size(Map) when is_map(Map) -> without(Ks, M) when is_list(Ks), is_map(M) -> maps:from_list([{K,V}||{K,V} <- maps:to_list(M), not lists:member(K, Ks)]). + + +-spec with(Ks, Map1) -> Map2 when + Ks :: [K], + Map1 :: map(), + Map2 :: map(), + K :: term(). + +with(Ks, M) when is_list(Ks), is_map(M) -> + maps:from_list([{K,V}||{K,V} <- maps:to_list(M), lists:member(K, Ks)]). diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index c0ee8799c8..6c25beabe9 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -421,13 +421,13 @@ obsolete_1(ssh_cm, stop_listener, 1) -> obsolete_1(ssh_cm, session_open, A) when A =:= 2; A =:= 4 -> {removed,{ssh_connection,session_channel,A},"R14B"}; obsolete_1(ssh_cm, direct_tcpip, A) when A =:= 6; A =:= 8 -> - {removed,{ssh_connection,direct_tcpip,A}}; + {removed,{ssh_connection,direct_tcpip,A},"R14B"}; obsolete_1(ssh_cm, tcpip_forward, 3) -> {removed,{ssh_connection,tcpip_forward,3},"R14B"}; obsolete_1(ssh_cm, cancel_tcpip_forward, 3) -> {removed,{ssh_connection,cancel_tcpip_forward,3},"R14B"}; obsolete_1(ssh_cm, open_pty, A) when A =:= 3; A =:= 7; A =:= 9 -> - {removed,{ssh_connection,open_pty,A},"R14"}; + {removed,{ssh_connection,open_pty,A},"R14B"}; obsolete_1(ssh_cm, setenv, 5) -> {removed,{ssh_connection,setenv,5},"R14B"}; obsolete_1(ssh_cm, shell, 2) -> @@ -441,11 +441,11 @@ obsolete_1(ssh_cm, winch, A) when A =:= 4; A =:= 6 -> obsolete_1(ssh_cm, signal, 3) -> {removed,{ssh_connection,signal,3},"R14B"}; obsolete_1(ssh_cm, attach, A) when A =:= 2; A =:= 3 -> - {removed,{ssh,attach,A}}; + {removed,"no longer useful; removed in R14B"}; obsolete_1(ssh_cm, detach, 2) -> - {removed,"no longer useful; will be removed in R14B"}; + {removed,"no longer useful; removed in R14B"}; obsolete_1(ssh_cm, set_user_ack, 4) -> - {removed,"no longer useful; will be removed in R14B"}; + {removed,"no longer useful; removed in R14B"}; obsolete_1(ssh_cm, adjust_window, 3) -> {removed,{ssh_connection,adjust_window,3},"R14B"}; obsolete_1(ssh_cm, close, 2) -> @@ -461,9 +461,9 @@ obsolete_1(ssh_cm, send_ack, A) when 3 =< A, A =< 5 -> obsolete_1(ssh_ssh, connect, A) when 1 =< A, A =< 3 -> {removed,{ssh,shell,A},"R14B"}; obsolete_1(ssh_sshd, listen, A) when 0 =< A, A =< 3 -> - {removed,{ssh,daemon,[1,2,3]},"R14"}; + {removed,{ssh,daemon,[1,2,3]},"R14B"}; obsolete_1(ssh_sshd, stop, 1) -> - {removed,{ssh,stop_listener,1}}; + {removed,{ssh,stop_listener,1},"R14B"}; %% Added in R13A. obsolete_1(regexp, _, _) -> diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 1eb6fc2e86..bf2a4e7ac5 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -216,10 +216,8 @@ ensure_link(SpawnOpts) -> init_p(Parent, Ancestors, Fun) when is_function(Fun) -> put('$ancestors', [Parent|Ancestors]), - {module,Mod} = erlang:fun_info(Fun, module), - {name,Name} = erlang:fun_info(Fun, name), - {arity,Arity} = erlang:fun_info(Fun, arity), - put('$initial_call', {Mod,Name,Arity}), + Mfa = erlang:fun_info_mfa(Fun), + put('$initial_call', Mfa), try Fun() catch diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 3b90542452..679c13f0cf 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -371,6 +371,14 @@ expand_expr({bc,L,E,Qs}, C) -> {bc,L,expand_expr(E, C),expand_quals(Qs, C)}; expand_expr({tuple,L,Elts}, C) -> {tuple,L,expand_exprs(Elts, C)}; +expand_expr({map,L,Es}, C) -> + {map,L,expand_exprs(Es, C)}; +expand_expr({map,L,Arg,Es}, C) -> + {map,L,expand_expr(Arg, C),expand_exprs(Es, C)}; +expand_expr({map_field_assoc,L,K,V}, C) -> + {map_field_assoc,L,expand_expr(K, C),expand_expr(V, C)}; +expand_expr({map_field_exact,L,K,V}, C) -> + {map_field_exact,L,expand_expr(K, C),expand_expr(V, C)}; expand_expr({record_index,L,Name,F}, C) -> {record_index,L,Name,expand_expr(F, C)}; expand_expr({record,L,Name,Is}, C) -> diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 3585eec342..aa9899da3b 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -103,7 +103,7 @@ dets]}, {applications, [kernel]}, {env, []}, - {runtime_dependencies, ["sasl-2.4","kernel-3.0.2","erts-6.1.2","crypto-3.3", + {runtime_dependencies, ["sasl-2.4","kernel-3.0.2","erts-6.2","crypto-3.3", "compiler-5.0"]} ]}. diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 99d9b8b431..7802ea884f 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -17,11 +17,11 @@ %% %CopyrightEnd% {"%VSN%", %% Up from - max one major revision back - [{<<"2\\.1(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1 + [{<<"2\\.[1-2](\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1-17.3 {<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.0 {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R16 %% Down to - max one major revision back - [{<<"2\\.1(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1 + [{<<"2\\.[1-2](\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1-17.3 {<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.0 {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R16 }. |