diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/beam_lib.erl | 9 | ||||
| -rw-r--r-- | lib/stdlib/src/dets.erl | 46 | ||||
| -rw-r--r-- | lib/stdlib/src/edlin.erl | 1 | ||||
| -rw-r--r-- | lib/stdlib/src/ets.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/file_sorter.erl | 22 | ||||
| -rw-r--r-- | lib/stdlib/src/otp_internal.erl | 3 | ||||
| -rw-r--r-- | lib/stdlib/src/qlc.erl | 14 | ||||
| -rw-r--r-- | lib/stdlib/src/stdlib.app.src | 2 | 
8 files changed, 63 insertions, 36 deletions
| diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 6e00401dce..00cd1221fa 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -931,7 +931,10 @@ call_crypto_server(Req) ->      end.  call_crypto_server_1(Req) -> -    {ok, _} = gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []), +    case gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []) of +	{ok, _} -> ok; +	{error, {already_started, _}} -> ok +    end,      erlang:yield(),      call_crypto_server(Req). @@ -972,9 +975,7 @@ handle_call({get_crypto_key, What}, From, #state{crypto_key_f=F}=S) ->  handle_call({crypto_key_fun, F}, {_,_} = From, S) ->      case S#state.crypto_key_f of  	undefined -> -	    %% Don't allow tuple funs here. (They weren't allowed before, -	    %% so there is no reason to allow them now.) -	    if is_function(F), is_function(F, 1) -> +	    if is_function(F, 1) ->  		    {Result, Fun, Reply} =   			case catch F(init) of  			    ok -> diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 7036316242..bf22949870 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -372,7 +372,7 @@ info(Tab) ->        Item :: 'access' | 'auto_save' | 'bchunk_format'              | 'hash' | 'file_size' | 'filename' | 'keypos' | 'memory'              | 'no_keys' | 'no_objects' | 'no_slots' | 'owner' | 'ram_file' -            | 'safe_fixed' | 'size' | 'type' | 'version', +            | 'safe_fixed' | 'safe_fixed_monotonic_time' | 'size' | 'type' | 'version',        Value :: term().  info(Tab, owner) -> @@ -1291,7 +1291,15 @@ init(Parent, Server) ->      open_file_loop(#head{parent = Parent, server = Server}).  open_file_loop(Head) -> -    open_file_loop(Head, 0). +    %% The Dets server pretends the file is open before +    %% internal_open() has been called, which means that unless the +    %% internal_open message is applied first, other processes can +    %% find the pid by calling dets_server:get_pid() and do things +    %% before Head has been initialized properly. +    receive +        ?DETS_CALL(From, {internal_open, _Ref, _Args}=Op) -> +            do_apply_op(Op, From, Head, 0) +    end.  open_file_loop(Head, N) when element(1, Head#head.update_mode) =:= error ->      open_file_loop2(Head, N); @@ -1966,7 +1974,9 @@ do_safe_fixtable(Head, Pid, true) ->      case Head#head.fixed of   	false ->   	    link(Pid), -	    Fixed = {utime_now(), [{Pid, 1}]}, +	    MonTime = erlang:monotonic_time(), +	    TimeOffset = erlang:time_offset(), +	    Fixed = {{MonTime, TimeOffset}, [{Pid, 1}]},  	    Ftab = dets_utils:get_freelists(Head),  	    Head#head{fixed = Fixed, freelists = {Ftab, Ftab}};  	{TimeStamp, Counters} -> @@ -2093,7 +2103,22 @@ finfo(H, no_keys) ->  finfo(H, no_slots) -> {H, (H#head.mod):no_slots(H)};  finfo(H, pid) -> {H, self()};  finfo(H, ram_file) -> {H, H#head.ram_file}; -finfo(H, safe_fixed) -> {H, H#head.fixed}; +finfo(H, safe_fixed) -> +    {H, +     case H#head.fixed of +	 false -> +	     false; +	 {{FixMonTime, TimeOffset}, RefList} -> +	     {make_timestamp(FixMonTime, TimeOffset), RefList} +     end}; +finfo(H, safe_fixed_monotonic_time) -> +    {H, +     case H#head.fixed of +	 false -> +	     false; +	 {{FixMonTime, _TimeOffset}, RefList} -> +	     {FixMonTime, RefList} +     end};  finfo(H, size) ->       case catch write_cache(H) of  	{H2, []} -> @@ -3277,11 +3302,14 @@ err(Error) ->  time_now() ->      erlang:monotonic_time(1000000). --compile({inline, [utime_now/0]}). -utime_now() -> -    Time = time_now(), -    UniqueCounter = erlang:unique_integer([monotonic]), -    {Time, UniqueCounter}. +make_timestamp(MonTime, TimeOffset) -> +    ErlangSystemTime = erlang:convert_time_unit(MonTime+TimeOffset, +						native, +						micro_seconds), +    MegaSecs = ErlangSystemTime div 1000000000000, +    Secs = ErlangSystemTime div 1000000 - MegaSecs*1000000, +    MicroSecs = ErlangSystemTime rem 1000000, +    {MegaSecs, Secs, MicroSecs}.  %%%%%%%%%%%%%%%%%  DEBUG functions %%%%%%%%%%%%%%%% diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 19444c0502..0e9c457de2 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -465,7 +465,6 @@ word_char(C) when C >= $a, C =< $z -> true;  word_char(C) when C >= $ß, C =< $ÿ, C =/= $÷ -> true;  word_char(C) when C >= $0, C =< $9 -> true;  word_char(C) when C =:= $_ -> true; -word_char(C) when C =:= $. -> true;    % accept dot-separated names  word_char(_) -> false.  %% over_white(Chars, InitialStack, InitialCount) -> diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index 847def2fd8..1fca3624dc 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -146,7 +146,7 @@ info(_) ->        Tab :: tab(),        Item :: compressed | fixed | heir | keypos | memory              | name | named_table | node | owner | protection -            | safe_fixed | size | stats | type +            | safe_fixed | safe_fixed_monotonic_time | size | stats | type  	    | write_concurrency | read_concurrency,        Value :: term(). diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl index 47adb133b0..aed857aa77 100644 --- a/lib/stdlib/src/file_sorter.erl +++ b/lib/stdlib/src/file_sorter.erl @@ -305,7 +305,6 @@ options(Option) ->  options([{format, Format} | L], Opts) when Format =:= binary;                                              Format =:= term; -                                           is_function(Format),                                             is_function(Format, 1) ->      options(L, Opts#opts{format = Format});  options([{format, binary_term} | L], Opts) -> @@ -324,7 +323,7 @@ options([{tmpdir, Dir} | L],  Opts) ->          FileName ->               options(L, Opts#opts{tmpdir = {dir, FileName}})      end; -options([{order, Fun} | L], Opts) when is_function(Fun), is_function(Fun, 2) -> +options([{order, Fun} | L], Opts) when is_function(Fun, 2) ->      options(L, Opts#opts{order = Fun});  options([{order, Order} | L], Opts) when Order =:= ascending;                                            Order =:= descending -> @@ -409,7 +408,7 @@ merge_terms_fun(RFun) ->              case RFun(read) of                  end_of_input ->                      eof; -                {Objs, NRFun} when is_function(NRFun), is_function(NRFun, 1) -> +                {Objs, NRFun} when is_function(NRFun, 1) ->                      {_, [], Ts, _} = fun_objs(Objs, [], 0, ?MAXSIZE, I, W),                      {{I, Ts, ?CHUNKSIZE}, merge_terms_fun(NRFun)};                  Error -> @@ -425,13 +424,12 @@ merge_bins_fun(FileName) ->              Fun(A)      end. -wrap_output_terms(term, OutFun, _Z) when is_function(OutFun), -                                         is_function(OutFun, 1) -> +wrap_output_terms(term, OutFun, _Z) when is_function(OutFun, 1) ->      {fun_wterms(OutFun), true};  wrap_output_terms(term, File, Z) when File =/= undefined ->      {file_wterms(name, File, Z++[write]), false};  wrap_output_terms(_Format, Output, _Z) -> -    {Output, is_function(Output) and is_function(Output, 1)}. +    {Output, is_function(Output, 1)}.  binary_term_fun() ->      fun binary_to_term/1. @@ -1309,8 +1307,7 @@ infun(W) ->              {end_of_input, W1};          {end_of_input, Value} ->              {end_of_input, W1#w{inout_value = {value, Value}}}; -        {Objs, NFun} when is_function(NFun),  -                          is_function(NFun, 1),  +        {Objs, NFun} when is_function(NFun, 1),                            is_list(Objs) ->              {cont, W#w{in = NFun}, Objs};          Error -> @@ -1333,7 +1330,7 @@ outfun(A, W) ->      try (W#w.out)(A) of          Reply when A =:= close ->              Reply; -        NF when is_function(NF), is_function(NF, 1) -> +        NF when is_function(NF, 1) ->              W#w{out = NF};          Error ->              error(Error, W1) @@ -1358,7 +1355,7 @@ is_keyposs([Bad | _]) ->  is_keyposs(Bad) ->      {badarg, Bad}. -is_input(Fun) when is_function(Fun), is_function(Fun, 1) -> +is_input(Fun) when is_function(Fun, 1) ->      {true, Fun};  is_input(Files) ->      is_files(Files). @@ -1378,7 +1375,7 @@ is_files([], L) ->  is_files(Bad, _L) ->      {badarg, Bad}. -maybe_output(Fun) when is_function(Fun), is_function(Fun, 1) -> +maybe_output(Fun) when is_function(Fun, 1) ->      {true, Fun};  maybe_output(File) ->      case read_file_info(File) of @@ -1587,7 +1584,6 @@ fun_rterms(InFun) ->         (read) ->              case InFun(read) of                  {Ts, NInFun} when is_list(Ts),  -                                  is_function(NInFun),                                    is_function(NInFun, 1) ->                      {to_bin(Ts, []), fun_rterms(NInFun)};                  Else -> @@ -1600,7 +1596,7 @@ fun_wterms(OutFun) ->              OutFun(close);         (L) ->              case OutFun(wterms_arg(L)) of -                NOutFun when is_function(NOutFun), is_function(NOutFun, 1) -> +                NOutFun when is_function(NOutFun, 1) ->                      fun_wterms(NOutFun);                  Else ->                      Else diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 960c70f255..bc70c296da 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -647,6 +647,9 @@ obsolete_1(random, _, _) ->  obsolete_1(code, rehash, 0) ->      {deprecated, "deprecated because the code path cache feature has been removed"}; +obsolete_1(overload, _, _) -> +    {deprecated, "deprecated; will be removed in OTP 19"}; +  obsolete_1(_, _, _) ->      no. diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index 3ba3a88038..24e64efee7 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -808,21 +808,21 @@ options(Options0, [Key | Keys], L) when is_list(Options0) ->                  {ok, U};              {pre_fun, U=undefined} ->                  {ok, U}; -            {info_fun, Fun} when is_function(Fun), is_function(Fun, 1) -> +            {info_fun, Fun} when is_function(Fun, 1) ->                  {ok, Fun}; -            {pre_fun, Fun} when is_function(Fun), is_function(Fun, 1) -> +            {pre_fun, Fun} when is_function(Fun, 1) ->                  {ok, Fun}; -            {post_fun, Fun} when is_function(Fun), is_function(Fun, 0) -> +            {post_fun, Fun} when is_function(Fun, 0) ->                  {ok, Fun}; -            {lookup_fun, Fun} when is_function(Fun), is_function(Fun, 2) -> +            {lookup_fun, Fun} when is_function(Fun, 2) ->                  {ok, Fun};              {max_lookup, Max} when is_integer(Max), Max >= 0 ->                  {ok, Max};              {max_lookup, infinity} ->                  {ok, -1}; -            {format_fun, Fun} when is_function(Fun), is_function(Fun, 1) -> +            {format_fun, Fun} when is_function(Fun, 1) ->                  {ok, Fun}; -            {parent_fun, Fun} when is_function(Fun), is_function(Fun, 0) -> +            {parent_fun, Fun} when is_function(Fun, 0) ->                  {ok, Fun};              {key_equality, KE='=='} ->                  {ok, KE}; @@ -885,7 +885,7 @@ options(Options0, [Key | Keys], L) when is_list(Options0) ->              {depth, Depth} when Depth =:= infinity;                                  is_integer(Depth), Depth >= 0 ->                  {ok, Depth}; -            {order, Order} when is_function(Order), is_function(Order, 2); +            {order, Order} when is_function(Order, 2);                                  (Order =:= ascending);                                  (Order =:= descending) ->                  {ok, Order}; diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 7f9bbbf649..b8a7973cf2 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -105,7 +105,7 @@                 dets]},    {applications, [kernel]},    {env, []}, -  {runtime_dependencies, ["sasl-2.6","kernel-4.1","erts-7.0","crypto-3.3", +  {runtime_dependencies, ["sasl-2.6","kernel-4.1","erts-7.3","crypto-3.3",  			  "compiler-5.0"]}  ]}. | 
