Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
2311-Read-.beam-files-for-cache-paths-in-the-cl...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2311-Read-.beam-files-for-cache-paths-in-the-client.patch of Package erlang
From de9942ecd7d8b955f7fd1b467298f389a8be74b8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co> Date: Wed, 27 Dec 2023 09:56:09 +0100 Subject: [PATCH 1/2] Read .beam files for cache paths in the client This reduces the amount of work on the code server and erl_prim_loader, by loading data on the client whenever possible. This is done by introducing erl_prim_loader:read_file/1, which stays closer to Erlang's file reading semantics. Future work should fully remove the concept of paths from erl_prim_loader and move them into init. --- erts/doc/src/erl_prim_loader.xml | 20 ++ erts/preloaded/src/erl_prim_loader.erl | 225 +++++++++++------- lib/debugger/src/int.erl | 9 +- lib/kernel/src/application_controller.erl | 8 +- lib/kernel/src/code.erl | 66 ++++- lib/kernel/src/code_server.erl | 80 ++----- lib/kernel/src/erl_boot_server.erl | 2 +- lib/kernel/src/inet_config.erl | 6 +- lib/kernel/src/inet_db.erl | 4 +- lib/reltool/src/reltool_utils.erl | 8 +- lib/sasl/src/release_handler_1.erl | 26 +- lib/ssl/src/ssl_dist_sup.erl | 4 +- lib/stdlib/src/shell.erl | 6 +- .../archive_script/archive_script_main.erl | 4 +- .../archive_script/archive_script_main2.erl | 4 +- .../archive_script_file_access.erl | 10 + 16 files changed, 288 insertions(+), 194 deletions(-) diff --git a/erts/doc/src/erl_prim_loader.xml b/erts/doc/src/erl_prim_loader.xml index e9f7d6745c..802ccb7f80 100644 --- a/erts/doc/src/erl_prim_loader.xml +++ b/erts/doc/src/erl_prim_loader.xml @@ -50,6 +50,8 @@ <name name="get_file" arity="1" since=""/> <fsummary>Get a file.</fsummary> <desc> + <p><em>Use of this function is deprecated + in favor of <c>read_file/1</c>.</em></p> <p>Fetches a file using the low-level loader. <c><anno>Filename</anno></c> is either an absolute filename or only the name of the file, for example, <c>"lists.beam"</c>. If an internal @@ -68,6 +70,8 @@ <name name="get_path" arity="0" since=""/> <fsummary>Get the path set in the loader.</fsummary> <desc> + <p><em>Use of this function is deprecated + in favor of <c>code:get_path/1</c>.</em></p> <p>Gets the path set in the loader. The path is set by the <seeerl marker="init"><c>init(3)</c></seeerl> process according to information found in the start script.</p> @@ -91,6 +95,22 @@ </desc> </func> + <func> + <name name="read_file" arity="1" since="OTP 27.0.0"/> + <fsummary>Reads a file.</fsummary> + <desc> + <p>Reads a file using the low-level loader. Returns + <c>{ok, <anno>Bin</anno>}</c> if successful, otherwise + <c>error</c>. <c><anno>Bin</anno></c> is the contents + of the file as a binary.</p> + <p><c><anno>Filename</anno></c> can also be a file in an archive, + for example, + <c>$OTPROOT/lib/</c><c>mnesia-4.4.7.ez/mnesia-4.4.7/ebin/</c><c>mnesia.beam</c>. + For information about archive files, see + <seeerl marker="kernel:code"><c>code(3)</c></seeerl>.</p> + </desc> + </func> + <func> <name name="read_file_info" arity="1" since=""/> <fsummary>Get information about a file.</fsummary> diff --git a/erts/preloaded/src/erl_prim_loader.erl b/erts/preloaded/src/erl_prim_loader.erl index 4442d00914..08197fa5ca 100644 --- a/erts/preloaded/src/erl_prim_loader.erl +++ b/erts/preloaded/src/erl_prim_loader.erl @@ -42,11 +42,11 @@ -include("inet_boot.hrl"). %% Public --export([start/0, set_path/1, get_path/0, get_file/1, +-export([start/0, set_path/1, get_path/0, get_file/1, read_file/1, list_dir/1, read_file_info/1, read_link_info/1, get_cwd/0, get_cwd/1]). %% Used by erl_boot_server --export([prim_init/0, prim_get_file/2, prim_list_dir/2, +-export([prim_init/0, prim_read_file/2, prim_list_dir/2, prim_read_file_info/3, prim_get_cwd/2]). %% Used by escript @@ -65,6 +65,7 @@ -record(prim_state, {debug :: boolean(), primary_archive}). -type prim_state() :: #prim_state{}. +-type archive() :: {archive, file:filename(), file:filename()}. -record(state, {loader :: 'efile' | 'inet', @@ -148,6 +149,7 @@ start_inet(Parent) -> data = Tcp, timeout = ?INET_IDLE_TIMEOUT, prim_state = PS}, + set_loader_config(inet), loop(State, Parent, []). start_efile(Parent) -> @@ -167,12 +169,18 @@ start_efile(Parent) -> data = noport, timeout = ?EFILE_IDLE_TIMEOUT, prim_state = PS}, + set_loader_config({efile, PS#prim_state.primary_archive}), loop(State, Parent, []). init_ack(Pid) -> Pid ! {self(),ok}, ok. +set_loader_config(Value) -> + persistent_term:put(?MODULE, Value). +get_loader_config() -> + persistent_term:get(?MODULE). + -spec set_path(Path) -> 'ok' when Path :: [Dir :: string()]. set_path(Paths) when is_list(Paths) -> @@ -196,27 +204,43 @@ get_file(File) -> Dir :: string(), Filenames :: [Filename :: string()]. list_dir(Dir) -> - check_file_result(list_dir, Dir, request({list_dir,Dir})). + check_file_result(list_dir, Dir, client_or_request(list_dir, Dir)). + +-spec read_file(Filename) -> {'ok', Bin} | 'error' when + Filename :: string(), + Bin :: binary(). +read_file(File) -> + check_file_result(read_file, File, client_or_request(read_file, File)). -spec read_file_info(Filename) -> {'ok', FileInfo} | 'error' when Filename :: string(), FileInfo :: file:file_info(). read_file_info(File) -> - check_file_result(read_file_info, File, request({read_file_info,File})). + check_file_result(read_file_info, File, client_or_request(read_file_info, File)). -spec read_link_info(Filename) -> {'ok', FileInfo} | 'error' when Filename :: string(), FileInfo :: file:file_info(). read_link_info(File) -> - check_file_result(read_link_info, File, request({read_link_info,File})). + check_file_result(read_link_info, File, client_or_request(read_link_info, File)). -spec get_cwd() -> {'ok', string()} | 'error'. get_cwd() -> - check_file_result(get_cwd, [], request({get_cwd,[]})). + Res = + case get_loader_config() of + {efile, _} -> prim_file:get_cwd(); + inet -> request({get_cwd,[]}) + end, + check_file_result(get_cwd, [], Res). -spec get_cwd(string()) -> {'ok', string()} | 'error'. get_cwd(Drive) -> - check_file_result(get_cwd, Drive, request({get_cwd,[Drive]})). + Res = + case get_loader_config() of + {efile, _} -> prim_file:get_cwd(Drive); + inet -> request({get_cwd,[Drive]}) + end, + check_file_result(get_cwd, Drive, Res). -spec set_primary_archive(File :: string() | 'undefined', ArchiveBin :: binary() | 'undefined', @@ -265,55 +289,65 @@ request(Req) -> error end. +client_or_request(Fun, File) -> + case get_loader_config() of + {efile, PrimaryArchive} -> + case name_split(PrimaryArchive, File) of + {file, SplitFile} -> prim_file:Fun(SplitFile); + {archive, _, _} = Archive -> request({Fun,Archive}) + end; + inet -> + request({Fun,File}) + end. + check_file_result(_, _, {error,enoent}) -> error; check_file_result(_, _, {error,enotdir}) -> error; check_file_result(_, _, {error,einval}) -> error; -check_file_result(Func, Target, {error,Reason}) -> - case (catch atom_to_list(Reason)) of - {'EXIT',_} -> % exit trapped - error; - Errno -> % errno - Process = case process_info(self(), registered_name) of - {registered_name,R} -> - "Process: " ++ atom_to_list(R) ++ "."; - _ -> - "" - end, - TargetStr = - if is_atom(Target) -> atom_to_list(Target); - is_list(Target) -> Target; - true -> [] - end, - Report = - case TargetStr of - [] -> - "File operation error: " ++ Errno ++ ". " ++ - "Function: " ++ atom_to_list(Func) ++ ". " ++ Process; - _ -> - "File operation error: " ++ Errno ++ ". " ++ - "Target: " ++ TargetStr ++ ". " ++ - "Function: " ++ atom_to_list(Func) ++ ". " ++ Process - end, - %% This is equal to calling logger:error/2 which - %% we don't want to do from code_server during system boot. - %% We don't want to call logger:timestamp() either. - _ = try - logger ! {log,error,#{label=>{?MODULE,file_error},report=>Report}, - #{pid=>self(), - gl=>group_leader(), - time=>os:system_time(microsecond), - error_logger=>#{tag=>error_report, - type=>std_error}}} - catch _:_ -> - %% If logger has not been started yet we just display it - erlang:display({?MODULE,file_error}), - erlang:display(Report) - end, - error - end; +check_file_result(Func, Target, {error,Reason}) when is_atom(Reason) -> + Errno = atom_to_list(Reason), + Process = + case process_info(self(), registered_name) of + {registered_name,R} -> + "Process: " ++ atom_to_list(R) ++ "."; + _ -> + "" + end, + TargetStr = + if is_atom(Target) -> atom_to_list(Target); + is_list(Target) -> Target; + true -> [] + end, + Report = + case TargetStr of + [] -> + "File operation error: " ++ Errno ++ ". " ++ + "Function: " ++ atom_to_list(Func) ++ ". " ++ Process; + _ -> + "File operation error: " ++ Errno ++ ". " ++ + "Target: " ++ TargetStr ++ ". " ++ + "Function: " ++ atom_to_list(Func) ++ ". " ++ Process + end, + %% This is equal to calling logger:error/2 which + %% we don't want to do from code_server during system boot. + %% We don't want to call logger:timestamp() either. + _ = try + logger ! {log,error,#{label=>{?MODULE,file_error},report=>Report}, + #{pid=>self(), + gl=>group_leader(), + time=>os:system_time(microsecond), + error_logger=>#{tag=>error_report, + type=>std_error}}} + catch _:_ -> + %% If logger has not been started yet we just display it + erlang:display({?MODULE,file_error}), + erlang:display(Report) + end, + error; +check_file_result(_, _, {error, _}) -> + error; check_file_result(_, _, Other) -> Other. @@ -361,6 +395,8 @@ handle_request(Req, Paths, St0) -> handle_get_modules(St0, Modules, Fun, ModPaths); {list_dir,Dir} -> handle_list_dir(St0, Dir); + {read_file,File} -> + handle_read_file(St0, File); {read_file_info,File} -> handle_read_file_info(St0, File); {read_link_info,File} -> @@ -395,6 +431,11 @@ handle_list_dir(State = #state{loader = efile}, Dir) -> handle_list_dir(State = #state{loader = inet}, Dir) -> ?SAFE2(inet_list_dir(State, Dir), State). +handle_read_file(State = #state{loader = efile}, File) -> + ?SAFE2(efile_read_file(State, File), State); +handle_read_file(State = #state{loader = inet}, File) -> + ?SAFE2(inet_read_file(State, File), State). + handle_read_file_info(State = #state{loader = efile}, File) -> ?SAFE2(efile_read_file_info(State, File, true), State); handle_read_file_info(State = #state{loader = inet}, File) -> @@ -405,8 +446,6 @@ handle_read_link_info(State = #state{loader = efile}, File) -> handle_read_link_info(State = #state{loader = inet}, File) -> ?SAFE2(inet_read_link_info(State, File), State). -handle_get_cwd(State = #state{loader = efile}, Drive) -> - ?SAFE2(efile_get_cwd(State, Drive), State); handle_get_cwd(State = #state{loader = inet}, Drive) -> ?SAFE2(inet_get_cwd(State, Drive), State). @@ -442,10 +481,8 @@ efile_get_file_from_port(State, File, Paths) -> end. efile_get_file_from_port2(#state{prim_state = PS} = State, File) -> - {Res, PS2} = prim_get_file(PS, File), + {Res, PS2} = prim_read_file(PS, File), case Res of - {error,port_died} -> - exit('prim_load port died'); {error,Reason} -> {{error,Reason},State#state{prim_state = PS2}}; {ok,BinFile} -> @@ -471,18 +508,19 @@ efile_set_primary_archive(#state{prim_state = PS} = State, File, ArchiveBin, FileInfo, ParserFun) -> {Res, PS2} = prim_set_primary_archive(PS, File, ArchiveBin, FileInfo, ParserFun), + set_loader_config({efile, PS2#prim_state.primary_archive}), {Res,State#state{prim_state = PS2}}. efile_list_dir(#state{prim_state = PS} = State, Dir) -> {Res, PS2} = prim_list_dir(PS, Dir), {Res, State#state{prim_state = PS2}}. -efile_read_file_info(#state{prim_state = PS} = State, File, FollowLinks) -> - {Res, PS2} = prim_read_file_info(PS, File, FollowLinks), +efile_read_file(#state{prim_state = PS} = State, File) -> + {Res, PS2} = prim_read_file(PS, File), {Res, State#state{prim_state = PS2}}. -efile_get_cwd(#state{prim_state = PS} = State, Drive) -> - {Res, PS2} = prim_get_cwd(PS, Drive), +efile_read_file_info(#state{prim_state = PS} = State, File, FollowLinks) -> + {Res, PS2} = prim_read_file_info(PS, File, FollowLinks), {Res, State#state{prim_state = PS2}}. efile_timeout_handler(State, _Parent) -> @@ -720,39 +758,44 @@ inet_timeout_handler(State, _Parent) -> inet_get_file_from_port(State, File, Paths) -> case is_basename(File) of false -> % get absolute file name. - inet_send_and_rcv({get,File}, File, State); + inet_get_file_from_port1(File, State); true when Paths =:= [] -> % get plain file name. - inet_send_and_rcv({get,File}, File, State); + inet_get_file_from_port1(File, State); true -> % use paths. - inet_get_file_from_port1(File, Paths, State) + inet_get_file_from_port2(File, Paths, State) + end. + +inet_get_file_from_port1(File, State0) -> + {Res, State1} = inet_send_and_rcv({get,File}, State0), + case Res of + {ok, BinFile} -> {{ok, BinFile, File}, State1}; + Other -> {Other, State1} end. -inet_get_file_from_port1(File, [P | Paths], State) -> +inet_get_file_from_port2(File, [P | Paths], State) -> File1 = join(P, File), - case inet_send_and_rcv({get,File1}, File1, State) of + case inet_get_file_from_port1(File1, State) of {{error,Reason},State1} -> case Paths of [] -> % return last error {{error,Reason},State1}; _ -> % try more paths - inet_get_file_from_port1(File, Paths, State1) + inet_get_file_from_port2(File, Paths, State1) end; Result -> Result end; -inet_get_file_from_port1(_File, [], State) -> +inet_get_file_from_port2(_File, [], State) -> {{error,file_not_found},State}. -inet_send_and_rcv(Msg, Tag, State) when State#state.data =:= noport -> - {ok,Tcp} = find_master(State#state.hosts), %% reconnect - inet_send_and_rcv(Msg, Tag, State#state{data = Tcp, - timeout = ?INET_IDLE_TIMEOUT}); -inet_send_and_rcv(Msg, Tag, #state{data = Tcp, timeout = Timeout} = State) -> +inet_send_and_rcv(Msg, State0) when State0#state.data =:= noport -> + {ok,Tcp} = find_master(State0#state.hosts), %% reconnect + State1 = State0#state{data = Tcp, timeout = ?INET_IDLE_TIMEOUT}, + inet_send_and_rcv(Msg, State1); +inet_send_and_rcv(Msg, #state{data = Tcp, timeout = Timeout} = State) -> prim_inet:send(Tcp, term_to_binary(Msg)), receive {tcp,Tcp,BinMsg} -> case catch binary_to_term(BinMsg) of - {get,{ok,BinFile}} -> - {{ok,BinFile,Tag},State}; {_Cmd,Res={ok,_}} -> {Res,State}; {_Cmd,{error,Error}} -> @@ -764,35 +807,39 @@ inet_send_and_rcv(Msg, Tag, #state{data = Tcp, timeout = Timeout} = State) -> end; {tcp_closed,Tcp} -> %% Ok we must reconnect - inet_send_and_rcv(Msg, Tag, State#state{data = noport}); + inet_send_and_rcv(Msg, State#state{data = noport}); {tcp_error,Tcp,_Reason} -> %% Ok we must reconnect - inet_send_and_rcv(Msg, Tag, inet_stop_port(State)); + inet_send_and_rcv(Msg, inet_stop_port(State)); {'EXIT', Tcp, _} -> %% Ok we must reconnect - inet_send_and_rcv(Msg, Tag, State#state{data = noport}) + inet_send_and_rcv(Msg, State#state{data = noport}) after Timeout -> %% Ok we must reconnect - inet_send_and_rcv(Msg, Tag, inet_stop_port(State)) + inet_send_and_rcv(Msg, inet_stop_port(State)) end. %% -> {{ok,List},State} | {{error,Reason},State} inet_list_dir(State, Dir) -> - inet_send_and_rcv({list_dir,Dir}, list_dir, State). + inet_send_and_rcv({list_dir,Dir}, State). + +%% -> {{ok,Binary},State} | {{error,Reason},State} +inet_read_file(State, File) -> + inet_send_and_rcv({get,File}, State). %% -> {{ok,Info},State} | {{error,Reason},State} inet_read_file_info(State, File) -> - inet_send_and_rcv({read_file_info,File}, read_file_info, State). + inet_send_and_rcv({read_file_info,File}, State). %% -> {{ok,Info},State} | {{error,Reason},State} inet_read_link_info(State, File) -> - inet_send_and_rcv({read_link_info,File}, read_link_info, State). + inet_send_and_rcv({read_link_info,File}, State). %% -> {{ok,Cwd},State} | {{error,Reason},State} inet_get_cwd(State, []) -> - inet_send_and_rcv(get_cwd, get_cwd, State); + inet_send_and_rcv(get_cwd, State); inet_get_cwd(State, [Drive]) -> - inet_send_and_rcv({get_cwd,Drive}, get_cwd, State). + inet_send_and_rcv({get_cwd,Drive}, State). inet_stop_port(#state{data=Tcp}=State) -> prim_inet:close(Tcp), @@ -930,16 +977,16 @@ prim_set_primary_archive(PS, ArchiveFile0, ArchiveBin, debug(PS3, {return, Res3}), {Res3, PS3}. --spec prim_get_file(prim_state(), file:filename()) -> {_, prim_state()}. -prim_get_file(PS, File) -> - debug(PS, {get_file, File}), +-spec prim_read_file(prim_state(), file:filename() | archive()) -> {_, prim_state()}. +prim_read_file(PS, File) -> + debug(PS, {read_file, File}), {Res2, PS2} = case name_split(PS#prim_state.primary_archive, File) of {file, PrimFile} -> Res = prim_file:read_file(PrimFile), {Res, PS}; {archive, ArchiveFile, FileInArchive} -> - debug(PS, {archive_get_file, ArchiveFile, FileInArchive}), + debug(PS, {archive_read_file, ArchiveFile, FileInArchive}), FileComponents = path_split(FileInArchive), Fun = fun({Components, _GetInfo, GetBin}, Acc) -> @@ -955,7 +1002,7 @@ prim_get_file(PS, File) -> debug(PS, {return, Res2}), {Res2, PS2}. --spec prim_list_dir(prim_state(), file:filename()) -> +-spec prim_list_dir(prim_state(), file:filename() | archive()) -> {{'ok', [file:filename()]}, prim_state()} | {{'error', term()}, prim_state()}. prim_list_dir(PS, Dir) -> @@ -1008,7 +1055,7 @@ prim_list_dir(PS, Dir) -> debug(PS, {return, Res2}), {Res2, PS3}. --spec prim_read_file_info(prim_state(), file:filename(), boolean()) -> +-spec prim_read_file_info(prim_state(), file:filename() | archive(), boolean()) -> {{'ok', #file_info{}}, prim_state()} | {{'error', term()}, prim_state()}. prim_read_file_info(PS, File, FollowLinks) -> @@ -1325,6 +1372,8 @@ path_join([Path],Acc) -> path_join([Path|Paths],Acc) -> path_join(Paths,"/" ++ reverse(Path) ++ Acc). +name_split(_PrimaryArchive, {archive, _, _} = Archive) -> + Archive; name_split(undefined, File) -> %% Ignore primary archive RevExt = reverse(init:archive_extension()), diff --git a/lib/debugger/src/int.erl b/lib/debugger/src/int.erl index 6f4790d7ed..60e4425f19 100644 --- a/lib/debugger/src/int.erl +++ b/lib/debugger/src/int.erl @@ -650,8 +650,8 @@ load({Mod, Src, Beam, BeamBin, Exp, Abst}, Dist) -> erts_debug:breakpoint({Mod,'_','_'}, false), {module,Mod} = code:load_binary(Mod, Beam, BeamBin) end), - case erl_prim_loader:get_file(filename:absname(Src)) of - {ok, SrcBin, _} -> + case erl_prim_loader:read_file(filename:absname(Src)) of + {ok, SrcBin} -> MD5 = code:module_md5(BeamBin), SrcBin1 = unicode:characters_to_binary(SrcBin, enc(SrcBin)), true = is_binary(SrcBin1), @@ -790,7 +790,7 @@ check_beam(BeamBin) when is_binary(BeamBin) -> error end; check_beam(Beam) when is_list(Beam) -> - {ok, Bin, _FullPath} = erl_prim_loader:get_file(filename:absname(Beam)), + {ok, Bin} = erl_prim_loader:read_file(filename:absname(Beam)), check_beam(Bin). is_file(Name) -> @@ -806,8 +806,7 @@ everywhere(local, Fun) -> scan_module_name(File) -> try - {ok, Bin, _FullPath} = - erl_prim_loader:get_file(filename:absname(File)), + {ok, Bin} = erl_prim_loader:read_file(filename:absname(File)), scan_module_name_1([], <<>>, Bin, enc(Bin)) catch _:_ -> diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl index 60080c155e..1f936653bb 100644 --- a/lib/kernel/src/application_controller.erl +++ b/lib/kernel/src/application_controller.erl @@ -1494,8 +1494,8 @@ make_appl(Application) -> {ok, make_appl_i(Application)}. prim_consult(FullName) -> - case erl_prim_loader:get_file(FullName) of - {ok, Bin, _} -> + case erl_prim_loader:read_file(FullName) of + {ok, Bin} -> case file_binary_to_list(Bin) of {ok, String} -> case erl_scan:string(String) of @@ -1969,8 +1969,8 @@ check_conf_sys([], SysEnv, Errors, _) -> load_file(File) -> %% We can't use file:consult/1 here. Too bad. - case erl_prim_loader:get_file(File) of - {ok, Bin, _FileName} -> + case erl_prim_loader:read_file(File) of + {ok, Bin} -> %% Make sure that there is some whitespace at the end of the string %% (so that reading a file with no NL following the "." will work). case file_binary_to_list(Bin) of diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl index 304638e0a6..a68595c262 100644 --- a/lib/kernel/src/code.erl +++ b/lib/kernel/src/code.erl @@ -201,7 +201,7 @@ ensure_loaded(Mod) when is_atom(Mod) -> {module, Mod} -> {module, Mod}; {error, What} -> {error, What}; {Binary,File,Ref} -> - case erlang:prepare_loading(Mod, Binary) of + case ensure_prepare_loading(Mod, Binary, File) of {error,_}=Error -> call({load_error, Ref, Mod, Error}); Prepared -> @@ -210,6 +210,14 @@ ensure_loaded(Mod) when is_atom(Mod) -> end end. +ensure_prepare_loading(Mod, missing, File) -> + case erl_prim_loader:read_file(File) of + {ok, Binary} -> erlang:prepare_loading(Mod, Binary); + error -> {error, nofile} + end; +ensure_prepare_loading(Mod, Binary, _File) -> + erlang:prepare_loading(Mod, Binary). + %% XXX File as an atom is allowed only for backwards compatibility. -spec load_abs(Filename) -> load_ret() when Filename :: file:filename(). @@ -223,8 +231,8 @@ load_abs(File, M) when (is_list(File) orelse is_atom(File)), is_atom(M) -> true -> FileName0 = lists:concat([File, objfile_extension()]), FileName = code_server:absname(FileName0), - case erl_prim_loader:get_file(FileName) of - {ok,Bin,_} -> + case erl_prim_loader:read_file(FileName) of + {ok,Bin} -> load_module(M, FileName, Bin, false); error -> {error, nofile} @@ -285,7 +293,16 @@ is_loaded(Mod) when is_atom(Mod) -> Module :: module(), Binary :: binary(), Filename :: file:filename(). -get_object_code(Mod) when is_atom(Mod) -> call({get_object_code, Mod}). +get_object_code(Mod) when is_atom(Mod) -> + case call({get_object_code, Mod}) of + {Module, missing, File} -> + case erl_prim_loader:read_file(File) of + {ok, Binary} -> {Module, Binary, File}; + error -> error + end; + {_, _, _} = MBF -> MBF; + error -> error + end. -spec all_loaded() -> [{Module, Loaded}] when Module :: module(), @@ -393,7 +410,26 @@ set_path(PathList) -> set_path(PathList, nocache). -spec set_path(Path, cache()) -> set_path_ret() when Path :: [Dir :: file:filename()]. set_path(PathList, Cache) when is_list(PathList), ?is_cache(Cache) -> - call({set_path,PathList,Cache}). + case normalize_paths(PathList, [], ok) of + {ok, Normalized} -> + call({set_path,Normalized,Cache}); + {error, _} -> + {error, bad_directory} + end. + +%% Atoms are supported only for backwards compatibility purposes. +%% They are not part of the typespec. +normalize_paths([P|Path], Acc, Status) when is_atom(P) -> + normalize_paths(Path, [atom_to_list(P)|Acc], Status); +normalize_paths([P|Path], Acc, Status) when is_list(P) -> + case int_list(P) of + true -> normalize_paths(Path, [filename:join([P]) | Acc], Status); + false -> normalize_paths(Path, Acc, error) + end; +normalize_paths([_|Path], Acc, _Status) -> + normalize_paths(Path, Acc, error); +normalize_paths([], Acc, Status) -> + {Status, lists:reverse(Acc)}. -spec get_path() -> Path when Path :: [Dir :: file:filename()]. @@ -406,7 +442,7 @@ add_path(Dir) -> add_path(Dir, nocache). -spec add_path(Dir, cache()) -> add_path_ret() when Dir :: file:filename(). -add_path(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> call({add_path,last,Dir,Cache}). +add_path(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> add_pathz(Dir, Cache). -spec add_pathz(Dir) -> add_path_ret() when Dir :: file:filename(). @@ -414,7 +450,9 @@ add_pathz(Dir) -> add_pathz(Dir, nocache). -spec add_pathz(Dir, cache()) -> add_path_ret() when Dir :: file:filename(). -add_pathz(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> call({add_path,last,Dir,Cache}). +add_pathz(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> + {_, [Normalized]} = normalize_paths([Dir], [], ok), + call({add_path,last,Normalized,Cache}). -spec add_patha(Dir) -> add_path_ret() when Dir :: file:filename(). @@ -422,7 +460,9 @@ add_patha(Dir) -> add_patha(Dir, nocache). -spec add_patha(Dir, cache()) -> add_path_ret() when Dir :: file:filename(). -add_patha(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> call({add_path,first,Dir,Cache}). +add_patha(Dir, Cache) when is_list(Dir), ?is_cache(Cache) -> + {_, [Normalized]} = normalize_paths([Dir], [], ok), + call({add_path,first,Normalized,Cache}). -spec add_paths(Dirs) -> 'ok' when Dirs :: [Dir :: file:filename()]. @@ -430,7 +470,7 @@ add_paths(Dirs) -> add_paths(Dirs, nocache). -spec add_paths(Dirs, cache()) -> 'ok' when Dirs :: [Dir :: file:filename()]. -add_paths(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> call({add_paths,last,Dirs,Cache}). +add_paths(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> add_pathsz(Dirs, Cache). -spec add_pathsz(Dirs) -> 'ok' when Dirs :: [Dir :: file:filename()]. @@ -438,7 +478,9 @@ add_pathsz(Dirs) -> add_pathsz(Dirs, nocache). -spec add_pathsz(Dirs, cache()) -> 'ok' when Dirs :: [Dir :: file:filename()]. -add_pathsz(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> call({add_paths,last,Dirs,Cache}). +add_pathsz(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> + {_, Normalized} = normalize_paths(Dirs, [], ok), + call({add_paths,last,Normalized,Cache}). -spec add_pathsa(Dirs) -> 'ok' when Dirs :: [Dir :: file:filename()]. @@ -446,7 +488,9 @@ add_pathsa(Dirs) -> add_pathsa(Dirs, nocache). -spec add_pathsa(Dirs, cache()) -> 'ok' when Dirs :: [Dir :: file:filename()]. -add_pathsa(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> call({add_paths,first,Dirs,Cache}). +add_pathsa(Dirs, Cache) when is_list(Dirs), ?is_cache(Cache) -> + {_, Normalized} = normalize_paths(Dirs, [], ok), + call({add_paths,first,Normalized,Cache}). -spec del_path(NameOrDir) -> boolean() | {'error', What} when NameOrDir :: Name | Dir, diff --git a/lib/kernel/src/code_server.erl b/lib/kernel/src/code_server.erl index b96589fbf7..78f8cee98e 100644 --- a/lib/kernel/src/code_server.erl +++ b/lib/kernel/src/code_server.erl @@ -728,25 +728,17 @@ do_check_path([Dir | Tail], PathChoice, ArchiveExt, Acc) -> %% %% Add new path(s). %% -add_path(Where,Dir,Path,Cache,NameDb) when is_atom(Dir) -> - add_path(Where,atom_to_list(Dir),Path,Cache,NameDb); add_path(Where,Dir0,Path,Cache,NameDb) when is_list(Dir0) -> - case int_list(Dir0) of - true -> - Dir = filename:join([Dir0]), % Normalize - case check_path([Dir]) of - {ok, [NewDir]} -> - {true, do_add(Where,NewDir,Path,Cache,NameDb)}; - Error -> - {Error, Path} - end; - false -> - {{error, bad_directory}, Path} + Dir = filename:join([Dir0]), % Normalize + case check_path([Dir]) of + {ok, [NewDir]} -> + {true, do_add(Where,NewDir,Path,Cache,NameDb)}; + Error -> + {Error, Path} end; add_path(_,_,Path,_,_) -> {{error, bad_directory}, Path}. - %% %% If the new directory is added first or if the directory didn't exist %% the name-directory table must be updated. @@ -777,8 +769,7 @@ update(Dir, NameDb) -> %% %% Set a completely new path. %% -set_path(NewPath0, OldPath, Cache, NameDb, Root) -> - NewPath = normalize(NewPath0), +set_path(NewPath, OldPath, Cache, NameDb, Root) -> case check_path(NewPath) of {ok, NewPath2} -> ets:delete(NameDb), @@ -789,25 +780,6 @@ set_path(NewPath0, OldPath, Cache, NameDb, Root) -> {Error, OldPath, NameDb} end. -%% -%% Normalize the given path. -%% The check_path function catches erroneous path, -%% thus it is ignored here. -%% -normalize([P|Path]) when is_atom(P) -> - normalize([atom_to_list(P)|Path]); -normalize([P|Path]) when is_list(P) -> - case int_list(P) of - true -> [filename:join([P])|normalize(Path)]; - false -> [P|normalize(Path)] - end; -normalize([P|Path]) -> - [P|normalize(Path)]; -normalize([]) -> - []; -normalize(Other) -> - Other. - %% Handle a table of name-directory pairs. %% The priv_dir/1 and lib_dir/1 functions will have %% an O(1) lookup. @@ -1168,10 +1140,6 @@ try_finish_module_2(File, Mod, PC, From, EnsureLoaded, St0) -> end, handle_on_load(Res, Action, Mod, From, St0). -int_list([H|T]) when is_integer(H) -> int_list(T); -int_list([_|_]) -> false; -int_list([]) -> true. - get_object_code(#state{path=Path} = St, Mod) when is_atom(Mod) -> ModStr = atom_to_list(Mod), case erl_prim_loader:is_basename(ModStr) of @@ -1241,23 +1209,23 @@ loader_down(#state{loading = Loading0} = St, {Mod, Bin, FName}) -> St end. +mod_to_bin([{Dir, nocache}|Tail], ModFile, Acc) -> + File = filename:append(Dir, ModFile), + + case erl_prim_loader:read_file(File) of + error -> + mod_to_bin(Tail, ModFile, [{Dir, nocache} | Acc]); + + {ok,Bin} -> + Path = lists:reverse(Acc, [{Dir, nocache} | Tail]), + {Bin, absname_when_relative(File), Path} + end; mod_to_bin([{Dir, Cache0}|Tail], ModFile, Acc) -> case with_cache(Cache0, Dir, ModFile) of {true, Cache1} -> File = filename:append(Dir, ModFile), - - case erl_prim_loader:get_file(File) of - error -> - mod_to_bin(Tail, ModFile, [{Dir, Cache1} | Acc]); - - {ok,Bin,_} -> - Path = lists:reverse(Acc, [{Dir, Cache1} | Tail]), - - case filename:pathtype(File) of - absolute -> {Bin, File, Path}; - _ -> {Bin, absname(File), Path} - end - end; + Path = lists:reverse(Acc, [{Dir, Cache1} | Tail]), + {missing, absname_when_relative(File), Path}; {false, Cache1} -> mod_to_bin(Tail, ModFile, [{Dir, Cache1} | Acc]) end; @@ -1270,8 +1238,6 @@ mod_to_bin([], ModFile, Acc) -> {Bin, absname(FName), lists:reverse(Acc)} end. -with_cache(nocache, _Dir, _ModFile) -> - {true, nocache}; with_cache(cache, Dir, ModFile) -> case erl_prim_loader:list_dir(Dir) of {ok, Entries} -> with_cache(maps:from_keys(Entries, []), Dir, ModFile); @@ -1280,6 +1246,12 @@ with_cache(cache, Dir, ModFile) -> with_cache(Cache, _Dir, ModFile) when is_map(Cache) -> {is_map_key(ModFile, Cache), Cache}. +absname_when_relative(File) -> + case filename:pathtype(File) of + absolute -> File; + _ -> absname(File) + end. + absname(File) -> case erl_prim_loader:get_cwd() of {ok,Cwd} -> absname(File, Cwd); diff --git a/lib/kernel/src/erl_boot_server.erl b/lib/kernel/src/erl_boot_server.erl index adbf1bdbcf..27138687f8 100644 --- a/lib/kernel/src/erl_boot_server.erl +++ b/lib/kernel/src/erl_boot_server.erl @@ -333,7 +333,7 @@ boot_loop(Socket, PS) -> handle_command(S, PS, Msg) -> case catch binary_to_term(Msg) of {get,File} -> - {Res, PS2} = erl_prim_loader:prim_get_file(PS, File), + {Res, PS2} = erl_prim_loader:prim_read_file(PS, File), send_file_result(S, get, Res), PS2; {list_dir,Dir} -> diff --git a/lib/kernel/src/inet_config.erl b/lib/kernel/src/inet_config.erl index 3b4c4287bc..b48b362108 100644 --- a/lib/kernel/src/inet_config.erl +++ b/lib/kernel/src/inet_config.erl @@ -458,12 +458,8 @@ get_rc(File) -> error end. -%% XXX Check if we really need to prim load the stuff get_file(File) -> - case erl_prim_loader:get_file(File) of - {ok,Bin,_} -> {ok,Bin}; - Error -> Error - end. + erl_prim_loader:read_file(File). error(Fmt, Args) -> error_logger:error_msg("inet_config: " ++ Fmt, Args). diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl index 6b4a0d4450..80f0d4527c 100644 --- a/lib/kernel/src/inet_db.erl +++ b/lib/kernel/src/inet_db.erl @@ -1345,8 +1345,8 @@ handle_update_file( %% File updated - read content ets:insert(Db, {TagInfo, Finfo_1}), Bin = - case erl_prim_loader:get_file(File) of - {ok, B, _} -> B; + case erl_prim_loader:read_file(File) of + {ok, B} -> B; _ -> <<>> end, handle_set_file(ParseFun, File, Bin, From, State); diff --git a/lib/reltool/src/reltool_utils.erl b/lib/reltool/src/reltool_utils.erl index 186fcfd00c..f247c1ef64 100644 --- a/lib/reltool/src/reltool_utils.erl +++ b/lib/reltool/src/reltool_utils.erl @@ -120,8 +120,8 @@ prim_consult(Bin) when is_binary(Bin) -> {error, Module:format_error(Reason)} end; prim_consult(FullName) when is_list(FullName) -> - case erl_prim_loader:get_file(FullName) of - {ok, Bin, _} -> + case erl_prim_loader:read_file(FullName) of + {ok, Bin} -> prim_consult(Bin); error -> {error, file:format_error(enoent)} @@ -575,8 +575,8 @@ recursive_copy_file(From, To) -> end. copy_file(From, To) -> - case erl_prim_loader:get_file(From) of - {ok, Bin, _} -> + case erl_prim_loader:read_file(From) of + {ok, Bin} -> case file:write_file(To, Bin) of ok -> FromInfo = read_file_info(From), diff --git a/lib/sasl/src/release_handler_1.erl b/lib/sasl/src/release_handler_1.erl index 3a5883dfb9..b69bd43572 100644 --- a/lib/sasl/src/release_handler_1.erl +++ b/lib/sasl/src/release_handler_1.erl @@ -314,10 +314,10 @@ eval({load_object_code, {Lib, LibVsn, Modules}}, EvalState) -> lists:foldl(fun(Mod, {Bins, Vsns}) -> File = lists:concat([Mod, Ext]), FName = root_dir_relative_path(filename:join([LibDir, "ebin", File])), - case erl_prim_loader:get_file(FName) of - {ok, Bin, FName2} -> + case erl_prim_loader:read_file(FName) of + {ok, Bin} -> NVsns = add_vsns(Mod, Bin, Vsns), - {[{Mod, Bin, FName2} | Bins],NVsns}; + {[{Mod, Bin, FName} | Bins],NVsns}; error -> throw({error, {no_such_file,FName}}) end @@ -774,14 +774,18 @@ replace_undefined(Vsn,_) -> Vsn. %% Returns: Vsn = term() %%----------------------------------------------------------------- get_current_vsn(Mod) -> - File = code:which(Mod), - case erl_prim_loader:get_file(File) of - {ok, Bin, _File2} -> - get_vsn(Bin); - error -> - %% This is the case when a new module is added, there will - %% be no current version of it at the time of this call. - undefined + case code:which(Mod) of + File when is_list(File) -> + case erl_prim_loader:read_file(File) of + {ok, Bin} -> + get_vsn(Bin); + error -> + undefined + end; + _ -> + %% This is the case when a new module is added, there will + %% be no current version of it at the time of this call. + undefined end. %%----------------------------------------------------------------- diff --git a/lib/ssl/src/ssl_dist_sup.erl b/lib/ssl/src/ssl_dist_sup.erl index ac7c6549df..a0d3c12383 100644 --- a/lib/ssl/src/ssl_dist_sup.erl +++ b/lib/ssl/src/ssl_dist_sup.erl @@ -88,8 +88,8 @@ ssl_connection_sup() -> }. consult(File) -> - case erl_prim_loader:get_file(File) of - {ok, Binary, _FullName} -> + case erl_prim_loader:read_file(File) of + {ok, Binary} -> Encoding = case epp:read_encoding_from_binary(Binary) of none -> latin1; diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 96b1f345cc..0204b8fa3b 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1559,9 +1559,9 @@ find_file(Mod) when is_atom(Mod) -> %% but code:which/1 finds all loaded modules %% - File can also be a file in an archive, %% beam_lib:chunks/2 cannot handle such paths but - %% erl_prim_loader:get_file/1 can - case erl_prim_loader:get_file(File) of - {ok, Beam, _} -> + %% erl_prim_loader:read_file/1 can + case erl_prim_loader:read_file(File) of + {ok, Beam} -> {beam, Beam, File}; error -> {error, nofile} diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl index 3b005e8aff..8b2b8670a4 100644 --- a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl +++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main.erl @@ -40,8 +40,8 @@ main(MainArgs) -> %% Access dict priv dir PrivDir = code:priv_dir(?DICT), PrivFile = filename:join([PrivDir, "archive_script_dict.txt"]), - case erl_prim_loader:get_file(PrivFile) of - {ok, Bin, _FullPath} -> + case erl_prim_loader:read_file(PrivFile) of + {ok, Bin} -> io:format("priv:~p\n", [{ok, Bin}]); error -> io:format("priv:~p\n", [{error, PrivFile}]) diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl index 1dc76b3dfa..26697d8c68 100644 --- a/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl +++ b/lib/stdlib/test/escript_SUITE_data/archive_script/archive_script_main2.erl @@ -42,8 +42,8 @@ main(MainArgs) -> %% Access dict priv dir PrivDir = code:priv_dir(?DICT), PrivFile = filename:join([PrivDir, "archive_script_dict.txt"]), - case erl_prim_loader:get_file(PrivFile) of - {ok, Bin, _FullPath} -> + case erl_prim_loader:read_file(PrivFile) of + {ok, Bin} -> io:format("priv:~p\n", [{ok, Bin}]); error -> io:format("priv:~p\n", [{error, PrivFile}]) diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl b/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl index 7cffacdf97..54e5011580 100644 --- a/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl +++ b/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl @@ -88,6 +88,15 @@ main([RelArchiveFile]) -> {ok,Bin,RelBeam} = erl_prim_loader:get_file(RelBeam), {ok,Bin,DotSlashBeam} = erl_prim_loader:get_file(DotSlashBeam), + error = erl_prim_loader:read_file(AbsArchiveFile), + error = erl_prim_loader:read_file(RelArchiveFile), + error = erl_prim_loader:read_file(DotSlashArchiveFile), + error = erl_prim_loader:read_file(AbsArchiveFile ++ "/"), + error = erl_prim_loader:read_file(AbsArchiveFile ++ "/."), + {ok,Bin} = erl_prim_loader:read_file(AbsBeam), + {ok,Bin} = erl_prim_loader:read_file(RelBeam), + {ok,Bin} = erl_prim_loader:read_file(DotSlashBeam), + {ok,#file_info{type=directory}=DFI} = erl_prim_loader:read_file_info(AbsArchiveFile), {ok,DFI} = erl_prim_loader:read_file_info(RelArchiveFile), @@ -101,6 +110,7 @@ main([RelArchiveFile]) -> F = AbsArchiveFile ++ ".extension", error = erl_prim_loader:list_dir(F), {ok,_,_} = erl_prim_loader:get_file(F), + {ok,_} = erl_prim_loader:read_file(F), {ok,#file_info{type=regular}} = erl_prim_loader:read_file_info(F), ok. -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor