Skip to content

Commit

Permalink
stdlib: Correct contracts
Browse files Browse the repository at this point in the history
  • Loading branch information
uabboli committed Jan 22, 2018
1 parent bd87395 commit a92b77d
Show file tree
Hide file tree
Showing 14 changed files with 53 additions and 46 deletions.
5 changes: 3 additions & 2 deletions lib/stdlib/src/gen_event.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -125,7 +125,8 @@
| {'logfile', string()}.
-type option() :: {'timeout', timeout()}
| {'debug', [debug_flag()]}
| {'spawn_opt', [proc_lib:spawn_option()]}.
| {'spawn_opt', [proc_lib:spawn_option()]}
| {'hibernate_after', timeout()}.
-type emgr_ref() :: atom() | {atom(), atom()} | {'global', atom()}
| {'via', atom(), term()} | pid().
-type start_ret() :: {'ok', pid()} | {'error', term()}.
Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/src/gen_fsm.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -198,7 +198,7 @@
%%% start(Name, Mod, Args, Options)
%%% start_link(Mod, Args, Options)
%%% start_link(Name, Mod, Args, Options) where:
%%% Name ::= {local, atom()} | {global, atom()} | {via, atom(), term()}
%%% Name ::= {local, atom()} | {global, term()} | {via, atom(), term()}
%%% Mod ::= atom(), callback module implementing the 'real' fsm
%%% Args ::= term(), init arguments (to Mod:init/1)
%%% Options ::= [{debug, [Flag]}]
Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/src/io_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -149,7 +149,7 @@ fread(Chars, Format) ->

-spec fread(Continuation, CharSpec, Format) -> Return when
Continuation :: continuation() | [],
CharSpec :: string() | eof,
CharSpec :: string() | 'eof',
Format :: string(),
Return :: {'more', Continuation1 :: continuation()}
| {'done', Result, LeftOverChars :: string()},
Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/src/io_lib_fread.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -38,7 +38,7 @@

-spec fread(Continuation, String, Format) -> Return when
Continuation :: io_lib:continuation() | [],
String :: string(),
String :: string() | 'eof',
Format :: string(),
Return :: {'more', Continuation1 :: io_lib:continuation()}
| {'done', Result, LeftOverChars :: string()},
Expand Down
6 changes: 4 additions & 2 deletions lib/stdlib/src/sys.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -38,7 +38,9 @@

-export_type([dbg_opt/0]).

-type name() :: pid() | atom() | {'global', atom()}.
-type name() :: pid() | atom()
| {'global', term()}
| {'via', module(), term()}.
-type system_event() :: {'in', Msg :: _}
| {'in', Msg :: _, From :: _}
| {'out', Msg :: _, To :: _}
Expand Down
6 changes: 3 additions & 3 deletions lib/stdlib/test/epp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1998-2017. All Rights Reserved.
%% Copyright Ericsson AB 1998-2018. 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.
Expand Down Expand Up @@ -551,8 +551,8 @@ otp_8130(Config) when is_list(Config) ->
"t() -> "
" L = \"{ 34 , \\\"1\\\\x{AAA}\\\" , \\\"34\\\" , X . a , $\\\\x{AAA} }\", "
" R = ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}),"
" Lt = erl_scan:string(L, 1, [unicode]),"
" Rt = erl_scan:string(R, 1, [unicode]),"
" Lt = erl_scan:string(L, 1),"
" Rt = erl_scan:string(R, 1),"
" Lt = Rt, ok. ">>,
ok},

Expand Down
7 changes: 4 additions & 3 deletions lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1999-2017. All Rights Reserved.
%% Copyright Ericsson AB 1999-2018. 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.
Expand Down Expand Up @@ -3981,8 +3981,9 @@ non_latin1_module(Config) ->

