Skip to content

Commit

Permalink
Merge pull request #8078 from the-mikedavis/code-server-where-is-file
Browse files Browse the repository at this point in the history
Use code_server path cache in code:where_is_file/1

OTP-19194
  • Loading branch information
kikofernandez authored Aug 20, 2024
2 parents 141120a + c8687e3 commit 44a56d6
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 3 deletions.
6 changes: 3 additions & 3 deletions lib/kernel/src/code.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1751,7 +1751,8 @@ file containing object code for `Module` and returns the absolute filename.
which(Module) when is_atom(Module) ->
case is_loaded(Module) of
false ->
which(Module, get_path());
File = atom_to_list(Module) ++ objfile_extension(),
where_is_file(File);
{file, File} ->
File
end.
Expand All @@ -1773,8 +1774,7 @@ locate application resource files.
Filename :: file:filename(),
Absname :: file:filename().
where_is_file(File) when is_list(File) ->
Path = get_path(),
where_is_file(Path, File).
call({where_is_file, File}).

%% To avoid unnecessary work when looking at many modules, this also
%% accepts pairs of directories and pre-fetched contents in the path
Expand Down
24 changes: 24 additions & 0 deletions lib/kernel/src/code_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -302,6 +302,11 @@ handle_call({replace_path,Name,Dir,Control}, _From,
handle_call(get_path, _From, S) ->
{reply,[P || {P, _Cache} <- S#state.path],S};

handle_call({where_is_file,File}, _From,
#state{path=Path,path_cache=Cache0}=S) ->
{Resp,Cache} = where_is_file(Path, File, Cache0),
{reply,Resp,S#state{path_cache=Cache}};

handle_call(clear_cache, _From, S) ->
{reply,ok,S#state{path_cache=#{}}};

Expand Down Expand Up @@ -1485,3 +1490,22 @@ archive_extension() ->

to_list(X) when is_list(X) -> X;
to_list(X) when is_atom(X) -> atom_to_list(X).

where_is_file([], _File, Cache) ->
{non_existing, Cache};
where_is_file([{Dir, nocache} | Tail], File, Cache) ->
Full = filename:append(Dir, File),
case erl_prim_loader:read_file_info(Full) of
{ok,_} ->
{Full, Cache};
_Error ->
where_is_file(Tail, File, Cache)
end;
where_is_file([{Dir, CacheKey} | Tail], File, Cache) when is_integer(CacheKey) ->
case with_cache(CacheKey, Dir, File, Cache) of
{true, Cache1} ->
Full = filename:append(Dir, File),
{Full, Cache1};
{false, Cache1} ->
where_is_file(Tail, File, Cache1)
end.

0 comments on commit 44a56d6

Please sign in to comment.