aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
authorErlang/OTP <[email protected]>2010-04-14 06:22:14 +0000
committerErlang/OTP <[email protected]>2010-04-14 06:22:14 +0000
commit99c0cee8e32b3065b0b0568e49fd334648b32e41 (patch)
treed7d9bc2c7bf72667d3e868778e4614f89c9eb849 /lib/stdlib/src
parent1aa3a061cfa397acba8afd4eb9a3765b4292156c (diff)
parentd1e87375746e0600c7e09029b814fdd552ec6f6e (diff)
downloadotp-99c0cee8e32b3065b0b0568e49fd334648b32e41.tar.gz
otp-99c0cee8e32b3065b0b0568e49fd334648b32e41.tar.bz2
otp-99c0cee8e32b3065b0b0568e49fd334648b32e41.zip
Merge branch 'ks/stdlib' into dev
* ks/stdlib: erl_parse.yrl: Add missing operator in type declaration stdlib: Add types and specs stdlib: Use fun object instead of {M,F} tuple ets: Cleanup as suggested by tidier OTP-8576 ks/stdlib
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/c.erl117
-rw-r--r--lib/stdlib/src/dets_sup.erl17
-rw-r--r--lib/stdlib/src/erl_parse.yrl2
-rw-r--r--lib/stdlib/src/ets.erl110
-rw-r--r--lib/stdlib/src/gen_event.erl13
-rw-r--r--lib/stdlib/src/gen_fsm.erl20
-rw-r--r--lib/stdlib/src/gen_server.erl24
7 files changed, 182 insertions, 121 deletions
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 433833e233..e05a1c787f 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(c).
@@ -31,10 +31,14 @@
-export([display_info/1]).
-export([appcall/4]).
--import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysearch/3,keysort/2,
+-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2,
concat/1,max/1,min/1,foreach/2,foldl/3,flatmap/2]).
-import(io, [format/1, format/2]).
+%%-----------------------------------------------------------------------
+
+-spec help() -> 'ok'.
+
help() ->
format("bt(Pid) -- stack backtrace for a process\n"
"c(File) -- compile and load code in <File>\n"
@@ -65,8 +69,12 @@ help() ->
%% c(FileName)
%% Compile a file/module.
+-spec c(file:name()) -> {'ok', module()} | 'error'.
+
c(File) -> c(File, []).
+-spec c(file:name(), [compile:option()]) -> {'ok', module()} | 'error'.
+
c(File, Opts0) when is_list(Opts0) ->
Opts = [report_errors,report_warnings|Opts0],
case compile:file(File, Opts) of
@@ -82,6 +90,8 @@ c(File, Opt) ->
%%% Obtain the 'outdir' option from the argument. Return "." if no
%%% such option was given.
+-spec outdir([compile:option()]) -> file:filename().
+
outdir([]) ->
".";
outdir([Opt|Rest]) ->
@@ -118,8 +128,8 @@ machine_load(Mod, File, Opts) ->
%%% loaded from some other place than current directory.
%%% Now, loading from other than current directory is supposed to work.
%%% so this function does nothing special.
-check_load({error, R}, _) -> {error, R};
-check_load(_, X) -> {ok, X}.
+check_load({error, _R} = Error, _) -> Error;
+check_load(_, Mod) -> {ok, Mod}.
%% Compile a list of modules
%% enables the nice unix shell cmd
@@ -128,6 +138,8 @@ check_load(_, X) -> {ok, X}.
%% with constant c2 defined, c1=v1 (v1 must be a term!), include dir
%% IDir, outdir ODir.
+-spec lc([erl_compile:cmd_line_arg()]) -> 'ok' | 'error'.
+
lc(Args) ->
case catch split(Args, [], []) of
error -> error;
@@ -145,7 +157,7 @@ lc_batch() ->
io:format("Error: no files to compile~n"),
halt(1).
--spec lc_batch([_]) -> no_return().
+-spec lc_batch([erl_compile:cmd_line_arg()]) -> no_return().
lc_batch(Args) ->
try split(Args, [], []) of
@@ -191,8 +203,13 @@ make_term(Str) ->
throw(error)
end.
+-spec nc(file:name()) -> {'ok', module()} | 'error'.
+
nc(File) -> nc(File, []).
+-spec nc(file:name(), [compile:option()] | compile:option()) ->
+ {'ok', module} | 'error'.
+
nc(File, Opts0) when is_list(Opts0) ->
Opts = Opts0 ++ [report_errors, report_warnings],
case compile:file(File, Opts) of
@@ -215,26 +232,37 @@ nc(File, Opt) when is_atom(Opt) ->
%% l(Mod)
%% Reload module Mod from file of same name
+-spec l(module()) -> code:load_ret().
l(Mod) ->
code:purge(Mod),
code:load_file(Mod).
%% Network version of l/1
+%%-spec nl(module()) ->
nl(Mod) ->
case code:get_object_code(Mod) of
{_Module, Bin, Fname} ->
- rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]);
+ rpc:eval_everywhere(code, load_binary, [Mod, Fname, Bin]);
Other ->
Other
end.
+-spec i() -> 'ok'.
+
i() -> i(processes()).
+
+-spec ni() -> 'ok'.
+
ni() -> i(all_procs()).
+-spec i([pid()]) -> 'ok'.
+
i(Ps) ->
i(Ps, length(Ps)).
+-spec i([pid()], non_neg_integer()) -> 'ok'.
+
i(Ps, N) when N =< 100 ->
iformat("Pid", "Initial Call", "Heap", "Reds",
"Msgs"),
@@ -275,7 +303,6 @@ paged_i(Ps, Acc, N, Page) ->
paged_i([], NewAcc, 0, Page)
end.
-
choice(F) ->
case get_line('(c)ontinue (q)uit -->', "c\n") of
"c\n" ->
@@ -285,7 +312,6 @@ choice(F) ->
_ ->
choice(F)
end.
-
get_line(P, Default) ->
case io:get_line(P) of
@@ -305,7 +331,6 @@ mfa_string({M,F,A}) ->
mfa_string(X) ->
w(X).
-
display_info(Pid) ->
case pinfo(Pid) of
undefined -> {0,0,0,0};
@@ -317,7 +342,7 @@ display_info(Pid) ->
Other ->
Other
end,
- Reds = fetch(reductions, Info),
+ Reds = fetch(reductions, Info),
LM = length(fetch(messages, Info)),
HS = fetch(heap_size, Info),
SS = fetch(stack_size, Info),
@@ -364,21 +389,30 @@ pinfo(Pid) ->
end.
fetch(Key, Info) ->
- case keysearch(Key, 1, Info) of
- {value, {_, Val}} -> Val;
+ case lists:keyfind(Key, 1, Info) of
+ {_, Val} -> Val;
false -> 0
end.
-pid(X,Y,Z) ->
+-spec pid(non_neg_integer(), non_neg_integer(), non_neg_integer()) -> pid().
+
+pid(X, Y, Z) ->
list_to_pid("<" ++ integer_to_list(X) ++ "." ++
integer_to_list(Y) ++ "." ++
integer_to_list(Z) ++ ">").
-i(X,Y,Z) -> pinfo(pid(X,Y,Z)).
+-spec i(non_neg_integer(), non_neg_integer(), non_neg_integer()) ->
+ [{atom(), term()}].
+
+i(X, Y, Z) -> pinfo(pid(X, Y, Z)).
+
+-spec q() -> no_return().
q() ->
init:stop().
+-spec bt(pid()) -> 'ok' | 'undefined'.
+
bt(Pid) ->
case catch erlang:process_display(Pid, backtrace) of
{'EXIT', _} ->
@@ -387,6 +421,8 @@ bt(Pid) ->
ok
end.
+-spec m() -> 'ok'.
+
m() ->
mformat("Module", "File"),
foreach(fun ({Mod,File}) -> mformat(Mod, File) end, sort(code:all_loaded())).
@@ -414,8 +450,8 @@ error(Fmt, Args) ->
f_p_e(P, F) ->
case file:path_eval(P, F) of
- {error, enoent} ->
- {error, enoent};
+ {error, enoent} = Enoent ->
+ Enoent;
{error, E={Line, _Mod, _Term}} ->
error("file:path_eval(~p,~p): error on line ~p: ~s~n",
[P, F, Line, file:format_error(E)]),
@@ -438,10 +474,11 @@ bi(I) ->
%%
%% Short and nice form of module info
%%
+-spec m(module()) -> 'ok'.
m(M) ->
L = M:module_info(),
- {value,{exports,E}} = keysearch(exports, 1, L),
+ {exports,E} = lists:keyfind(exports, 1, L),
Time = get_compile_time(L),
COpts = get_compile_options(L),
format("Module ~w compiled: ",[M]), print_time(Time),
@@ -470,10 +507,10 @@ get_compile_options(L) ->
end.
get_compile_info(L, Tag) ->
- case keysearch(compile, 1, L) of
- {value, {compile, I}} ->
- case keysearch(Tag, 1, I) of
- {value, {Tag, Val}} -> {ok,Val};
+ case lists:keyfind(compile, 1, L) of
+ {compile, I} ->
+ case lists:keyfind(Tag, 1, I) of
+ {Tag, Val} -> {ok,Val};
false -> error
end;
false -> error
@@ -523,6 +560,8 @@ month(11) -> "November";
month(12) -> "December".
%% Just because we can't eval receive statements...
+-spec flush() -> 'ok'.
+
flush() ->
receive
X ->
@@ -533,9 +572,13 @@ flush() ->
end.
%% Print formatted info about all registered names in the system
+-spec nregs() -> 'ok'.
+
nregs() ->
foreach(fun (N) -> print_node_regs(N) end, all_regs()).
+-spec regs() -> 'ok'.
+
regs() ->
print_node_regs({node(),registered()}).
@@ -609,6 +652,8 @@ portformat(Name, Id, Cmd) ->
%% cd(Directory)
%% These are just wrappers around the file:get/set_cwd functions.
+-spec pwd() -> 'ok'.
+
pwd() ->
case file:get_cwd() of
{ok, Str} ->
@@ -617,6 +662,8 @@ pwd() ->
ok = io:format("Cannot determine current directory\n")
end.
+-spec cd(file:name()) -> 'ok'.
+
cd(Dir) ->
file:set_cwd(Dir),
pwd().
@@ -625,9 +672,13 @@ cd(Dir) ->
%% ls(Directory)
%% The strategy is to print in fixed width files.
+-spec ls() -> 'ok'.
+
ls() ->
ls(".").
+-spec ls(file:name()) -> 'ok'.
+
ls(Dir) ->
case file:list_dir(Dir) of
{ok, Entries} ->
@@ -660,24 +711,31 @@ w(X) ->
%% memory/[0,1]
%%
-memory() -> erlang:memory().
+-spec memory() -> [{atom(), non_neg_integer()}].
+
+memory() -> erlang:memory().
+
+-spec memory(atom()) -> non_neg_integer()
+ ; ([atom()]) -> [{atom(), non_neg_integer()}].
+
memory(TypeSpec) -> erlang:memory(TypeSpec).
%%
%% Cross Reference Check
%%
-
+%%-spec xm(module() | file:filename()) -> xref:m/1 return
xm(M) ->
appcall(tools, xref, m, [M]).
%%
%% Call yecc
%%
-
+%%-spec y(file:name()) -> yecc:file/2 return
y(File) -> y(File, []).
+%%-spec y(file:name(), [yecc:option()]) -> yecc:file/2 return
y(File, Opts) ->
- appcall(parsetools, yecc, file, [File,Opts]).
+ appcall(parsetools, yecc, file, [File, Opts]).
%%
@@ -699,4 +757,3 @@ appcall(App, M, F, Args) ->
erlang:raise(error, undef, Stk)
end
end.
-
diff --git a/lib/stdlib/src/dets_sup.erl b/lib/stdlib/src/dets_sup.erl
index 5c6caa787d..8ea2ba9b3f 100644
--- a/lib/stdlib/src/dets_sup.erl
+++ b/lib/stdlib/src/dets_sup.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2002-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(dets_sup).
@@ -22,9 +22,16 @@
-export([start_link/0, init/1]).
+-spec start_link() -> {'ok', pid()} | 'ignore' | {'error', term()}.
+
start_link() ->
supervisor:start_link({local, dets_sup}, dets_sup, []).
+-spec init([]) ->
+ {'ok', {{'simple_one_for_one', 4, 3600},
+ [{'dets', {'dets', 'istart_link', []},
+ 'temporary', 30000, 'worker', ['dets']}]}}.
+
init([]) ->
SupFlags = {simple_one_for_one, 4, 3600},
Child = {dets, {dets, istart_link, []}, temporary, 30000, worker, [dets]},
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 808e1a8926..786319d79c 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -994,7 +994,7 @@ inop_prec('#') -> {800,700,800};
inop_prec(':') -> {900,800,900};
inop_prec('.') -> {900,900,1000}.
--type pre_op() :: 'catch' | '+' | '-' | 'bnot' | '#'.
+-type pre_op() :: 'catch' | '+' | '-' | 'bnot' | 'not' | '#'.
-spec preop_prec(pre_op()) -> {0 | 600 | 700, 100 | 700 | 800}.
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 9f84e3639f..6fc234a16a 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(ets).
@@ -622,14 +622,14 @@ do_read_and_verify(ReadFun,InitState,Tab,FtOptions,HeadCount,Verify) ->
end,
{ok,Tab};
{ok,{FinalMD5State,FinalCount,['$end_of_table',LastInfo],_}} ->
- ECount = case lists:keysearch(count,1,LastInfo) of
- {value,{count,N}} ->
+ ECount = case lists:keyfind(count,1,LastInfo) of
+ {count,N} ->
N;
_ ->
false
end,
- EMD5 = case lists:keysearch(md5,1,LastInfo) of
- {value,{md5,M}} ->
+ EMD5 = case lists:keyfind(md5,1,LastInfo) of
+ {md5,M} ->
M;
_ ->
false
@@ -742,22 +742,21 @@ get_header_data(Name,true) ->
false ->
throw(badfile);
true ->
- Major = case lists:keysearch(major,1,L) of
- {value,{major,Maj}} ->
+ Major = case lists:keyfind(major,1,L) of
+ {major,Maj} ->
Maj;
_ ->
0
end,
- Minor = case lists:keysearch(minor,1,L) of
- {value,{minor,Min}} ->
+ Minor = case lists:keyfind(minor,1,L) of
+ {minor,Min} ->
Min;
_ ->
0
end,
FtOptions =
- case lists:keysearch(extended_info,1,L) of
- {value,{extended_info,I}}
- when is_list(I) ->
+ case lists:keyfind(extended_info,1,L) of
+ {extended_info,I} when is_list(I) ->
#filetab_options
{
object_count =
@@ -786,29 +785,28 @@ get_header_data(Name,true) ->
end;
get_header_data(Name, false) ->
- case wrap_chunk(Name,start,1,false) of
+ case wrap_chunk(Name, start, 1, false) of
{C,[Tup]} when is_tuple(Tup) ->
L = tuple_to_list(Tup),
case verify_header_mandatory(L) of
false ->
throw(badfile);
true ->
- Major = case lists:keysearch(major_version,1,L) of
- {value,{major_version,Maj}} ->
+ Major = case lists:keyfind(major_version, 1, L) of
+ {major_version, Maj} ->
Maj;
_ ->
0
end,
- Minor = case lists:keysearch(minor_version,1,L) of
- {value,{minor_version,Min}} ->
+ Minor = case lists:keyfind(minor_version, 1, L) of
+ {minor_version, Min} ->
Min;
_ ->
0
end,
FtOptions =
- case lists:keysearch(extended_info,1,L) of
- {value,{extended_info,I}}
- when is_list(I) ->
+ case lists:keyfind(extended_info, 1, L) of
+ {extended_info, I} when is_list(I) ->
#filetab_options
{
object_count =
@@ -825,25 +823,26 @@ get_header_data(Name, false) ->
throw(badfile)
end.
-md5_and_convert([],MD5State,Count) ->
+md5_and_convert([], MD5State, Count) ->
{[],MD5State,Count,[]};
-md5_and_convert([H|T],MD5State,Count) when is_binary(H) ->
+md5_and_convert([H|T], MD5State, Count) when is_binary(H) ->
case (catch binary_to_term(H)) of
{'EXIT', _} ->
md5_and_convert(T,MD5State,Count);
- ['$end_of_table',Dat] ->
- {[],MD5State,Count,['$end_of_table',Dat]};
+ ['$end_of_table',_Dat] = L ->
+ {[],MD5State,Count,L};
Term ->
- X = erlang:md5_update(MD5State,H),
- {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T,X,Count+1),
+ X = erlang:md5_update(MD5State, H),
+ {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T, X, Count+1),
{[Term | Rest],NewMD5,NewCount,NewLast}
end.
-scan_for_endinfo([],Count) ->
+
+scan_for_endinfo([], Count) ->
{[],Count,[]};
-scan_for_endinfo([['$end_of_table',Dat]],Count) ->
+scan_for_endinfo([['$end_of_table',Dat]], Count) ->
{['$end_of_table',Dat],Count,[]};
-scan_for_endinfo([Term|T],Count) ->
- {NewLast,NCount,Rest} = scan_for_endinfo(T,Count+1),
+scan_for_endinfo([Term|T], Count) ->
+ {NewLast,NCount,Rest} = scan_for_endinfo(T, Count+1),
{NewLast,NCount,[Term | Rest]}.
load_table(ReadFun, State, Tab) ->
@@ -852,19 +851,19 @@ load_table(ReadFun, State, Tab) ->
[] ->
{ok,NewState};
List ->
- ets:insert(Tab,List),
- load_table(ReadFun,NewState,Tab)
+ ets:insert(Tab, List),
+ load_table(ReadFun, NewState, Tab)
end.
create_tab(I) ->
- {value, {name, Name}} = lists:keysearch(name, 1, I),
- {value, {type, Type}} = lists:keysearch(type, 1, I),
- {value, {protection, P}} = lists:keysearch(protection, 1, I),
- {value, {named_table, Val}} = lists:keysearch(named_table, 1, I),
- {value, {keypos, Kp}} = lists:keysearch(keypos, 1, I),
- {value, {size, Sz}} = lists:keysearch(size, 1, I),
+ {name, Name} = lists:keyfind(name, 1, I),
+ {type, Type} = lists:keyfind(type, 1, I),
+ {protection, P} = lists:keyfind(protection, 1, I),
+ {named_table, Val} = lists:keyfind(named_table, 1, I),
+ {keypos, _Kp} = Keypos = lists:keyfind(keypos, 1, I),
+ {size, Sz} = lists:keyfind(size, 1, I),
try
- Tab = ets:new(Name, [Type, P, {keypos, Kp} | named_table(Val)]),
+ Tab = ets:new(Name, [Type, P, Keypos | named_table(Val)]),
{ok, Tab, Sz}
catch
_:_ ->
@@ -905,9 +904,9 @@ tabfile_info(File) when is_list(File) ; is_atom(File) ->
{value, Val} = lists:keysearch(named_table, 1, FullHeader),
{value, Kp} = lists:keysearch(keypos, 1, FullHeader),
{value, Sz} = lists:keysearch(size, 1, FullHeader),
- Ei = case lists:keysearch(extended_info, 1, FullHeader) of
- {value, Ei0} -> Ei0;
- _ -> {extended_info, []}
+ Ei = case lists:keyfind(extended_info, 1, FullHeader) of
+ false -> {extended_info, []};
+ Ei0 -> Ei0
end,
{ok, [N,Type,P,Val,Kp,Sz,Ei,{version,{Major,Minor}}]}
catch
@@ -1021,21 +1020,20 @@ options(Option, Keys) ->
options([Option], Keys, []).
options(Options, [Key | Keys], L) when is_list(Options) ->
- V = case lists:keysearch(Key, 1, Options) of
- {value, {n_objects, default}} ->
+ V = case lists:keyfind(Key, 1, Options) of
+ {n_objects, default} ->
{ok, default_option(Key)};
- {value, {n_objects, NObjs}} when is_integer(NObjs),
- NObjs >= 1 ->
+ {n_objects, NObjs} when is_integer(NObjs), NObjs >= 1 ->
{ok, NObjs};
- {value, {traverse, select}} ->
+ {traverse, select} ->
{ok, select};
- {value, {traverse, {select, MS}}} ->
- {ok, {select, MS}};
- {value, {traverse, first_next}} ->
+ {traverse, {select, _MS} = Select} ->
+ {ok, Select};
+ {traverse, first_next} ->
{ok, first_next};
- {value, {traverse, last_prev}} ->
+ {traverse, last_prev} ->
{ok, last_prev};
- {value, {Key, _}} ->
+ {Key, _} ->
badarg;
false ->
Default = default_option(Key),
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 1b30aaf5eb..27ff9441e6 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(gen_event).
@@ -42,7 +42,6 @@
system_continue/3,
system_terminate/4,
system_code_change/4,
- print_event/3,
format_status/2]).
-import(error_logger, [error_msg/2]).
@@ -239,7 +238,7 @@ fetch_msg(Parent, ServerName, MSL, Debug, Hib) ->
Msg when Debug =:= [] ->
handle_msg(Msg, Parent, ServerName, MSL, []);
Msg ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event},
+ Debug1 = sys:handle_debug(Debug, fun print_event/3,
ServerName, {in, Msg}),
handle_msg(Msg, Parent, ServerName, MSL, Debug1)
end.
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index ba0275ae2b..9961646418 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(gen_fsm).
@@ -116,7 +116,7 @@
-export([behaviour_info/1]).
%% Internal exports
--export([init_it/6, print_event/3,
+-export([init_it/6,
system_continue/3,
system_terminate/4,
system_code_change/4,
@@ -376,7 +376,7 @@ decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) ->
_Msg when Debug =:= [] ->
handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time);
_Msg ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event},
+ Debug1 = sys:handle_debug(Debug, fun print_event/3,
{Name, StateName}, {in, Msg}),
handle_msg(Msg, Parent, Name, StateName, StateData,
Mod, Time, Debug1)
@@ -466,11 +466,11 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, Debug) ->
From = from(Msg),
case catch dispatch(Msg, Mod, StateName, StateData) of
{next_state, NStateName, NStateData} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event},
+ Debug1 = sys:handle_debug(Debug, fun print_event/3,
{Name, NStateName}, return),
loop(Parent, Name, NStateName, NStateData, Mod, infinity, Debug1);
{next_state, NStateName, NStateData, Time1} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event},
+ Debug1 = sys:handle_debug(Debug, fun print_event/3,
{Name, NStateName}, return),
loop(Parent, Name, NStateName, NStateData, Mod, Time1, Debug1);
{reply, Reply, NStateName, NStateData} when From =/= undefined ->
@@ -519,7 +519,7 @@ reply({To, Tag}, Reply) ->
reply(Name, {To, Tag}, Reply, Debug, StateName) ->
reply({To, Tag}, Reply),
- sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ sys:handle_debug(Debug, fun print_event/3, Name,
{out, Reply, To, StateName}).
%%% ---------------------------------------------------
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index f1a9a31c63..1c9e5270b6 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. 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
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(gen_server).
@@ -103,7 +103,7 @@
format_status/2]).
%% Internal exports
--export([init_it/6, print_event/3]).
+-export([init_it/6]).
-import(error_logger, [format/2]).
@@ -353,7 +353,7 @@ decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) ->
_Msg when Debug =:= [] ->
handle_msg(Msg, Parent, Name, State, Mod);
_Msg ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event},
+ Debug1 = sys:handle_debug(Debug, fun print_event/3,
Name, {in, Msg}),
handle_msg(Msg, Parent, Name, State, Mod, Debug1)
end.
@@ -589,11 +589,11 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, Mod, Time1, Debug1);
{noreply, NState} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, infinity, Debug1);
{noreply, NState, Time1} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, Time1, Debug1);
{stop, Reason, Reply, NState} ->
@@ -625,11 +625,11 @@ handle_common_reply(Reply, Parent, Name, Msg, Mod, State) ->
handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug) ->
case Reply of
{noreply, NState} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, infinity, Debug1);
{noreply, NState, Time1} ->
- Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, Time1, Debug1);
{stop, Reason, NState} ->
@@ -642,7 +642,7 @@ handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug) ->
reply(Name, {To, Tag}, Reply, State, Debug) ->
reply({To, Tag}, Reply),
- sys:handle_debug(Debug, {?MODULE, print_event}, Name,
+ sys:handle_debug(Debug, fun print_event/3, Name,
{out, Reply, To, State} ).