aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/calendar.erl94
-rw-r--r--lib/stdlib/src/erl_parse.yrl7
-rw-r--r--lib/stdlib/src/erl_pp.erl4
-rw-r--r--lib/stdlib/src/erl_tar.erl4
-rw-r--r--lib/stdlib/src/gen_statem.erl230
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl46
-rw-r--r--lib/stdlib/src/ms_transform.erl4
-rw-r--r--lib/stdlib/src/stdlib.appup.src10
8 files changed, 206 insertions, 193 deletions
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index bb5d450cd6..3a8fe2211b 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -357,13 +357,17 @@ rfc3339_to_system_time(DateTimeString) ->
rfc3339_to_system_time(DateTimeString, Options) ->
Unit = proplists:get_value(unit, Options, second),
%% _T is the character separating the date and the time:
- {DateStr, [_T|TimeStr]} = lists:split(10, DateTimeString),
- {TimeStr2, TimeStr3} = lists:split(8, TimeStr),
- {ok, [Hour, Min, Sec], []} = io_lib:fread("~d:~d:~d", TimeStr2),
- {ok, [Year, Month, Day], []} = io_lib:fread("~d-~d-~d", DateStr),
+ [Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
+ H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString,
+ Hour = list_to_integer([H1, H2]),
+ Min = list_to_integer([Min1, Min2]),
+ Sec = list_to_integer([S1, S2]),
+ Year = list_to_integer([Y1, Y2, Y3, Y4]),
+ Month = list_to_integer([Mon1, Mon2]),
+ Day = list_to_integer([D1, D2]),
DateTime = {{Year, Month, Day}, {Hour, Min, Sec}},
IsFractionChar = fun(C) -> C >= $0 andalso C =< $9 orelse C =:= $. end,
- {FractionStr, UtcOffset} = lists:splitwith(IsFractionChar, TimeStr3),
+ {FractionStr, UtcOffset} = lists:splitwith(IsFractionChar, TimeStr),
Time = datetime_to_system_time(DateTime),
Secs = Time - offset_adjustment(Time, second, UtcOffset),
check(DateTimeString, Options, Secs),
@@ -451,8 +455,9 @@ system_time_to_rfc3339(Time, Options) ->
DateTime = system_time_to_datetime(Secs),
{{Year, Month, Day}, {Hour, Min, Sec}} = DateTime,
FractionStr = fraction_str(Factor, AdjustedTime),
- flat_fwrite("~4.10.0B-~2.10.0B-~2.10.0B~c~2.10.0B:~2.10.0B:~2.10.0B~s~s",
- [Year, Month, Day, T, Hour, Min, Sec, FractionStr, Offset]).
+ L = [pad4(Year), "-", pad2(Month), "-", pad2(Day), [T],
+ pad2(Hour), ":", pad2(Min), ":", pad2(Sec), FractionStr, Offset],
+ lists:append(L).
%% time_difference(T1, T2) = Tdiff
%%
@@ -529,24 +534,41 @@ valid_date({Y, M, D}) ->
%% day_to_year(DayOfEpoch) = {Year, DayOfYear}
%%
-%% The idea here is to first guess a year, and then adjust. Although
-%% the implementation is recursive, at most 1 or 2 recursive steps
+%% The idea here is to first set the upper and lower bounds for a year,
+%% and then adjust a range by interpolation search. Although complexity
+%% of the algorithm is log(log(n)), at most 1 or 2 recursive steps
%% are taken.
-%% If DayOfEpoch is very large, we need far more than 1 or 2 iterations,
-%% since we just subtract a yearful of days at a time until we're there.
%%
-spec day_to_year(non_neg_integer()) -> {year(), day_of_year()}.
day_to_year(DayOfEpoch) when DayOfEpoch >= 0 ->
- Y0 = DayOfEpoch div ?DAYS_PER_YEAR,
- {Y1, D1} = dty(Y0, DayOfEpoch, dy(Y0)),
+ YMax = DayOfEpoch div ?DAYS_PER_YEAR,
+ YMin = DayOfEpoch div ?DAYS_PER_LEAP_YEAR,
+ {Y1, D1} = dty(YMin, YMax, DayOfEpoch, dy(YMin), dy(YMax)),
{Y1, DayOfEpoch - D1}.
--spec dty(year(), non_neg_integer(), non_neg_integer()) ->
+-spec dty(year(), year(), non_neg_integer(), non_neg_integer(),
+ non_neg_integer()) ->
{year(), non_neg_integer()}.
-dty(Y, D1, D2) when D1 < D2 ->
- dty(Y-1, D1, dy(Y-1));
-dty(Y, _D1, D2) ->
- {Y, D2}.
+dty(Min, Max, _D1, DMin, _DMax) when Min == Max ->
+ {Min, DMin};
+dty(Min, Max, D1, DMin, DMax) ->
+ Diff = Max - Min,
+ Mid = Min + (Diff * (D1 - DMin)) div (DMax - DMin),
+ MidLength =
+ case is_leap_year(Mid) of
+ true -> ?DAYS_PER_LEAP_YEAR;
+ false -> ?DAYS_PER_YEAR
+ end,
+ case dy(Mid) of
+ D2 when D1 < D2 ->
+ NewMax = Mid - 1,
+ dty(Min, NewMax, D1, DMin, dy(NewMax));
+ D2 when D1 - D2 >= MidLength ->
+ NewMin = Mid + 1,
+ dty(NewMin, Max, D1, dy(NewMin), DMax);
+ D2 ->
+ {Mid, D2}
+ end.
%%
%% The Gregorian days of the iso week 01 day 1 for a given year.
@@ -663,7 +685,7 @@ offset(OffsetOption, Secs0) when OffsetOption =:= "";
Secs = abs(Secs0),
Hour = Secs div 3600,
Min = (Secs rem 3600) div 60,
- io_lib:fwrite("~c~2.10.0B:~2.10.0B", [Sign, Hour, Min]);
+ [Sign | lists:append([pad2(Hour), ":", pad2(Min)])];
offset(OffsetOption, _Secs) ->
OffsetOption.
@@ -678,8 +700,10 @@ offset_string_adjustment(_Time, _Unit, "Z") ->
0;
offset_string_adjustment(_Time, _Unit, "z") ->
0;
-offset_string_adjustment(_Time, _Unit, [Sign|Tz]) ->
- {ok, [Hour, Min], []} = io_lib:fread("~d:~d", Tz),
+offset_string_adjustment(_Time, _Unit, Tz) ->
+ [Sign, H1, H2, $:, M1, M2] = Tz,
+ Hour = list_to_integer([H1, H2]),
+ Min = list_to_integer([M1, M2]),
Adjustment = 3600 * Hour + 60 * Min,
case Sign of
$- -> -Adjustment;
@@ -687,8 +711,9 @@ offset_string_adjustment(_Time, _Unit, [Sign|Tz]) ->
end.
local_offset(SystemTime, Unit) ->
- LocalTime = system_time_to_local_time(SystemTime, Unit),
+ %% Not optimized for special cases.
UniversalTime = system_time_to_universal_time(SystemTime, Unit),
+ LocalTime = erlang:universaltime_to_localtime(UniversalTime),
LocalSecs = datetime_to_gregorian_seconds(LocalTime),
UniversalSecs = datetime_to_gregorian_seconds(UniversalTime),
LocalSecs - UniversalSecs.
@@ -697,7 +722,8 @@ fraction_str(1, _Time) ->
"";
fraction_str(Factor, Time) ->
Fraction = Time rem Factor,
- io_lib:fwrite(".~*..0B", [log10(Factor), abs(Fraction)]).
+ S = integer_to_list(abs(Fraction)),
+ [$. | pad(log10(Factor) - length(S), S)].
fraction(second, _) ->
0;
@@ -718,5 +744,21 @@ log10(1000) -> 3;
log10(1000000) -> 6;
log10(1000000000) -> 9.
-flat_fwrite(F, S) ->
- lists:flatten(io_lib:fwrite(F, S)).
+pad(0, S) ->
+ S;
+pad(I, S) ->
+ [$0 | pad(I - 1, S)].
+
+pad2(N) when N < 10 ->
+ [$0 | integer_to_list(N)];
+pad2(N) ->
+ integer_to_list(N).
+
+pad4(N) when N < 10 ->
+ [$0, $0, $0 | integer_to_list(N)];
+pad4(N) when N < 100 ->
+ [$0, $0 | integer_to_list(N)];
+pad4(N) when N < 1000 ->
+ [$0 | integer_to_list(N)];
+pad4(N) ->
+ integer_to_list(N).
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 9602f0bcd9..5fa9c4f75c 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -872,7 +872,7 @@ Erlang code.
-type af_fun_type() :: {'type', anno(), 'fun', []}
| {'type', anno(), 'fun', [{'type', anno(), 'any'} |
abstract_type()]}
- | {'type', anno(), 'fun', af_function_type()}.
+ | af_function_type().
-type af_integer_range_type() ::
{'type', anno(), 'range', [af_singleton_integer_type()]}.
@@ -924,10 +924,11 @@ Erlang code.
-type af_function_constraint() :: [af_constraint()].
-type af_constraint() :: {'type', anno(), 'constraint',
- af_lit_atom('is_subtype'),
- [af_type_variable() | abstract_type()]}. % [V, T]
+ [af_lit_atom('is_subtype') |
+ [af_type_variable() | abstract_type()]]}. % [IsSubtype, [V, T]]
-type af_singleton_integer_type() :: af_integer()
+ | af_character()
| af_unary_op(af_singleton_integer_type())
| af_binary_op(af_singleton_integer_type()).
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index dd302a2880..ada3ff5de3 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -697,6 +697,8 @@ fun_info(Extra) ->
%% BITS:
+bit_grp([], _Opts) ->
+ leaf("<<>>");
bit_grp(Fs, Opts) ->
append([['<<'], [bit_elems(Fs, Opts)], ['>>']]).
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index d8b8f466b1..7064fcacfa 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -324,7 +324,7 @@ do_open(Name, Mode) when is_list(Mode) ->
open1({binary,Bin}, read, _Raw, Opts) when is_binary(Bin) ->
case file:open(Bin, [ram,binary,read]) of
{ok,File} ->
- _ = [ram_file:uncompress(File) || Opts =:= [compressed]],
+ _ = [ram_file:uncompress(File) || lists:member(compressed, Opts)],
{ok, #reader{handle=File,access=read,func=fun file_op/2}};
Error ->
Error
@@ -357,7 +357,7 @@ open_mode([read|Rest], false, Raw, Opts) ->
open_mode([write|Rest], false, Raw, Opts) ->
open_mode(Rest, write, Raw, Opts);
open_mode([compressed|Rest], Access, Raw, Opts) ->
- open_mode(Rest, Access, Raw, [compressed|Opts]);
+ open_mode(Rest, Access, Raw, [compressed,read_ahead|Opts]);
open_mode([cooked|Rest], Access, _Raw, Opts) ->
open_mode(Rest, Access, [], Opts);
open_mode([], Access, Raw, Opts) ->
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index faa43fbc1e..8965af253b 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2016-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2016-2019. 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.
@@ -398,17 +398,11 @@ timeout_event_type(Type) ->
data :: term(),
postponed = [] :: [{event_type(),term()}],
%%
- timer_refs = #{} :: % timer ref => the timer's event type
- #{reference() => timeout_event_type()},
- timer_types = #{} :: % timer's event type => timer ref
- #{timeout_event_type() => reference()},
- cancel_timers = 0 :: non_neg_integer(),
- %% We add a timer to both timer_refs and timer_types
- %% when we start it. When we request an asynchronous
- %% timer cancel we remove it from timer_types. When
- %% the timer cancel message arrives we remove it from
- %% timer_refs.
- %%
+ timers = {#{},#{}} ::
+ {%% timer ref => the timer's event type
+ TimerRefs :: #{reference() => timeout_event_type()},
+ %% timer's event type => timer ref
+ TimerTypes :: #{timeout_event_type() => reference()}},
hibernate = false :: boolean(),
hibernate_after = infinity :: timeout()}).
@@ -857,7 +851,7 @@ wakeup_from_hibernate(Parent, Debug, S) ->
%% and detours through sys:handle_system_message/7 and proc_lib:hibernate/3
%% Entry point for system_continue/3
-loop(Parent, Debug, #state{hibernate = true, cancel_timers = 0} = S) ->
+loop(Parent, Debug, #state{hibernate = true} = S) ->
loop_hibernate(Parent, Debug, S);
loop(Parent, Debug, S) ->
loop_receive(Parent, Debug, S).
@@ -893,70 +887,20 @@ loop_receive(
Q = [EXIT],
terminate(exit, Reason, ?STACKTRACE(), Debug, S, Q);
{timeout,TimerRef,TimerMsg} ->
- #state{
- timer_refs = TimerRefs,
- timer_types = TimerTypes} = S,
- case TimerRefs of
- #{TimerRef := TimerType} ->
- %% We know of this timer; is it a running
- %% timer or a timer being cancelled that
- %% managed to send a late timeout message?
- case TimerTypes of
- #{TimerType := TimerRef} ->
- %% The timer type maps back to this
- %% timer ref, so it was a running timer
- %% Unregister the triggered timeout
- NewTimerRefs =
- maps:remove(TimerRef, TimerRefs),
- NewTimerTypes =
- maps:remove(TimerType, TimerTypes),
- loop_receive_result(
- Parent, Debug,
- S#state{
- timer_refs = NewTimerRefs,
- timer_types = NewTimerTypes},
- TimerType, TimerMsg);
- _ ->
- %% This was a late timeout message
- %% from timer being cancelled, so
- %% ignore it and expect a cancel_timer
- %% msg shortly
- loop_receive(Parent, Debug, S)
- end;
- _ ->
+ case S#state.timers of
+ {#{TimerRef := TimerType} = TimerRefs,TimerTypes} ->
+ %% Our timer
+ NewTimers =
+ {maps:remove(TimerRef, TimerRefs),
+ maps:remove(TimerType, TimerTypes)},
+ loop_receive_result(
+ Parent, Debug,
+ S#state{timers = NewTimers},
+ TimerType, TimerMsg);
+ {#{},_} ->
%% Not our timer; present it as an event
loop_receive_result(Parent, Debug, S, info, Msg)
end;
- {cancel_timer,TimerRef,_} ->
- #state{
- timer_refs = TimerRefs,
- cancel_timers = CancelTimers,
- hibernate = Hibernate} = S,
- case TimerRefs of
- #{TimerRef := _} ->
- %% We must have requested a cancel
- %% of this timer so it is already
- %% removed from TimerTypes
- NewTimerRefs =
- maps:remove(TimerRef, TimerRefs),
- NewCancelTimers = CancelTimers - 1,
- NewS =
- S#state{
- timer_refs = NewTimerRefs,
- cancel_timers = NewCancelTimers},
- if
- Hibernate =:= true, NewCancelTimers =:= 0 ->
- %% No more cancel_timer msgs to expect;
- %% we can hibernate
- loop_hibernate(Parent, Debug, NewS);
- NewCancelTimers >= 0 -> % Assert
- loop_receive(Parent, Debug, NewS)
- end;
- _ ->
- %% Not our cancel_timer msg;
- %% present it as an event
- loop_receive_result(Parent, Debug, S, info, Msg)
- end;
_ ->
%% External msg
case Msg of
@@ -1429,9 +1373,7 @@ loop_event_done(
loop_event_done(
Parent, Debug_0,
#state{
- state = State, postponed = P_0,
- timer_refs = TimerRefs_0, timer_types = TimerTypes_0,
- cancel_timers = CancelTimers_0} = S,
+ state = State, postponed = P_0, timers = Timers_0} = S,
Events_0, Event_0, NextState, NewData,
#trans_opts{
hibernate = Hibernate, timeouts_r = TimeoutsR,
@@ -1463,22 +1405,17 @@ loop_event_done(
if
NextState =:= State ->
{Events_0,P_1,
- cancel_timer_by_type(
- timeout, {TimerTypes_0,CancelTimers_0})};
+ cancel_timer_by_type(timeout, Timers_0)};
true ->
{lists:reverse(P_1, Events_0),
[],
cancel_timer_by_type(
state_timeout,
- cancel_timer_by_type(
- timeout, {TimerTypes_0,CancelTimers_0}))}
- %% The state timer is removed from TimerTypes
- %% but remains in TimerRefs until we get
- %% the cancel_timer msg
+ cancel_timer_by_type(timeout, Timers_0))}
end,
- {TimerRefs_3,{TimerTypes_3,CancelTimers_3},TimeoutEvents} =
+ {Timers_3,TimeoutEvents} =
%% Stop and start timers
- parse_timers(TimerRefs_0, Timers_2, TimeoutsR),
+ parse_timers(Timers_2, TimeoutsR),
%% Place next events last in reversed queue
Events_3R = lists:reverse(Events_2, NextEventsR),
%% Enqueue immediate timeout events
@@ -1489,9 +1426,7 @@ loop_event_done(
state = NextState,
data = NewData,
postponed = P_2,
- timer_refs = TimerRefs_3,
- timer_types = TimerTypes_3,
- cancel_timers = CancelTimers_3,
+ timers = Timers_3,
hibernate = Hibernate},
lists:reverse(Events_4R)).
@@ -1501,8 +1436,7 @@ loop_event_done_fast(
Parent, Hibernate,
#state{
state = NextState,
- timer_types = #{timeout := _} = TimerTypes,
- cancel_timers = CancelTimers} = S,
+ timers = {_,#{timeout := _}} = Timers} = S,
Events, P, NextState, NewData) ->
%%
%% Same state, event timeout active
@@ -1510,8 +1444,7 @@ loop_event_done_fast(
loop_event_done_fast(
Parent, Hibernate, S,
Events, P, NextState, NewData,
- cancel_timer_by_type(
- timeout, {TimerTypes,CancelTimers}));
+ cancel_timer_by_type(timeout, Timers));
loop_event_done_fast(
Parent, Hibernate,
#state{state = NextState} = S,
@@ -1529,8 +1462,7 @@ loop_event_done_fast(
loop_event_done_fast(
Parent, Hibernate,
#state{
- timer_types = #{timeout := _} = TimerTypes,
- cancel_timers = CancelTimers} = S,
+ timers = {_,#{timeout := _}} = Timers} = S,
Events, P, NextState, NewData) ->
%%
%% State change, event timeout active
@@ -1540,13 +1472,11 @@ loop_event_done_fast(
lists:reverse(P, Events), [], NextState, NewData,
cancel_timer_by_type(
state_timeout,
- cancel_timer_by_type(
- timeout, {TimerTypes,CancelTimers})));
+ cancel_timer_by_type(timeout, Timers)));
loop_event_done_fast(
Parent, Hibernate,
#state{
- timer_types = #{state_timeout := _} = TimerTypes,
- cancel_timers = CancelTimers} = S,
+ timers = {_,#{state_timeout := _}} = Timers} = S,
Events, P, NextState, NewData) ->
%%
%% State change, state timeout active
@@ -1556,8 +1486,7 @@ loop_event_done_fast(
lists:reverse(P, Events), [], NextState, NewData,
cancel_timer_by_type(
state_timeout,
- cancel_timer_by_type(
- timeout, {TimerTypes,CancelTimers})));
+ cancel_timer_by_type(timeout, Timers)));
loop_event_done_fast(
Parent, Hibernate,
#state{} = S,
@@ -1577,9 +1506,7 @@ loop_event_done_fast(
%% Fast path
%%
loop_event_done_fast(
- Parent, Hibernate, S,
- Events, P, NextState, NewData,
- {TimerTypes,CancelTimers}) ->
+ Parent, Hibernate, S, Events, P, NextState, NewData, Timers) ->
%%
loop_event_done(
Parent, ?not_sys_debug,
@@ -1587,8 +1514,7 @@ loop_event_done_fast(
state = NextState,
data = NewData,
postponed = P,
- timer_types = TimerTypes,
- cancel_timers = CancelTimers,
+ timers = Timers,
hibernate = Hibernate},
Events).
@@ -1703,41 +1629,40 @@ classify_time(_, _, Opts) when is_list(Opts) ->
%% and pending event timer
%%
%% Stop and start timers non-event timers
-parse_timers(TimerRefs, Timers, TimeoutsR) ->
- parse_timers(TimerRefs, Timers, TimeoutsR, #{}, []).
+parse_timers(Timers, TimeoutsR) ->
+ parse_timers(Timers, TimeoutsR, #{}, []).
%%
-parse_timers(
- TimerRefs, Timers, [], _Seen, TimeoutEvents) ->
+parse_timers(Timers, [], _Seen, TimeoutEvents) ->
%%
- {TimerRefs,Timers,TimeoutEvents};
+ {Timers,TimeoutEvents};
parse_timers(
- TimerRefs, Timers, [Timeout|TimeoutsR], Seen, TimeoutEvents) ->
+ Timers, [Timeout|TimeoutsR], Seen, TimeoutEvents) ->
%%
case Timeout of
{TimerType,Time,TimerMsg,TimerOpts} ->
%% Absolute timer
parse_timers(
- TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
+ Timers, TimeoutsR, Seen, TimeoutEvents,
TimerType, Time, TimerMsg, listify(TimerOpts));
%% Relative timers below
{TimerType,0,TimerMsg} ->
parse_timers(
- TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
+ Timers, TimeoutsR, Seen, TimeoutEvents,
TimerType, zero, TimerMsg, []);
{TimerType,Time,TimerMsg} ->
parse_timers(
- TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
+ Timers, TimeoutsR, Seen, TimeoutEvents,
TimerType, Time, TimerMsg, [])
end.
parse_timers(
- TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
+ Timers, TimeoutsR, Seen, TimeoutEvents,
TimerType, Time, TimerMsg, TimerOpts) ->
case Seen of
#{TimerType := _} ->
%% Type seen before - ignore
parse_timers(
- TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents);
+ Timers, TimeoutsR, Seen, TimeoutEvents);
#{} ->
%% Unseen type - handle
NewSeen = Seen#{TimerType => true},
@@ -1745,13 +1670,13 @@ parse_timers(
infinity ->
%% Cancel any running timer
parse_timers(
- TimerRefs, cancel_timer_by_type(TimerType, Timers),
+ cancel_timer_by_type(TimerType, Timers),
TimeoutsR, NewSeen, TimeoutEvents);
zero ->
%% Cancel any running timer
%% Handle zero time timeouts later
parse_timers(
- TimerRefs, cancel_timer_by_type(TimerType, Timers),
+ cancel_timer_by_type(TimerType, Timers),
TimeoutsR, NewSeen,
[{TimerType,TimerMsg}|TimeoutEvents]);
_ ->
@@ -1759,26 +1684,27 @@ parse_timers(
TimerRef =
erlang:start_timer(
Time, self(), TimerMsg, TimerOpts),
- case Timers of
- {#{TimerType := OldTimerRef} = TimerTypes,
- CancelTimers} ->
- %% Cancel the running timer
+ {TimerRefs,TimerTypes} = Timers,
+ case TimerTypes of
+ #{TimerType := OldTimerRef} ->
+ %% Cancel the running timer,
+ %% update the timeout type,
+ %% insert the new timer ref,
+ %% and remove the old timer ref
cancel_timer(OldTimerRef),
- NewCancelTimers = CancelTimers + 1,
%% Insert the new timer into
%% both TimerRefs and TimerTypes
parse_timers(
- TimerRefs#{TimerRef => TimerType},
- {TimerTypes#{TimerType => TimerRef},
- NewCancelTimers},
+ {maps:remove(
+ OldTimerRef,
+ TimerRefs#{TimerRef => TimerType}),
+ TimerTypes#{TimerType := TimerRef}},
TimeoutsR, NewSeen, TimeoutEvents);
- {#{} = TimerTypes,CancelTimers} ->
- %% Insert the new timer into
- %% both TimerRefs and TimerTypes
+ #{} ->
+ %% Insert the new timer type and ref
parse_timers(
- TimerRefs#{TimerRef => TimerType},
- {TimerTypes#{TimerType => TimerRef},
- CancelTimers},
+ {TimerRefs#{TimerRef => TimerType},
+ TimerTypes#{TimerType => TimerRef}},
TimeoutsR, NewSeen, TimeoutEvents)
end
end
@@ -2021,24 +1947,34 @@ listify(Item) when is_list(Item) ->
listify(Item) ->
[Item].
+
+-define(cancel_timer(TimerRef),
+ case erlang:cancel_timer(TimerRef) of
+ false ->
+ %% No timer found and we have not seen the timeout message
+ receive
+ {timeout,(TimerRef),_} ->
+ ok
+ end;
+ _ ->
+ %% Timer was running
+ ok
+ end).
+
+-compile({inline, [cancel_timer/1]}).
+cancel_timer(TimerRef) ->
+ ?cancel_timer(TimerRef).
+
%% Cancel timer if running, otherwise no op
%%
-%% This is an asynchronous cancel so the timer is not really cancelled
-%% until we get a cancel_timer msg i.e {cancel_timer,TimerRef,_}.
-%% In the mean time we might get a timeout message.
-%%
-%% Remove the timer from TimerTypes.
-%% When we get the cancel_timer msg we remove it from TimerRefs.
+%% Remove the timer from Timers.
-compile({inline, [cancel_timer_by_type/2]}).
-cancel_timer_by_type(TimerType, {TimerTypes,CancelTimers} = TT_CT) ->
+cancel_timer_by_type(TimerType, {TimerRefs,TimerTypes} = Timers) ->
case TimerTypes of
#{TimerType := TimerRef} ->
- ok = erlang:cancel_timer(TimerRef, [{async,true}]),
- {maps:remove(TimerType, TimerTypes),CancelTimers + 1};
+ ?cancel_timer(TimerRef),
+ {maps:remove(TimerRef, TimerRefs),
+ maps:remove(TimerType, TimerTypes)};
#{} ->
- TT_CT
+ Timers
end.
-
--compile({inline, [cancel_timer/1]}).
-cancel_timer(TimerRef) ->
- ok = erlang:cancel_timer(TimerRef, [{async,true}]).
diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 5483ea87b5..8f2fd7ea8f 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -721,7 +721,7 @@ printable_list(_L, 1, _T, _Enc) ->
printable_list(L, _D, T, latin1) when T < 0 ->
io_lib:printable_latin1_list(L);
printable_list(L, _D, T, Enc) when T >= 0 ->
- case slice(L, tsub(T, 2)) of
+ case slice(L, tsub(T, 2), Enc) of
false ->
false;
{prefix, Prefix} when Enc =:= latin1 ->
@@ -737,20 +737,46 @@ printable_list(L, _D, T, Enc) when T >= 0 ->
printable_list(L, _D, T, _Uni) when T < 0->
io_lib:printable_list(L).
-slice(L, N) ->
- try io_lib:chars_length(L) =< N of
- true ->
+slice(L, N, latin1) ->
+ try lists:split(N, L) of
+ {_, []} ->
all;
- false ->
- case string:slice(L, 0, N) of
- "" ->
- false;
- Prefix ->
- {prefix, Prefix}
+ {[], _} ->
+ false;
+ {L1, _} ->
+ {prefix, L1}
+ catch
+ _:_ ->
+ all
+ end;
+slice(L, N, _Uni) ->
+ %% Be careful not to traverse more of L than necessary.
+ try string:slice(L, 0, N) of
+ "" ->
+ false;
+ Prefix ->
+ %% Assume no binaries are introduced by string:slice().
+ case is_flat(L, lists:flatlength(Prefix)) of
+ true ->
+ case string:equal(Prefix, L) of
+ true ->
+ all;
+ false ->
+ {prefix, Prefix}
+ end;
+ false ->
+ false
end
catch _:_ -> false
end.
+is_flat(_L, 0) ->
+ true;
+is_flat([C|Cs], N) when is_integer(C) ->
+ is_flat(Cs, N - 1);
+is_flat(_, _N) ->
+ false.
+
printable_bin0(Bin, D, T, Enc) ->
Len = case D >= 0 of
true ->
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 6d243e1bec..97ec785c62 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -556,8 +556,8 @@ tg({call, Line, {remote,_,{atom,_,erlang},{atom, Line2, FunName}},ParaList},
FunName,length(ParaList)}})
end;
tg({call, Line, {remote,_,{atom,_,ModuleName},
- {atom, _, FunName}},_ParaList},B) ->
- throw({error,Line,{?ERR_GENREMOTECALL+B#tgd.eb,ModuleName,FunName}});
+ {atom, _, FunName}},ParaList},B) ->
+ throw({error,Line,{?ERR_GENREMOTECALL+B#tgd.eb,ModuleName,FunName,length(ParaList)}});
tg({cons,Line, H, T},B) ->
{cons, Line, tg(H,B), tg(T,B)};
tg({nil, Line},_B) ->
diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src
index 9e5d6a3bd8..08612ed17f 100644
--- a/lib/stdlib/src/stdlib.appup.src
+++ b/lib/stdlib/src/stdlib.appup.src
@@ -40,7 +40,10 @@
{<<"^3\\.6$">>,[restart_new_emulator]},
{<<"^3\\.6\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]},
{<<"^3\\.7$">>,[restart_new_emulator]},
- {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}],
+ {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]},
+ {<<"^3\\.7\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]},
+ {<<"^3\\.8$">>,[restart_new_emulator]},
+ {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}],
[{<<"^3\\.4$">>,[restart_new_emulator]},
{<<"^3\\.4\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]},
{<<"^3\\.4\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]},
@@ -54,4 +57,7 @@
{<<"^3\\.6$">>,[restart_new_emulator]},
{<<"^3\\.6\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]},
{<<"^3\\.7$">>,[restart_new_emulator]},
- {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}]}.
+ {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]},
+ {<<"^3\\.7\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]},
+ {<<"^3\\.8$">>,[restart_new_emulator]},
+ {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}]}.