aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/beam_lib.erl14
-rw-r--r--lib/stdlib/src/calendar.erl78
-rw-r--r--lib/stdlib/src/dets.erl13
-rw-r--r--lib/stdlib/src/dets_v8.erl4
-rw-r--r--lib/stdlib/src/erl_compile.erl3
-rw-r--r--lib/stdlib/src/erl_expand_records.erl2
-rw-r--r--lib/stdlib/src/erl_internal.erl1
-rw-r--r--lib/stdlib/src/erl_scan.erl7
-rw-r--r--lib/stdlib/src/erl_tar.erl30
-rw-r--r--lib/stdlib/src/escript.erl6
-rw-r--r--lib/stdlib/src/eval_bits.erl10
-rw-r--r--lib/stdlib/src/io_lib.erl8
-rw-r--r--lib/stdlib/src/io_lib_fread.erl64
-rw-r--r--lib/stdlib/src/otp_internal.erl8
-rw-r--r--lib/stdlib/src/proplists.erl3
-rw-r--r--lib/stdlib/src/queue.erl127
-rw-r--r--lib/stdlib/src/sofs.erl5
-rw-r--r--lib/stdlib/src/supervisor.erl7
-rw-r--r--lib/stdlib/src/sys.erl4
-rw-r--r--lib/stdlib/src/timer.erl6
-rw-r--r--lib/stdlib/src/zip.erl10
21 files changed, 174 insertions, 236 deletions
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index d9c645d787..fdfbb2e998 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -893,13 +893,17 @@ call_crypto_server(Req) ->
gen_server:call(?CRYPTO_KEY_SERVER, Req, infinity)
catch
exit:{noproc,_} ->
- start_crypto_server(),
- erlang:yield(),
- call_crypto_server(Req)
+ %% Not started.
+ call_crypto_server_1(Req);
+ exit:{normal,_} ->
+ %% The process finished just as we called it.
+ call_crypto_server_1(Req)
end.
-start_crypto_server() ->
- gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []).
+call_crypto_server_1(Req) ->
+ gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []),
+ erlang:yield(),
+ call_crypto_server(Req).
-spec init([]) -> {'ok', #state{}}.
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index 8d1071209e..0320e0cd0e 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -63,7 +63,7 @@
%% Types
%%----------------------------------------------------------------------
--export_type([t_now/0]).
+-export_type([date/0, time/0, datetime/0, datetime1970/0]).
-type year() :: non_neg_integer().
-type year1970() :: 1970..10000. % should probably be 1970..
@@ -76,15 +76,11 @@
-type ldom() :: 28 | 29 | 30 | 31. % last day of month
-type weeknum() :: 1..53.
--type t_now() :: {MegaSecs :: non_neg_integer(),
- Secs :: non_neg_integer(),
- MicroSecs :: non_neg_integer()}.
-
--type t_date() :: {year(),month(),day()}.
--type t_time() :: {hour(),minute(),second()}.
--type t_datetime() :: {t_date(),t_time()}.
--type t_datetime1970() :: {{year1970(),month(),day()},t_time()}.
--type t_yearweeknum() :: {year(),weeknum()}.
+-type date() :: {year(),month(),day()}.
+-type time() :: {hour(),minute(),second()}.
+-type datetime() :: {date(),time()}.
+-type datetime1970() :: {{year1970(),month(),day()},time()}.
+-type yearweeknum() :: {year(),weeknum()}.
%%----------------------------------------------------------------------
@@ -123,7 +119,7 @@ date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 ->
end.
-spec date_to_gregorian_days(Date) -> Days when
- Date :: t_date(),
+ Date :: date(),
Days :: non_neg_integer().
date_to_gregorian_days({Year, Month, Day}) ->
date_to_gregorian_days(Year, Month, Day).
@@ -135,7 +131,7 @@ date_to_gregorian_days({Year, Month, Day}) ->
%% January 1st.
%%
-spec datetime_to_gregorian_seconds(DateTime) -> Seconds when
- DateTime :: t_datetime(),
+ DateTime :: datetime(),
Seconds :: non_neg_integer().
datetime_to_gregorian_seconds({Date, Time}) ->
?SECONDS_PER_DAY*date_to_gregorian_days(Date) +
@@ -155,14 +151,14 @@ day_of_the_week(Year, Month, Day) ->
(date_to_gregorian_days(Year, Month, Day) + 5) rem 7 + 1.
-spec day_of_the_week(Date) -> daynum() when
- Date:: t_date().
+ Date:: date().
day_of_the_week({Year, Month, Day}) ->
day_of_the_week(Year, Month, Day).
%% gregorian_days_to_date(Days) = {Year, Month, Day}
%%
--spec gregorian_days_to_date(Days) -> t_date() when
+-spec gregorian_days_to_date(Days) -> date() when
Days :: non_neg_integer().
gregorian_days_to_date(Days) ->
{Year, DayOfYear} = day_to_year(Days),
@@ -172,7 +168,7 @@ gregorian_days_to_date(Days) ->
%% gregorian_seconds_to_datetime(Secs)
%%
--spec gregorian_seconds_to_datetime(Seconds) -> t_datetime() when
+-spec gregorian_seconds_to_datetime(Seconds) -> datetime() when
Seconds :: non_neg_integer().
gregorian_seconds_to_datetime(Secs) when Secs >= 0 ->
Days = Secs div ?SECONDS_PER_DAY,
@@ -198,7 +194,7 @@ is_leap_year1(_) -> false.
%%
%% Calculates the iso week number for the current date.
%%
--spec iso_week_number() -> t_yearweeknum().
+-spec iso_week_number() -> yearweeknum().
iso_week_number() ->
{Date, _} = local_time(),
iso_week_number(Date).
@@ -207,8 +203,8 @@ iso_week_number() ->
%%
%% Calculates the iso week number for the given date.
%%
--spec iso_week_number(Date) -> t_yearweeknum() when
- Date :: t_date().
+-spec iso_week_number(Date) -> yearweeknum() when
+ Date :: date().
iso_week_number({Year, Month, Day}) ->
D = date_to_gregorian_days({Year, Month, Day}),
W01_1_Year = gregorian_days_of_iso_w01_1(Year),
@@ -260,7 +256,7 @@ last_day_of_the_month1(_, M) when is_integer(M), M > 0, M < 13 ->
%% local_time()
%%
%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
--spec local_time() -> t_datetime().
+-spec local_time() -> datetime().
local_time() ->
erlang:localtime().
@@ -268,20 +264,20 @@ local_time() ->
%% local_time_to_universal_time(DateTime)
%%
-spec local_time_to_universal_time(DateTime1) -> DateTime2 when
- DateTime1 :: t_datetime1970(),
- DateTime2 :: t_datetime1970().
+ DateTime1 :: datetime1970(),
+ DateTime2 :: datetime1970().
local_time_to_universal_time(DateTime) ->
erlang:localtime_to_universaltime(DateTime).
--spec local_time_to_universal_time(t_datetime1970(),
+-spec local_time_to_universal_time(datetime1970(),
'true' | 'false' | 'undefined') ->
- t_datetime1970().
+ datetime1970().
local_time_to_universal_time(DateTime, IsDst) ->
erlang:localtime_to_universaltime(DateTime, IsDst).
-spec local_time_to_universal_time_dst(DateTime1) -> [DateTime] when
- DateTime1 :: t_datetime1970(),
- DateTime :: t_datetime1970().
+ DateTime1 :: datetime1970(),
+ DateTime :: datetime1970().
local_time_to_universal_time_dst(DateTime) ->
UtDst = erlang:localtime_to_universaltime(DateTime, true),
Ut = erlang:localtime_to_universaltime(DateTime, false),
@@ -309,14 +305,14 @@ local_time_to_universal_time_dst(DateTime) ->
%% = MilliSec = integer()
%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
%%
--spec now_to_datetime(Now) -> t_datetime1970() when
- Now :: t_now().
+-spec now_to_datetime(Now) -> datetime1970() when
+ Now :: erlang:timestamp().
now_to_datetime({MSec, Sec, _uSec}) ->
Sec0 = MSec*1000000 + Sec + ?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY,
gregorian_seconds_to_datetime(Sec0).
--spec now_to_universal_time(Now) -> t_datetime1970() when
- Now :: t_now().
+-spec now_to_universal_time(Now) -> datetime1970() when
+ Now :: erlang:timestamp().
now_to_universal_time(Now) ->
now_to_datetime(Now).
@@ -325,8 +321,8 @@ now_to_universal_time(Now) ->
%%
%% Args: Now = now()
%%
--spec now_to_local_time(Now) -> t_datetime1970() when
- Now :: t_now().
+-spec now_to_local_time(Now) -> datetime1970() when
+ Now :: erlang:timestamp().
now_to_local_time({MSec, Sec, _uSec}) ->
erlang:universaltime_to_localtime(
now_to_universal_time({MSec, Sec, _uSec})).
@@ -338,7 +334,7 @@ now_to_local_time({MSec, Sec, _uSec}) ->
-spec seconds_to_daystime(Seconds) -> {Days, Time} when
Seconds :: integer(),
Days :: integer(),
- Time :: t_time().
+ Time :: time().
seconds_to_daystime(Secs) ->
Days0 = Secs div ?SECONDS_PER_DAY,
Secs0 = Secs rem ?SECONDS_PER_DAY,
@@ -356,7 +352,7 @@ seconds_to_daystime(Secs) ->
%% Wraps.
%%
-type secs_per_day() :: 0..?SECONDS_PER_DAY.
--spec seconds_to_time(Seconds) -> t_time() when
+-spec seconds_to_time(Seconds) -> time() when
Seconds :: secs_per_day().
seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY ->
Secs0 = Secs rem ?SECONDS_PER_DAY,
@@ -375,10 +371,10 @@ seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY ->
%% Year = Month = Day = Hour = Minute = Sec = integer()
%%
-spec time_difference(T1, T2) -> {Days, Time} when
- T1 :: t_datetime(),
- T2 :: t_datetime(),
+ T1 :: datetime(),
+ T2 :: datetime(),
Days :: integer(),
- Time :: t_time().
+ Time :: time().
time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
{{Y2, Mo2, D2}, {H2, Mi2, S2}}) ->
Secs = datetime_to_gregorian_seconds({{Y2, Mo2, D2}, {H2, Mi2, S2}}) -
@@ -390,7 +386,7 @@ time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
%% time_to_seconds(Time)
%%
-spec time_to_seconds(Time) -> secs_per_day() when
- Time :: t_time().
+ Time :: time().
time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) ->
H * ?SECONDS_PER_HOUR +
M * ?SECONDS_PER_MINUTE + S.
@@ -399,15 +395,15 @@ time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) ->
%% universal_time()
%%
%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
--spec universal_time() -> t_datetime().
+-spec universal_time() -> datetime().
universal_time() ->
erlang:universaltime().
%% universal_time_to_local_time(DateTime)
%%
--spec universal_time_to_local_time(DateTime) -> t_datetime() when
- DateTime :: t_datetime1970().
+-spec universal_time_to_local_time(DateTime) -> datetime() when
+ DateTime :: datetime1970().
universal_time_to_local_time(DateTime) ->
erlang:universaltime_to_localtime(DateTime).
@@ -429,7 +425,7 @@ valid_date1(_, _, _) ->
false.
-spec valid_date(Date) -> boolean() when
- Date :: t_date().
+ Date :: date().
valid_date({Y, M, D}) ->
valid_date(Y, M, D).
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 671b5a9dd4..fa0641ffd9 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -411,7 +411,8 @@ init_table(Tab, InitFun) ->
InitFun :: fun((Arg) -> Res),
Arg :: read | close,
Res :: end_of_input | {[object()], InitFun} | {Data, InitFun} | term(),
- Options :: [{min_no_slots,no_slots()} | {format,term | bchunk}],
+ Options :: Option | [Option],
+ Option :: {min_no_slots,no_slots()} | {format,term | bchunk},
Reason :: term(),
Data :: binary() | tuple().
@@ -871,11 +872,15 @@ to_ets(DTab, ETab) ->
-spec traverse(Name, Fun) -> Return | {'error', Reason} when
Name :: tab_name(),
Fun :: fun((Object) -> FunReturn),
- FunReturn :: 'continue' | {'continue', Val} | {'done', Value},
+ Object :: object(),
+ FunReturn :: 'continue'
+ | {'continue', Val}
+ | {'done', Value}
+ | OtherValue,
+ Return :: [term()] | OtherValue,
Val :: term(),
Value :: term(),
- Object :: object(),
- Return :: [term()],
+ OtherValue :: term(),
Reason :: term().
traverse(Tab, Fun) ->
diff --git a/lib/stdlib/src/dets_v8.erl b/lib/stdlib/src/dets_v8.erl
index af36958c1c..cdd38d5604 100644
--- a/lib/stdlib/src/dets_v8.erl
+++ b/lib/stdlib/src/dets_v8.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2011. 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
@@ -163,7 +163,7 @@
%% The 8(c) version uses a different hashing algorithm, erlang:phash
%% (former versions use erlang:hash).
%% Version 8(b) files are only converted to version 8(c) if repair is
-%% done, so we need compatability with 8(b) for a _long_ time.
+%% done, so we need compatibility with 8(b) for a _long_ time.
%%
%% There are known bugs due to the fact that keys and objects are
%% sometimes compared (==) and sometimes matched (=:=). The version
diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl
index abff37e4bc..ff032b129c 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2011. 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
@@ -41,7 +41,6 @@ compiler(".idl") -> {ic, compile};
compiler(".asn1") -> {asn1ct, compile_asn1};
compiler(".asn") -> {asn1ct, compile_asn};
compiler(".py") -> {asn1ct, compile_py};
-compiler(".xml") -> {xmerl_scan, process};
compiler(_) -> no.
%% Entry from command line.
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index eada563914..20fd247cea 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -35,7 +35,7 @@
trecords=sets:new(), % Typed records
uses_types=false, % Are there -spec or -type in the module
strict_ra=[], % strict record accesses
- checked_ra=[] % succesfully accessed records
+ checked_ra=[] % successfully accessed records
}).
-spec(module(AbsForms, CompileOptions) -> AbsForms when
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index 478f05e792..3073fc0fb5 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -262,6 +262,7 @@ bif(bitsize, 1) -> true;
bif(bit_size, 1) -> true;
bif(bitstring_to_list, 1) -> true;
bif(byte_size, 1) -> true;
+bif(check_old_code, 1) -> true;
bif(check_process_code, 2) -> true;
bif(concat_binary, 1) -> true;
bif(date, 0) -> true;
diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index 718ca2e91a..10b2ed2e49 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -408,7 +408,12 @@ set_attr(line, {Line,Column}, Fun) when ?ALINE(Line), ?COLUMN(Column) ->
end;
set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) ->
{line,Line} = lists:keyfind(Tag, 1, Attrs),
- lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)});
+ case lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}) of
+ [{line,Ln}] when ?ALINE(Ln) ->
+ Ln;
+ As ->
+ As
+ end;
set_attr(T1, T2, T3) ->
erlang:error(badarg, [T1,T2,T3]).
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index fd85c7aef5..306834e845 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2011. 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
@@ -798,30 +798,10 @@ set_extracted_file_info(Name, #tar_header{mode=Mode, mtime=Mtime}) ->
%% Makes all directories leading up to the file.
-make_dirs(Name, Type) ->
- make_dirs1(filename:split(Name), Type).
-
-make_dirs1([Dir, Next|Rest], Type) ->
- case file:read_file_info(Dir) of
- {ok, #file_info{type=directory}} ->
- make_dirs1([filename:join(Dir, Next)|Rest], Type);
- {ok, #file_info{}} ->
- throw({error, enotdir});
- {error, _} ->
- case file:make_dir(Dir) of
- ok ->
- make_dirs1([filename:join(Dir, Next)|Rest], Type);
- {error, Reason} ->
- throw({error, Reason})
- end
- end;
-make_dirs1([_], file) -> ok;
-make_dirs1([Dir], dir) ->
- file:make_dir(Dir);
-make_dirs1([], _) ->
- %% There must be something wrong here. The list was not supposed
- %% to be empty.
- throw({error, enoent}).
+make_dirs(Name, file) ->
+ filelib:ensure_dir(Name);
+make_dirs(Name, dir) ->
+ filelib:ensure_dir(filename:join(Name,"*")).
%% Prints the message on if the verbose option is given (for reading).
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index d67617260e..cd1bacd2f5 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -62,10 +62,10 @@
-type zip_create_option() :: term().
-type section() ::
shebang
- | {shebang, shebang()}
+ | {shebang, shebang() | default | undefined}
| comment
- | {comment, comment()}
- | {emu_args, emu_args()}
+ | {comment, comment() | default | undefined}
+ | {emu_args, emu_args() | undefined}
| {source, file:filename() | binary()}
| {beam, file:filename() | binary()}
| {archive, file:filename() | binary()}
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index 2cbd6cdae7..1ffa6ea328 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2011. 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
@@ -34,12 +34,12 @@
%% @type matchfun(). A closure which performs a match given a value, a
%% pattern and an environment
%%
-%% @type field() represents a field in a "bin"
+%% @type field(). Represents a field in a "bin".
%%% Part 1: expression evaluation (binary construction)
%% @spec expr_grp(Fields::[field()], Bindings::bindings(),
-%% EvalFun::evalfun()) ->
+%% EvalFun::evalfun(), term(), term()) ->
%% {value, binary(), bindings()}
%%
%% @doc Returns a tuple with {value,Bin,Bs} where Bin is the binary
@@ -192,9 +192,9 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0},
end.
%%% Part 3: binary pattern matching
-%% @spec match_bits(Fields::[field()], Bin::binary()
+%% @spec match_bits(Fields::[field()], Bin::binary(),
%% GlobalEnv::bindings(), LocalEnv::bindings(),
-%% MatchFun::matchfun(),EvalFun::evalfun()) ->
+%% MatchFun::matchfun(),EvalFun::evalfun(), term()) ->
%% {match, bindings()}
%% @doc Used to perform matching. If the match succeeds a new
%% environment is returned. If the match have some syntactic or
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 54c7283abf..0252cdf742 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -100,7 +100,7 @@ fwrite(Format, Args) ->
-spec fread(Format, String) -> Result when
Format :: string(),
String :: string(),
- Result :: {'ok', InputList :: chars(), LeftOverChars :: string()}
+ Result :: {'ok', InputList :: [term()], LeftOverChars :: string()}
| {'more', RestFormat :: string(),
Nchars :: non_neg_integer(),
InputStack :: chars()}
@@ -109,13 +109,13 @@ fwrite(Format, Args) ->
fread(Chars, Format) ->
io_lib_fread:fread(Chars, Format).
--spec fread(Continuation, String, Format) -> Return when
+-spec fread(Continuation, CharSpec, Format) -> Return when
Continuation :: continuation() | [],
- String :: string(),
+ CharSpec :: string() | eof,
Format :: string(),
Return :: {'more', Continuation1 :: continuation()}
| {'done', Result, LeftOverChars :: string()},
- Result :: {'ok', InputList :: chars()}
+ Result :: {'ok', InputList :: [term()]}
| 'eof'
| {'error', What :: term()}.
diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl
index 52aa4d073c..ded1346097 100644
--- a/lib/stdlib/src/io_lib_fread.erl
+++ b/lib/stdlib/src/io_lib_fread.erl
@@ -24,6 +24,10 @@
-import(lists, [reverse/1,reverse/2]).
+-define(is_whitespace(C),
+ ((C) =:= $\s orelse (C) =:= $\t
+ orelse (C) =:= $\r orelse (C) =:= $\n)).
+
%%-----------------------------------------------------------------------
%% fread(Continuation, CharList, FormatString)
@@ -106,31 +110,27 @@ fread_line(Format0, Line, N0, Results0, More, Newline) ->
fread(Format, Line) ->
fread(Format, Line, 0, []).
-fread([$~|Format0], Line, N, Results) ->
+fread([$~|Format0]=AllFormat, Line, N, Results) ->
{Format,F,Sup,Unicode} = fread_field(Format0),
- fread1(Format, F, Sup, Unicode, Line, N, Results, Format0);
-fread([$\s|Format], Line, N, Results) ->
- fread_skip_white(Format, Line, N, Results);
-fread([$\t|Format], Line, N, Results) ->
- fread_skip_white(Format, Line, N, Results);
-fread([$\r|Format], Line, N, Results) ->
- fread_skip_white(Format, Line, N, Results);
-fread([$\n|Format], Line, N, Results) ->
+ fread1(Format, F, Sup, Unicode, Line, N, Results, AllFormat);
+fread([C|Format], Line, N, Results) when ?is_whitespace(C) ->
fread_skip_white(Format, Line, N, Results);
fread([C|Format], [C|Line], N, Results) ->
fread(Format, Line, N+1, Results);
fread([_F|_Format], [_C|_Line], _N, _Results) ->
fread_error(input);
+fread([_|_]=Format, [], N, Results) ->
+ {more,Format,N,Results};
+fread([_|_], eof, 0, []) ->
+ %% This is at start of input so no error.
+ eof;
+fread([_|_], eof, _N, _Results) ->
+ %% This is an error as there is no more input.
+ fread_error(input);
fread([], Line, _N, Results) ->
{ok,reverse(Results),Line}.
-fread_skip_white(Format, [$\s|Line], N, Results) ->
- fread_skip_white(Format, Line, N+1, Results);
-fread_skip_white(Format, [$\t|Line], N, Results) ->
- fread_skip_white(Format, Line, N+1, Results);
-fread_skip_white(Format, [$\r|Line], N, Results) ->
- fread_skip_white(Format, Line, N+1, Results);
-fread_skip_white(Format, [$\n|Line], N, Results) ->
+fread_skip_white(Format, [C|Line], N, Results) when ?is_whitespace(C) ->
fread_skip_white(Format, Line, N+1, Results);
fread_skip_white(Format, Line, N, Results) ->
fread(Format, Line, N, Results).
@@ -166,9 +166,9 @@ fread1([$l|Format], _F, Sup, _U, Line, N, Res, _AllFormat) ->
fread(Format, Line, N, fread_result(Sup, N, Res));
fread1(_Format, _F, _Sup, _U, [], N, Res, AllFormat) ->
%% Need more input here.
- {more,[$~|AllFormat],N,Res};
-fread1(_Format, _F, _Sup, _U, eof, _N, [], _AllFormat) ->
- %% This is at start of format string so no error.
+ {more,AllFormat,N,Res};
+fread1(_Format, _F, _Sup, _U, eof, 0, [], _AllFormat) ->
+ %% This is at start of input so no error.
eof;
fread1(_Format, _F, _Sup, _U, eof, _N, _Res, _AllFormat) ->
%% This is an error as there is no more input.
@@ -386,26 +386,16 @@ fread_string_cs(Line0, N0, true) ->
%% fread_digits(Line, N, Base, Characters)
%% Read segments of things, return "thing" characters in reverse order.
-fread_skip_white([$\s|Line]) -> fread_skip_white(Line);
-fread_skip_white([$\t|Line]) -> fread_skip_white(Line);
-fread_skip_white([$\r|Line]) -> fread_skip_white(Line);
-fread_skip_white([$\n|Line]) -> fread_skip_white(Line);
+fread_skip_white([C|Line]) when ?is_whitespace(C) ->
+ fread_skip_white(Line);
fread_skip_white(Line) -> Line.
-fread_skip_white([$\s|Line], N) ->
- fread_skip_white(Line, N+1);
-fread_skip_white([$\t|Line], N) ->
- fread_skip_white(Line, N+1);
-fread_skip_white([$\r|Line], N) ->
- fread_skip_white(Line, N+1);
-fread_skip_white([$\n|Line], N) ->
+fread_skip_white([C|Line], N) when ?is_whitespace(C) ->
fread_skip_white(Line, N+1);
fread_skip_white(Line, N) -> {Line,N}.
-fread_skip_latin1_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs};
-fread_skip_latin1_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs};
-fread_skip_latin1_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs};
-fread_skip_latin1_nonwhite([$\n|Line], N, Cs) -> {[$\n|Line],N,Cs};
+fread_skip_latin1_nonwhite([C|Line], N, Cs) when ?is_whitespace(C) ->
+ {[C|Line],N,Cs};
fread_skip_latin1_nonwhite([C|Line], N, []) when C > 255 ->
{[C|Line],N,error};
fread_skip_latin1_nonwhite([C|Line], N, Cs) when C > 255 ->
@@ -414,10 +404,8 @@ fread_skip_latin1_nonwhite([C|Line], N, Cs) ->
fread_skip_latin1_nonwhite(Line, N+1, [C|Cs]);
fread_skip_latin1_nonwhite([], N, Cs) -> {[],N,Cs}.
-fread_skip_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs};
-fread_skip_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs};
-fread_skip_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs};
-fread_skip_nonwhite([$\n|Line], N, Cs) -> {[$\n|Line],N,Cs};
+fread_skip_nonwhite([C|Line], N, Cs) when ?is_whitespace(C) ->
+ {[C|Line],N,Cs};
fread_skip_nonwhite([C|Line], N, Cs) ->
fread_skip_nonwhite(Line, N+1, [C|Cs]);
fread_skip_nonwhite([], N, Cs) -> {[],N,Cs}.
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 39d017d430..5129ba5074 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -461,6 +461,14 @@ obsolete_1(public_key, pem_to_der, 1) ->
obsolete_1(public_key, decode_private_key, A) when A =:= 1; A =:= 2 ->
{deprecated,{public_key,pem_entry_decode,1},"R15A"};
+%% Added in R14B03.
+obsolete_1(docb_gen, _, _) ->
+ {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"};
+obsolete_1(docb_transform, _, _) ->
+ {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"};
+obsolete_1(docb_xml_check, _, _) ->
+ {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"};
+
obsolete_1(_, _, _) ->
no.
diff --git a/lib/stdlib/src/proplists.erl b/lib/stdlib/src/proplists.erl
index 68697d0da2..e3eda5d932 100644
--- a/lib/stdlib/src/proplists.erl
+++ b/lib/stdlib/src/proplists.erl
@@ -49,9 +49,10 @@
%% ---------------------------------------------------------------------
--export_type([property/0]).
+-export_type([property/0, proplist/0]).
-type property() :: atom() | tuple().
+-type proplist() :: [property()].
%% ---------------------------------------------------------------------
diff --git a/lib/stdlib/src/queue.erl b/lib/stdlib/src/queue.erl
index 4c6b4d710b..afe917b151 100644
--- a/lib/stdlib/src/queue.erl
+++ b/lib/stdlib/src/queue.erl
@@ -56,16 +56,14 @@
new() -> {[],[]}. %{RearList,FrontList}
%% O(1)
--spec is_queue(Term) -> boolean() when
- Term :: term().
+-spec is_queue(Term :: term()) -> boolean().
is_queue({R,F}) when is_list(R), is_list(F) ->
true;
is_queue(_) ->
false.
%% O(1)
--spec is_empty(Q) -> boolean() when
- Q :: queue().
+-spec is_empty(Q :: queue()) -> boolean().
is_empty({[],[]}) ->
true;
is_empty({In,Out}) when is_list(In), is_list(Out) ->
@@ -74,16 +72,14 @@ is_empty(Q) ->
erlang:error(badarg, [Q]).
%% O(len(Q))
--spec len(Q) -> non_neg_integer() when
- Q :: queue().
+-spec len(Q :: queue()) -> non_neg_integer().
len({R,F}) when is_list(R), is_list(F) ->
length(R)+length(F);
len(Q) ->
erlang:error(badarg, [Q]).
%% O(len(Q))
--spec to_list(Q) -> list() when
- Q :: queue().
+-spec to_list(Q :: queue()) -> list().
to_list({In,Out}) when is_list(In), is_list(Out) ->
Out++lists:reverse(In, []);
to_list(Q) ->
@@ -92,8 +88,7 @@ to_list(Q) ->
%% Create queue from list
%%
%% O(length(L))
--spec from_list(L) -> queue() when
- L :: list().
+-spec from_list(L :: list()) -> queue().
from_list(L) when is_list(L) ->
f2r(L);
from_list(L) ->
@@ -102,9 +97,7 @@ from_list(L) ->
%% Return true or false depending on if element is in queue
%%
%% O(length(Q)) worst case
--spec member(Item, Q) -> boolean() when
- Item :: term(),
- Q :: queue().
+-spec member(Item :: term(), Q :: queue()) -> boolean().
member(X, {R,F}) when is_list(R), is_list(F) ->
lists:member(X, R) orelse lists:member(X, F);
member(X, Q) ->
@@ -117,10 +110,7 @@ member(X, Q) ->
%% Put at least one element in each list, if it is cheap
%%
%% O(1)
--spec in(Item, Q1) -> Q2 when
- Item :: term(),
- Q1 :: queue(),
- Q2 :: queue().
+-spec in(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
in(X, {[_]=In,[]}) ->
{[X], In};
in(X, {In,Out}) when is_list(In), is_list(Out) ->
@@ -132,10 +122,7 @@ in(X, Q) ->
%% Put at least one element in each list, if it is cheap
%%
%% O(1)
--spec in_r(Item, Q1) -> Q2 when
- Item :: term(),
- Q1 :: queue(),
- Q2 :: queue().
+-spec in_r(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
in_r(X, {[],[_]=F}) ->
{F,[X]};
in_r(X, {R,F}) when is_list(R), is_list(F) ->
@@ -146,10 +133,9 @@ in_r(X, Q) ->
%% Take from head/front
%%
%% O(1) amortized, O(len(Q)) worst case
--spec out(Q1) -> Result when
- Q1 :: queue(),
- Q2 :: queue(),
- Result :: {{value, Item :: term()}, Q2} | {empty, Q1}.
+-spec out(Q1 :: queue()) ->
+ {{value, Item :: term()}, Q2 :: queue()} |
+ {empty, Q1 :: queue()}.
out({[],[]}=Q) ->
{empty,Q};
out({[V],[]}) ->
@@ -167,10 +153,9 @@ out(Q) ->
%% Take from tail/rear
%%
%% O(1) amortized, O(len(Q)) worst case
--spec out_r(Q1) -> Result when
- Q1 :: queue(),
- Q2 :: queue(),
- Result :: {{value, Item :: term()}, Q2} | {empty, Q1}.
+-spec out_r(Q1 :: queue()) ->
+ {{value, Item :: term()}, Q2 :: queue()} |
+ {empty, Q1 :: queue()}.
out_r({[],[]}=Q) ->
{empty,Q};
out_r({[],[V]}) ->
@@ -191,9 +176,7 @@ out_r(Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec get(Q) -> Item when
- Q :: queue(),
- Item :: term().
+-spec get(Q :: queue()) -> Item :: term().
get({[],[]}=Q) ->
erlang:error(empty, [Q]);
get({R,F}) when is_list(R), is_list(F) ->
@@ -212,9 +195,7 @@ get([_|R], []) -> % malformed queue -> O(len(Q))
%% Return the last element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec get_r(Q) -> Item when
- Q :: queue(),
- Item :: term().
+-spec get_r(Q :: queue()) -> Item :: term().
get_r({[],[]}=Q) ->
erlang:error(empty, [Q]);
get_r({[H|_],F}) when is_list(F) ->
@@ -229,9 +210,7 @@ get_r(Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec peek(Q) -> 'empty' | {'value',Item} when
- Q :: queue(),
- Item :: term().
+-spec peek(Q :: queue()) -> empty | {value,Item :: term()}.
peek({[],[]}) ->
empty;
peek({R,[H|_]}) when is_list(R) ->
@@ -246,9 +225,7 @@ peek(Q) ->
%% Return the last element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec peek_r(Q) -> 'empty' | {'value',Item} when
- Q :: queue(),
- Item :: term().
+-spec peek_r(Q :: queue()) -> empty | {value,Item :: term()}.
peek_r({[],[]}) ->
empty;
peek_r({[H|_],F}) when is_list(F) ->
@@ -263,9 +240,7 @@ peek_r(Q) ->
%% Remove the first element and return resulting queue
%%
%% O(1) amortized
--spec drop(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec drop(Q1 :: queue()) -> Q2 :: queue().
drop({[],[]}=Q) ->
erlang:error(empty, [Q]);
drop({[_],[]}) ->
@@ -283,9 +258,7 @@ drop(Q) ->
%% Remove the last element and return resulting queue
%%
%% O(1) amortized
--spec drop_r(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec drop_r(Q1 :: queue()) -> Q2 :: queue().
drop_r({[],[]}=Q) ->
erlang:error(empty, [Q]);
drop_r({[],[_]}) ->
@@ -306,9 +279,7 @@ drop_r(Q) ->
%% Return reversed queue
%%
%% O(1)
--spec reverse(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec reverse(Q1 :: queue()) -> Q2 :: queue().
reverse({R,F}) when is_list(R), is_list(F) ->
{F,R};
reverse(Q) ->
@@ -318,10 +289,7 @@ reverse(Q) ->
%%
%% Q2 empty: O(1)
%% else: O(len(Q1))
--spec join(Q1, Q2) -> Q3 when
- Q1 :: queue(),
- Q2 :: queue(),
- Q3 :: queue().
+-spec join(Q1 :: queue(), Q2 :: queue()) -> Q3 :: queue().
join({R,F}=Q, {[],[]}) when is_list(R), is_list(F) ->
Q;
join({[],[]}, {R,F}=Q) when is_list(R), is_list(F) ->
@@ -335,11 +303,8 @@ join(Q1, Q2) ->
%%
%% N = 0..len(Q)
%% O(max(N, len(Q)))
--spec split(N, Q1) -> {Q2,Q3} when
- N :: non_neg_integer(),
- Q1 :: queue(),
- Q2 :: queue(),
- Q3 :: queue().
+-spec split(N :: non_neg_integer(), Q1 :: queue()) ->
+ {Q2 :: queue(),Q3 :: queue()}.
split(0, {R,F}=Q) when is_list(R), is_list(F) ->
{{[],[]},Q};
split(N, {R,F}=Q) when is_integer(N), N >= 1, is_list(R), is_list(F) ->
@@ -380,10 +345,8 @@ split_r1_to_f2(N, [X|R1], F1, R2, F2) ->
%%
%% Fun(_) -> List: O(length(List) * len(Q))
%% else: O(len(Q)
--spec filter(Fun, Q1) -> Q2 when
- Fun :: fun((Item :: term()) -> boolean() | list()),
- Q1 :: queue(),
- Q2 :: queue().
+-spec filter(Fun, Q1 :: queue()) -> Q2 :: queue() when
+ Fun :: fun((Item :: term()) -> boolean() | list()).
filter(Fun, {R0,F0}) when is_function(Fun, 1), is_list(R0), is_list(F0) ->
F = filter_f(Fun, F0),
R = filter_r(Fun, R0),
@@ -459,10 +422,7 @@ filter_r(Fun, [X|R0]) ->
%% Cons to head
%%
--spec cons(Item, Q1) -> Q2 when
- Item :: term(),
- Q1 :: queue(),
- Q2 :: queue().
+-spec cons(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
cons(X, Q) ->
in_r(X, Q).
@@ -471,9 +431,7 @@ cons(X, Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec head(Q) -> Item when
- Q :: queue(),
- Item :: term().
+-spec head(Q :: queue()) -> Item :: term().
head({[],[]}=Q) ->
erlang:error(empty, [Q]);
head({R,F}) when is_list(R), is_list(F) ->
@@ -483,9 +441,7 @@ head(Q) ->
%% Remove head element and return resulting queue
%%
--spec tail(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec tail(Q1 :: queue()) -> Q2 :: queue().
tail(Q) ->
drop(Q).
@@ -493,35 +449,22 @@ tail(Q) ->
%% Cons to tail
%%
--spec snoc(Q1, Item) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue(),
- Item :: term().
+-spec snoc(Q1 :: queue(), Item :: term()) -> Q2 :: queue().
snoc(Q, X) ->
in(X, Q).
%% Return last element
--spec daeh(Q) -> Item when
- Q :: queue(),
- Item :: term().
+-spec daeh(Q :: queue()) -> Item :: term().
daeh(Q) -> get_r(Q).
--spec last(Q) -> Item when
- Q :: queue(),
- Item :: term().
+-spec last(Q :: queue()) -> Item :: term().
last(Q) -> get_r(Q).
%% Remove last element and return resulting queue
--spec liat(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec liat(Q1 :: queue()) -> Q2 :: queue().
liat(Q) -> drop_r(Q).
--spec lait(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec lait(Q1 :: queue()) -> Q2 :: queue().
lait(Q) -> drop_r(Q). %% Oops, mis-spelled 'tail' reversed. Forget this one.
--spec init(Q1) -> Q2 when
- Q1 :: queue(),
- Q2 :: queue().
+-spec init(Q1 :: queue()) -> Q2 :: queue().
init(Q) -> drop_r(Q).
%%--------------------------------------------------------------------------
diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl
index d38b8ab37a..34eb224647 100644
--- a/lib/stdlib/src/sofs.erl
+++ b/lib/stdlib/src/sofs.erl
@@ -81,7 +81,8 @@
-define(ORDTAG, 'OrdSet').
-record(?TAG, {data = [] :: list(), type = type :: term()}).
--record(?ORDTAG, {orddata = {} :: tuple(), ordtype = type :: term()}).
+-record(?ORDTAG, {orddata = {} :: tuple() | atom(),
+ ordtype = type :: term()}).
-define(LIST(S), (S)#?TAG.data).
-define(TYPE(S), (S)#?TAG.type).
@@ -375,7 +376,7 @@ to_sets(S) when ?IS_ORDSET(S) ->
-spec(no_elements(ASet) -> NoElements when
ASet :: a_set() | ordset(),
- NoElements :: pos_integer()).
+ NoElements :: non_neg_integer()).
no_elements(S) when ?IS_SET(S) ->
length(?LIST(S));
no_elements(S) when ?IS_ORDSET(S), is_tuple(?ORDTYPE(S)) ->
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index e60706ed05..dc31647eb5 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -735,6 +735,13 @@ restart(one_for_all, Child, State) ->
terminate_children(Children, SupName) ->
terminate_children(Children, SupName, []).
+%% Temporary children should not be restarted and thus should
+%% be skipped when building the list of terminated children, although
+%% we do want them to be shut down as many functions from this module
+%% use this function to just clear everything.
+terminate_children([Child = #child{restart_type=temporary} | Children], SupName, Res) ->
+ do_terminate(Child, SupName),
+ terminate_children(Children, SupName, Res);
terminate_children([Child | Children], SupName, Res) ->
NChild = do_terminate(Child, SupName),
terminate_children(Children, SupName, [NChild | Res]);
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index 8ab72c9b50..f34201604c 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -154,7 +154,7 @@ log_to_file(Name, FileName, Timeout) ->
-spec statistics(Name, Flag) -> 'ok' | {'ok', Statistics} when
Name :: name(),
Flag :: 'true' | 'false' | 'get',
- Statistics :: [StatisticsTuple],
+ Statistics :: [StatisticsTuple] | no_statistics,
StatisticsTuple :: {'start_time', DateTime1}
| {'current_time', DateTime2}
| {'reductions', non_neg_integer()}
@@ -168,7 +168,7 @@ statistics(Name, Flag) ->
-spec statistics(Name, Flag, Timeout) -> 'ok' | {'ok', Statistics} when
Name :: name(),
Flag :: 'true' | 'false' | 'get',
- Statistics :: [StatisticsTuple],
+ Statistics :: [StatisticsTuple] | no_statistics,
StatisticsTuple :: {'start_time', DateTime1}
| {'current_time', DateTime2}
| {'reductions', non_neg_integer()}
diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl
index 89fae05e4f..689e42051f 100644
--- a/lib/stdlib/src/timer.erl
+++ b/lib/stdlib/src/timer.erl
@@ -199,9 +199,9 @@ tc(M, F, A) ->
%% Calculate the time difference (in microseconds) of two
%% erlang:now() timestamps, T2-T1.
%%
--spec now_diff(T1, T2) -> Tdiff when
- T1 :: calendar:t_now(),
- T2 :: calendar:t_now(),
+-spec now_diff(T2, T1) -> Tdiff when
+ T1 :: erlang:timestamp(),
+ T2 :: erlang:timestamp(),
Tdiff :: integer().
now_diff({A2, B2, C2}, {A1, B1, C1}) ->
((A2-A1)*1000000 + B2-B1)*1000000 + C2-C1.
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 524d709431..c82c8159b6 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -223,7 +223,7 @@ openzip_open(F, Options) ->
do_openzip_open(F, Options) ->
Opts = get_openzip_options(Options),
#openzip_opts{output = Output, open_opts = OpO, cwd = CWD} = Opts,
- Input = get_zip_input(F),
+ Input = get_input(F),
In0 = Input({open, F, OpO -- [write]}, []),
{[#zip_comment{comment = C} | Files], In1} =
get_central_dir(In0, fun raw_file_info_etc/5, Input),
@@ -489,7 +489,7 @@ do_list_dir(F, Options) ->
%% Print zip directory in short form
-spec(t(Archive) -> ok when
- Archive :: file:name() | binary | ZipHandle,
+ Archive :: file:name() | binary() | ZipHandle,
ZipHandle :: pid()).
t(F) when is_pid(F) -> zip_t(F);
@@ -513,7 +513,7 @@ do_t(F, RawPrint) ->
%% Print zip directory in long form (like ls -l)
-spec(tt(Archive) -> ok when
- Archive :: file:name() | binary | ZipHandle,
+ Archive :: file:name() | binary() | ZipHandle,
ZipHandle :: pid()).
tt(F) when is_pid(F) -> zip_tt(F);
@@ -1174,7 +1174,7 @@ zip_get(Pid) when is_pid(Pid) ->
zip_close(Pid) when is_pid(Pid) ->
request(self(), Pid, close).
--spec(zip_get(FileName, ZipHandle) -> {ok, [Result]} | {error, Reason} when
+-spec(zip_get(FileName, ZipHandle) -> {ok, Result} | {error, Reason} when
FileName :: file:name(),
ZipHandle :: pid(),
Result :: file:name() | {file:name(), binary()},
@@ -1183,7 +1183,7 @@ zip_close(Pid) when is_pid(Pid) ->
zip_get(FileName, Pid) when is_pid(Pid) ->
request(self(), Pid, {get, FileName}).
--spec(zip_list_dir(ZipHandle) -> Result | {error, Reason} when
+-spec(zip_list_dir(ZipHandle) -> {ok, Result} | {error, Reason} when
Result :: [zip_comment() | zip_file()],
ZipHandle :: pid(),
Reason :: term()).