Skip to content

Commit

Permalink
Reduce contention on the code_server
Browse files Browse the repository at this point in the history
load_file/1, load_abs/2, and load_binary/3 now
perform most of the work on the client.

is_sticky/1 and is_loaded/1 now read directly
from the module database.
  • Loading branch information
josevalim committed Jan 25, 2023
1 parent bdf564f commit c1b4f25
Show file tree
Hide file tree
Showing 2 changed files with 79 additions and 79 deletions.
49 changes: 42 additions & 7 deletions lib/kernel/src/code.erl
Expand Up @@ -184,7 +184,10 @@ objfile_extension() ->
-spec load_file(Module) -> load_ret() when
Module :: module().
load_file(Mod) when is_atom(Mod) ->
call({load_file,Mod}).
case get_object_code(Mod) of
error -> {error,nofile};
{Mod,Binary,File} -> load_module(Mod, File, Binary, false)
end.

-spec ensure_loaded(Module) -> {module, Module} | {error, What} when
Module :: module(),
Expand All @@ -199,13 +202,24 @@ ensure_loaded(Mod) when is_atom(Mod) ->
-spec load_abs(Filename) -> load_ret() when
Filename :: file:filename().
load_abs(File) when is_list(File); is_atom(File) ->
Mod = list_to_atom(filename:basename(File)),
call({load_abs,File,Mod}).
load_abs(File, list_to_atom(filename:basename(File))).

%% XXX Filename is also an atom(), e.g. 'cover_compiled'
-spec load_abs(Filename :: loaded_filename(), Module :: module()) -> load_ret().
load_abs(File, M) when (is_list(File) orelse is_atom(File)), is_atom(M) ->
call({load_abs,File,M}).
case modp(File) of
true ->
FileName0 = lists:concat([File, objfile_extension()]),
FileName = code_server:absname(FileName0),
case erl_prim_loader:get_file(FileName) of
{ok,Bin,_} ->
load_module(M, FileName, Bin, false);
error ->
{error, nofile}
end;
false ->
{error,badarg}
end.

%% XXX Filename is also an atom(), e.g. 'cover_compiled'
-spec load_binary(Module, Filename, Binary) ->
Expand All @@ -216,7 +230,26 @@ load_abs(File, M) when (is_list(File) orelse is_atom(File)), is_atom(M) ->
What :: badarg | load_error_rsn().
load_binary(Mod, File, Bin)
when is_atom(Mod), (is_list(File) orelse is_atom(File)), is_binary(Bin) ->
call({load_binary,Mod,File,Bin}).
case modp(File) of
true -> load_module(Mod, File, Bin, true);
false -> {error,badarg}
end.

load_module(Mod, File, Bin, Purge) ->
case erlang:prepare_loading(Mod, Bin) of
{error,_}=Error ->
Error;
Prepared ->
call({load_module, Prepared, Mod, File, Purge})
end.

modp(Atom) when is_atom(Atom) -> true;
modp(List) when is_list(List) -> int_list(List);
modp(_) -> false.

int_list([H|T]) when is_integer(H) -> int_list(T);
int_list([_|_]) -> false;
int_list([]) -> true.

-spec load_native_partial(Module :: module(), Binary :: binary()) -> load_ret().
load_native_partial(Mod, Bin) when is_atom(Mod), is_binary(Bin) ->
Expand All @@ -243,7 +276,8 @@ soft_purge(Mod) when is_atom(Mod) -> call({soft_purge,Mod}).
-spec is_loaded(Module) -> {'file', Loaded} | false when
Module :: module(),
Loaded :: loaded_filename().
is_loaded(Mod) when is_atom(Mod) -> call({is_loaded,Mod}).
is_loaded(Mod) when is_atom(Mod) ->
code_server:is_loaded(Mod).

-spec get_object_code(Module) -> {Module, Binary, Filename} | error when
Module :: module(),
Expand Down Expand Up @@ -346,7 +380,8 @@ unstick_mod(Mod) when is_atom(Mod) -> call({unstick_mod,Mod}).

-spec is_sticky(Module) -> boolean() when
Module :: module().
is_sticky(Mod) when is_atom(Mod) -> call({is_sticky,Mod}).
is_sticky(Mod) when is_atom(Mod) ->
code_server:is_sticky(Mod).