do_non_latin1_module(Mod) ->
File = atom_to_list(Mod) ++ ".erl",
Forms = [{attribute,1,file,{File,1}},
{attribute,1,module,Mod},
L1 = erl_anno:new(1),
Forms = [{attribute,L1,file,{File,1}},
{attribute,L1,module,Mod},
{eof,2}],
error = compile:forms(Forms),
{error,_,[]} = compile:forms(Forms, [return]),
Expand Down
6 changes: 3 additions & 3 deletions lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2006-2017. All Rights Reserved.
%% Copyright Ericsson AB 2006-2018. 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.
Expand Down Expand Up @@ -1262,7 +1262,7 @@ parse_forms(Chars) ->
parse_forms2([], _Cont, _Line, Forms) ->
lists:reverse(Forms);
parse_forms2(String, Cont0, Line, Forms) ->
case erl_scan:tokens(Cont0, String, Line, [unicode]) of
case erl_scan:tokens(Cont0, String, Line) of
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
Expand Down Expand Up @@ -1303,7 +1303,7 @@ parse_and_pp_expr(String, Indent, Options) ->
erl_pp:expr(parse_expr(StringDot), Indent, Options).

parse_expr(Chars) ->
{ok, Tokens, _} = erl_scan:string(Chars, 1, [unicode]),
{ok, Tokens, _} = erl_scan:string(Chars, 1),
{ok, [Expr]} = erl_parse:parse_exprs(Tokens),
Expr.

Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/test/escript_SUITE_data/unicode1
Expand Up @@ -8,7 +8,7 @@ main(_) ->
_D = erlang:system_flag(backtrace_depth, 0),
A = <<"\x{aaa}"/utf8>>,
S = lists:flatten(io_lib:format("~p/~p.", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B).
2 changes: 1 addition & 1 deletion lib/stdlib/test/escript_SUITE_data/unicode2
Expand Up @@ -8,7 +8,7 @@ main(_) ->
_D = erlang:system_flag(backtrace_depth, 0),
A = <<"\x{aa}">>,
S = lists:flatten(io_lib:format("~p/~p.", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B).
8 changes: 4 additions & 4 deletions lib/stdlib/test/gen_fsm_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -389,7 +389,7 @@ stop10(_Config) ->
Dir = filename:dirname(code:which(?MODULE)),
rpc:call(Node,code,add_path,[Dir]),
{ok, Pid} = rpc:call(Node,gen_fsm,start,[{global,to_stop},?MODULE,[],[]]),
global:sync(),
ok = global:sync(),
ok = gen_fsm:stop({global,to_stop}),
false = rpc:call(Node,erlang,is_process_alive,[Pid]),
{'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
Expand Down Expand Up @@ -1005,7 +1005,7 @@ undef_in_terminate(Config) when is_list(Config) ->
State = {undef_in_terminate, {?MODULE, terminate}},
{ok, FSM} = gen_fsm:start(?MODULE, {state_data, State}, []),
try
gen_fsm:stop(FSM),
ok = gen_fsm:stop(FSM),
ct:fail(failed)
catch
exit:{undef, [{?MODULE, terminate, _, _}|_]} ->
Expand Down Expand Up @@ -1201,7 +1201,7 @@ timeout({timeout,Ref,{timeout,Time}}, {From,Ref}) ->
Cref = gen_fsm:start_timer(Time, cancel),
Time4 = Time*4,
receive after Time4 -> ok end,
gen_fsm:cancel_timer(Cref),
_= gen_fsm:cancel_timer(Cref),
{next_state, timeout, {From,Ref2}};
timeout({timeout,Ref2,ok},{From,Ref2}) ->
gen_fsm:reply(From, ok),
Expand Down
14 changes: 7 additions & 7 deletions lib/stdlib/test/gen_server_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%% Copyright Ericsson AB 1996-2018. 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.
Expand Down Expand Up @@ -346,7 +346,7 @@ stop10(_Config) ->
Dir = filename:dirname(code:which(?MODULE)),
rpc:call(Node,code,add_path,[Dir]),
{ok, Pid} = rpc:call(Node,gen_server,start,[{global,to_stop},?MODULE,[],[]]),
global:sync(),
ok = global:sync(),
ok = gen_server:stop({global,to_stop}),
false = rpc:call(Node,erlang,is_process_alive,[Pid]),
{'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
Expand Down Expand Up @@ -467,7 +467,7 @@ start_node(Name) ->
%% After starting a slave, it takes a little while until global knows
%% about it, even if nodes() includes it, so we make sure that global
%% knows about it before registering something on all nodes.
global:sync(),
ok = global:sync(),
N.

call_remote1(Config) when is_list(Config) ->
Expand Down Expand Up @@ -605,7 +605,7 @@ cast_fast(Config) when is_list(Config) ->
cast_fast_messup() ->
%% Register a false node: hopp@hostname
unregister(erl_epmd),
erl_epmd:start_link(),
{ok, _} = erl_epmd:start_link(),
{ok,S} = gen_tcp:listen(0, []),
{ok,P} = inet:port(S),
{ok,_Creation} = erl_epmd:register_node(hopp, P),
Expand Down Expand Up @@ -1309,7 +1309,7 @@ do_call_with_huge_message_queue() ->

{Time,ok} = tc(fun() -> calls(10000, Pid) end),

[self() ! {msg,N} || N <- lists:seq(1, 500000)],
_ = [self() ! {msg,N} || N <- lists:seq(1, 500000)],
erlang:garbage_collect(),
{NewTime,ok} = tc(fun() -> calls(10000, Pid) end),
io:format("Time for empty message queue: ~p", [Time]),
Expand Down Expand Up @@ -1426,7 +1426,7 @@ undef_in_terminate(Config) when is_list(Config) ->
State = {undef_in_terminate, {oc_server, terminate}},
{ok, Server} = gen_server:start(?MODULE, {state, State}, []),
try
gen_server:stop(Server),
ok = gen_server:stop(Server),
ct:fail(failed)
catch
exit:{undef, [{oc_server, terminate, [], _}|_]} ->
Expand Down Expand Up @@ -1615,7 +1615,7 @@ handle_cast({From,delayed_cast,T}, _State) ->
handle_cast(hibernate_now, _State) ->
{noreply, [], hibernate};
handle_cast(hibernate_later, _State) ->
timer:send_after(1000,self(),hibernate_now),
{ok, _} = timer:send_after(1000,self(),hibernate_now),
{noreply, []};
handle_cast({call_undef_fun, Mod, Fun}, State) ->
Mod:Fun(),
Expand Down
6 changes: 4 additions & 2 deletions lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1999-2017. All Rights Reserved.
%% Copyright Ericsson AB 1999-2018. 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.
Expand Down Expand Up @@ -714,7 +714,7 @@ p(Term, D) ->
rp(Term, 1, 80, D).

p(Term, Col, Ll, D) ->
rp(Term, Col, Ll, D, no_fun).
rp(Term, Col, Ll, D, none).

rp(Term, Col, Ll, D) ->
rp(Term, Col, Ll, D, fun rfd/2).
Expand All @@ -724,6 +724,8 @@ rp(Term, Col, Ll, D) ->
rp(Term, Col, Ll, D, RF) ->
rp(Term, Col, Ll, D, ?MAXCS, RF).

rp(Term, Col, Ll, D, M, none) ->
rp(Term, Col, Ll, D, M, fun(_, _) -> no end);
rp(Term, Col, Ll, D, M, RF) ->
%% io:format("~n~n*** Col = ~p Ll = ~p D = ~p~n~p~n-->~n",
%% [Col, Ll, D, Term]),
Expand Down
25 changes: 13 additions & 12 deletions lib/stdlib/test/shell_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
%% Copyright Ericsson AB 2004-2018. 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.
Expand Down Expand Up @@ -561,9 +561,10 @@ otp_5226(Config) when is_list(Config) ->
otp_5327(Config) when is_list(Config) ->
"exception error: bad argument" =
comm_err(<<"<<\"hej\":default>>.">>),
L1 = erl_anno:new(1),
<<"abc">> =
erl_parse:normalise({bin,1,[{bin_element,1,{string,1,"abc"},
default,default}]}),
erl_parse:normalise({bin,L1,[{bin_element,L1,{string,L1,"abc"},
default,default}]}),
[<<"abc">>] = scan(<<"<<(<<\"abc\">>):3/binary>>.">>),
[<<"abc">>] = scan(<<"<<(<<\"abc\">>)/binary>>.">>),
"exception error: bad argument" =
Expand All @@ -576,9 +577,9 @@ otp_5327(Config) when is_list(Config) ->
comm_err(<<"<<10:default>>.">>),
[<<98,1:1>>] = scan(<<"<<3:3,5:6>>.">>),
{'EXIT',{badarg,_}} =
(catch erl_parse:normalise({bin,1,[{bin_element,1,{integer,1,17},
{atom,1,all},
default}]})),
(catch erl_parse:normalise({bin,L1,[{bin_element,L1,{integer,L1,17},
{atom,L1,all},
default}]})),
[<<-20/signed>>] = scan(<<"<<-20/signed>> = <<-20>>.">>),
[<<-300:16/signed>>] =
scan(<<"<<-300:16/signed>> = <<-300:16>>.">>),
Expand Down Expand Up @@ -2784,7 +2785,7 @@ otp_10302(Config) when is_list(Config) ->
<<"begin
A = <<\"\\xaa\">>,
S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B)
Expand All @@ -2797,7 +2798,7 @@ otp_10302(Config) when is_list(Config) ->
<<"io:setopts([{encoding,utf8}]).
A = <<\"\\xaa\">>,
S = lists:flatten(io_lib:format(\"~p/~p.\", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B).">>,
Expand All @@ -2809,7 +2810,7 @@ otp_10302(Config) when is_list(Config) ->
<<"begin
A = [1089],
S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B)
Expand All @@ -2821,7 +2822,7 @@ otp_10302(Config) when is_list(Config) ->
<<"io:setopts([{encoding,utf8}]).
A = [1089],
S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
{ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
{ok, Ts, _} = erl_scan:string(S, 1),
{ok, Es} = erl_parse:parse_exprs(Ts),
B = erl_eval:new_bindings(),
erl_eval:exprs(Es, B).">>,
Expand Down Expand Up @@ -2940,7 +2941,7 @@ otp_14296(Config) when is_list(Config) ->
end(),

fun() ->
Port = open_port({spawn, "ls"}, [line]),
Port = open_port({spawn, "ls"}, [{line,1}]),
KnownPort = erlang:port_to_list(Port),
S = KnownPort ++ ".",
R = KnownPort ++ ".\n",
Expand Down Expand Up @@ -3012,7 +3013,7 @@ scan(B) ->
scan(t(B), F).

scan(S0, F) ->
case erl_scan:tokens([], S0, 1, [unicode]) of
case erl_scan:tokens([], S0, 1) of
{done,{ok,Ts,_},S} ->
[F(Ts) | scan(S, F)];
_Else ->
Expand Down

0 comments on commit a92b77d

Please sign in to comment.