-spec set_path(Path) -> 'true' | {'error', What} when
Path :: [Dir :: file:filename()],
Expand Down
109 changes: 37 additions & 72 deletions lib/kernel/src/code_server.erl
Expand Up @@ -22,7 +22,8 @@
%% This file holds the server part of the code_server.

-export([start_link/1,
call/1,
call/1, absname/1,
is_loaded/1, is_sticky/1,
system_code_change/4,
error_msg/2, info_msg/2
]).
Expand All @@ -31,6 +32,7 @@
-include_lib("stdlib/include/ms_transform.hrl").

-import(lists, [foreach/2]).
-define(moddb, code_server).

-type on_load_action() ::
fun((term(), state()) -> {'reply',term(),state()} |
Expand Down Expand Up @@ -58,6 +60,14 @@ start_link(Args) ->
{Ref,Res} -> Res
end.

is_loaded(Mod) ->
case ets:lookup(?moddb, Mod) of
[{Mod,File}] -> {file,File};
[] -> false
end.

is_sticky(Mod) ->
is_sticky(Mod, ?moddb).

%% -----------------------------------------------------------
%% Init the code_server process.
Expand All @@ -67,7 +77,7 @@ init(Ref, Parent, [Root,Mode]) ->
register(?MODULE, self()),
process_flag(trap_exit, true),

Db = ets:new(code, [private]),
Db = ets:new(?moddb, [named_table, protected]),
foreach(fun (M) ->
%% Pre-loaded modules are always sticky.
ets:insert(Db, [{M,preloaded},{{sticky,M},true}])
Expand Down Expand Up @@ -251,9 +261,6 @@ handle_call({dir,Dir}, _From, S) ->
Resp = do_dir(Root,Dir,S#state.namedb),
{reply,Resp,S};

handle_call({load_file,Mod}, From, St) when is_atom(Mod) ->
load_file(Mod, From, St);

handle_call({add_path,Where,Dir0}, _From,
#state{namedb=Namedb,path=Path0}=S) ->
{Resp,Path} = add_path(Where, Dir0, Path0, Namedb),
Expand Down Expand Up @@ -282,17 +289,12 @@ handle_call({replace_path,Name,Dir}, _From,
handle_call(get_path, _From, S) ->
{reply,S#state.path,S};

%% Messages to load, delete and purge modules/files.
handle_call({load_abs,File,Mod}, From, S) when is_atom(Mod) ->
case modp(File) of
false ->
{reply,{error,badarg},S};
true ->
load_abs(File, Mod, From, S)
end;

handle_call({load_binary,Mod,File,Bin}, From, S) when is_atom(Mod) ->
do_load_binary(Mod, File, Bin, From, S);
handle_call({load_module,PC,Mod,File,Purge}, From, S) when is_atom(Mod) ->
case Purge andalso erlang:module_loaded(Mod) of
true -> do_purge(Mod);
false -> ok
end,
try_finish_module(File, Mod, PC, From, S);

handle_call({ensure_loaded,Mod}, From, St) when is_atom(Mod) ->
case erlang:module_loaded(Mod) of
Expand All @@ -319,9 +321,6 @@ handle_call({purge,Mod}, _From, St) when is_atom(Mod) ->
handle_call({soft_purge,Mod}, _From, St) when is_atom(Mod) ->
{reply,do_soft_purge(Mod),St};

handle_call({is_loaded,Mod}, _From, St) when is_atom(Mod) ->
{reply,is_loaded(Mod, St#state.moddb),St};

handle_call(all_loaded, _From, S) ->
Db = S#state.moddb,
{reply,all_loaded(Db),S};
Expand All @@ -332,10 +331,6 @@ handle_call({get_object_code,Mod}, _From, St) when is_atom(Mod) ->
Error -> {reply,Error,St}
end;

handle_call({is_sticky, Mod}, _From, S) ->
Db = S#state.moddb,
{reply, is_sticky(Mod,Db), S};

handle_call(stop,_From, S) ->
{stop,normal,stopped,S};

Expand Down Expand Up @@ -1082,49 +1077,22 @@ add_paths(Where,[Dir|Tail],Path,NameDb) ->
add_paths(_,_,Path,_) ->
{ok,Path}.

do_load_binary(Module, File, Binary, From, St) ->
case modp(File) andalso is_binary(Binary) of
true ->
case erlang:module_loaded(Module) of
true -> do_purge(Module);
false -> ok
end,
try_load_module(File, Module, Binary, From, St);
false ->
{reply,{error,badarg},St}
end.

modp(Atom) when is_atom(Atom) -> true;
modp(List) when is_list(List) -> int_list(List);
modp(_) -> false.

load_abs(File, Mod, From, St) ->
Ext = objfile_extension(),
FileName0 = lists:concat([File, Ext]),
FileName = absname(FileName0),
case erl_prim_loader:get_file(FileName) of
{ok,Bin,_} ->
try_load_module(FileName, Mod, Bin, From, St);
error ->
{reply,{error,nofile},St}
end.

try_load_module(File, Mod, Bin, From, St) ->
try_finish_module(File, Mod, PC, From, St) ->
Action = fun(_, S) ->
try_load_module_1(File, Mod, Bin, From, S)
try_finish_module_1(File, Mod, PC, From, S)
end,
handle_pending_on_load(Action, Mod, From, St).

try_load_module_1(File, Mod, Bin, From, #state{moddb=Db}=St) ->
try_finish_module_1(File, Mod, PC, From, #state{moddb=Db}=St) ->
case is_sticky(Mod, Db) of
true -> %% Sticky file reject the load
error_msg("Can't load module '~w' that resides in sticky dir\n",[Mod]),
{reply,{error,sticky_directory},St};
false ->
try_load_module_2(File, Mod, Bin, From, undefined, St)
try_finish_module_2(File, Mod, PC, From, St)
end.

try_load_module_2(File, Mod, Bin, From, _Architecture, St0) ->
try_finish_module_2(File, Mod, PC, From, St0) ->
Action = fun({module,_}=Module, #state{moddb=Db}=S) ->
ets:insert(Db, {Mod,File}),
{reply,Module,S};
Expand All @@ -1134,7 +1102,12 @@ try_load_module_2(File, Mod, Bin, From, _Architecture, St0) ->
error_msg("Loading of ~ts failed: ~p\n", [File, What]),
{reply,Error,S}
end,
Res = erlang:load_module(Mod, Bin),
Res = case erlang:finish_loading([PC]) of
ok ->
{module,Mod};
{Error,[Mod]} ->
{error,Error}
end,
handle_on_load(Res, Action, Mod, From, St0).

int_list([H|T]) when is_integer(H) -> int_list(T);
Expand All @@ -1147,23 +1120,22 @@ ensure_loaded(Mod, From, St0) ->
true ->
{reply,{module,Mod},S};
false ->
load_file_1(Mod, From, S)
ensure_loaded_1(Mod, From, S)
end
end,
handle_pending_on_load(Action, Mod, From, St0).

load_file(Mod, From, St0) ->
Action = fun(_, S) ->
load_file_1(Mod, From, S)
end,
handle_pending_on_load(Action, Mod, From, St0).

load_file_1(Mod, From, St) ->
ensure_loaded_1(Mod, From, St) ->
case get_object_code(St, Mod) of
error ->
{reply,{error,nofile},St};
{Mod,Binary,File} ->
try_load_module_1(File, Mod, Binary, From, St)
case erlang:prepare_loading(Mod, Binary) of
{error, _} = Error ->
{reply, Error, St};
PC ->
try_finish_module_1(File, Mod, PC, From, St)
end
end.

get_object_code(#state{path=Path}, Mod) when is_atom(Mod) ->
Expand Down Expand Up @@ -1232,13 +1204,6 @@ absname_vr([[X, $:]|Name], _, _AbsBase) ->
end,
absname(filename:join(Name), Dcwd).


is_loaded(M, Db) ->
case ets:lookup(Db, M) of
[{M,File}] -> {file,File};
[] -> false
end.

do_purge(Mod) ->
{_WasOld, DidKill} = erts_code_purger:purge(Mod),
DidKill.
Expand Down

0 comments on commit c1b4f25

Please sign in to comment.