aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/c.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/c.erl')
-rw-r--r--lib/stdlib/src/c.erl302
1 files changed, 255 insertions, 47 deletions
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index ad4915eabe..c04a201ce1 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. 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.
@@ -23,10 +23,10 @@
%% Avoid warning for local function error/2 clashing with autoimported BIF.
-compile({no_auto_import,[error/2]}).
--export([help/0,lc/1,c/1,c/2,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
+-export([help/0,lc/1,c/1,c/2,c/3,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
y/1, y/2,
lc_batch/0, lc_batch/1,
- i/3,pid/3,m/0,m/1,
+ i/3,pid/3,m/0,m/1,mm/0,lm/0,
bt/1, q/0,
erlangrc/0,erlangrc/1,bi/1, flush/0, regs/0, uptime/0,
nregs/0,pwd/0,ls/0,ls/1,cd/1,memory/1,memory/0, xm/1]).
@@ -35,7 +35,7 @@
-export([appcall/4]).
-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2,
- concat/1,max/1,min/1,foreach/2,foldl/3,flatmap/2]).
+ max/1,min/1,foreach/2,foldl/3,flatmap/2]).
-import(io, [format/1, format/2]).
%%-----------------------------------------------------------------------
@@ -44,7 +44,7 @@
help() ->
io:put_chars(<<"bt(Pid) -- stack backtrace for a process\n"
- "c(File) -- compile and load code in <File>\n"
+ "c(Mod) -- compile and load module or file <Mod>\n"
"cd(Dir) -- change working directory\n"
"flush() -- flush any messages sent to the shell\n"
"help() -- help info\n"
@@ -52,11 +52,13 @@ help() ->
"ni() -- information about the networked system\n"
"i(X,Y,Z) -- information about pid <X,Y,Z>\n"
"l(Module) -- load or reload module\n"
+ "lm() -- load all modified modules\n"
"lc([File]) -- compile a list of Erlang modules\n"
"ls() -- list files in the current directory\n"
"ls(Dir) -- list files in directory <Dir>\n"
"m() -- which modules are loaded\n"
"m(Mod) -- information about module <Mod>\n"
+ "mm() -- list all modified modules\n"
"memory() -- memory allocation information\n"
"memory(T) -- memory allocation information of type <T>\n"
"nc(File) -- compile and load code in <File> on all nodes\n"
@@ -70,32 +72,224 @@ help() ->
"xm(M) -- cross reference check a module\n"
"y(File) -- generate a Yecc parser\n">>).
-%% c(FileName)
-%% Compile a file/module.
-
--spec c(File) -> {'ok', Module} | 'error' when
- File :: file:name(),
- Module :: module().
+%% c(Module)
+%% Compile a module/file.
+
+-spec c(Module) -> {'ok', ModuleName} | 'error' when
+ Module :: file:name(),
+ ModuleName :: module().
+
+c(Module) -> c(Module, []).
+
+-spec c(Module, Options) -> {'ok', ModuleName} | 'error' when
+ Module :: file:name(),
+ Options :: [compile:option()] | compile:option(),
+ ModuleName :: module().
+
+c(Module, SingleOption) when not is_list(SingleOption) ->
+ c(Module, [SingleOption]);
+c(Module, Opts) when is_atom(Module) ->
+ %% either a module name or a source file name (possibly without
+ %% suffix); if such a source file exists, it is used to compile from
+ %% scratch with the given options, otherwise look for an object file
+ Suffix = case filename:extension(Module) of
+ "" -> src_suffix(Opts);
+ S -> S
+ end,
+ SrcFile = filename:rootname(Module, Suffix) ++ Suffix,
+ case filelib:is_file(SrcFile) of
+ true ->
+ compile_and_load(SrcFile, Opts);
+ false ->
+ c(Module, Opts, fun (_) -> true end)
+ end;
+c(Module, Opts) ->
+ %% we never interpret a string as a module name, only as a file
+ compile_and_load(Module, Opts).
-c(File) -> c(File, []).
+%% This tries to find an existing object file and use its compile_info and
+%% source path to recompile the module, overwriting the old object file.
+%% The Filter parameter is applied to the old compile options
--spec c(File, Options) -> {'ok', Module} | 'error' when
- File :: file:name(),
+-spec c(Module, Options, Filter) -> {'ok', ModuleName} | 'error' when
+ Module :: atom(),
Options :: [compile:option()],
- Module :: module().
+ Filter :: fun ((compile:option()) -> boolean()),
+ ModuleName :: module().
+
+c(Module, Options, Filter) when is_atom(Module) ->
+ case find_beam(Module) of
+ BeamFile when is_list(BeamFile) ->
+ c(Module, Options, Filter, BeamFile);
+ Error ->
+ {error, Error}
+ end.
+
+c(Module, Options, Filter, BeamFile) ->
+ case compile_info(Module, BeamFile) of
+ Info when is_list(Info) ->
+ case find_source(BeamFile, Info) of
+ SrcFile when is_list(SrcFile) ->
+ c(SrcFile, Options, Filter, BeamFile, Info);
+ Error ->
+ Error
+ end;
+ Error ->
+ Error
+ end.
-c(File, Opts0) when is_list(Opts0) ->
- Opts = [report_errors,report_warnings|Opts0],
+c(SrcFile, NewOpts, Filter, BeamFile, Info) ->
+ %% Filter old options; also remove options that will be replaced.
+ %% Write new beam over old beam unless other outdir is specified.
+ F = fun (Opt) -> not is_outdir_opt(Opt) andalso Filter(Opt) end,
+ Options = (NewOpts ++ [{outdir,filename:dirname(BeamFile)}]
+ ++ lists:filter(F, old_options(Info))),
+ format("Recompiling ~ts\n", [SrcFile]),
+ safe_recompile(SrcFile, Options, BeamFile).
+
+old_options(Info) ->
+ case lists:keyfind(options, 1, Info) of
+ {options, Opts} -> Opts;
+ false -> []
+ end.
+
+%% prefer the source path in the compile info if the file exists,
+%% otherwise do a standard source search relative to the beam file
+find_source(BeamFile, Info) ->
+ case lists:keyfind(source, 1, Info) of
+ {source, SrcFile} ->
+ case filelib:is_file(SrcFile) of
+ true -> SrcFile;
+ false -> find_source(BeamFile)
+ end;
+ _ ->
+ find_source(BeamFile)
+ end.
+
+find_source(BeamFile) ->
+ case filelib:find_source(BeamFile) of
+ {ok, SrcFile} -> SrcFile;
+ _ -> {error, no_source}
+ end.
+
+%% find the beam file for a module, preferring the path reported by code:which()
+%% if it still exists, or otherwise by searching the code path
+find_beam(Module) when is_atom(Module) ->
+ case code:which(Module) of
+ Beam when is_list(Beam), Beam =/= "" ->
+ case erlang:module_loaded(Module) of
+ false ->
+ Beam; % code:which/1 found this in the path
+ true ->
+ case filelib:is_file(Beam) of
+ true -> Beam;
+ false -> find_beam_1(Module) % file moved?
+ end
+ end;
+ Other when Other =:= ""; Other =:= cover_compiled ->
+ %% module is loaded but not compiled directly from source
+ find_beam_1(Module);
+ Error ->
+ Error
+ end.
+
+find_beam_1(Module) ->
+ File = atom_to_list(Module) ++ code:objfile_extension(),
+ case code:where_is_file(File) of
+ Beam when is_list(Beam) ->
+ Beam;
+ Error ->
+ Error
+ end.
+
+%% get the compile_info for a module
+%% -will report the info for the module in memory, if loaded
+%% -will try to find and examine the beam file if not in memory
+%% -will not cause a module to become loaded by accident
+compile_info(Module, Beam) when is_atom(Module) ->
+ case erlang:module_loaded(Module) of
+ true ->
+ %% getting the compile info for a loaded module should normally
+ %% work, but return an empty info list if it fails
+ try erlang:get_module_info(Module, compile)
+ catch _:_ -> []
+ end;
+ false ->
+ case beam_lib:chunks(Beam, [compile_info]) of
+ {ok, {_Module, [{compile_info, Info}]}} ->
+ Info;
+ Error ->
+ Error
+ end
+ end.
+
+%% compile module, backing up any existing target file and restoring the
+%% old version if compilation fails (this should only be used when we have
+%% an old beam file that we want to preserve)
+safe_recompile(File, Options, BeamFile) ->
+ %% Note that it's possible that because of options such as 'to_asm',
+ %% the compiler might not actually write a new beam file at all
+ Backup = BeamFile ++ ".bak",
+ case file:rename(BeamFile, Backup) of
+ Status when Status =:= ok; Status =:= {error,enoent} ->
+ case compile_and_load(File, Options) of
+ {ok, _} = Result ->
+ _ = if Status =:= ok -> file:delete(Backup);
+ true -> ok
+ end,
+ Result;
+ Error ->
+ _ = if Status =:= ok -> file:rename(Backup, BeamFile);
+ true -> ok
+ end,
+ Error
+ end;
+ Error ->
+ Error
+ end.
+
+%% Compile the file and load the resulting object code (if any).
+%% Automatically ensures that there is an outdir option, by default the
+%% directory of File, and that a 'from' option will be passed to match the
+%% actual source suffix if needed (unless already specified).
+compile_and_load(File, Opts0) when is_list(Opts0) ->
+ Opts = [report_errors, report_warnings
+ | ensure_from(filename:extension(File),
+ ensure_outdir(".", Opts0))],
case compile:file(File, Opts) of
{ok,Mod} -> %Listing file.
- machine_load(Mod, File, Opts);
+ purge_and_load(Mod, File, Opts);
{ok,Mod,_Ws} -> %Warnings maybe turned on.
- machine_load(Mod, File, Opts);
+ purge_and_load(Mod, File, Opts);
Other -> %Errors go here
Other
end;
-c(File, Opt) ->
- c(File, [Opt]).
+compile_and_load(File, Opt) ->
+ compile_and_load(File, [Opt]).
+
+ensure_from(Suffix, Opts0) ->
+ case lists:partition(fun is_from_opt/1, Opts0++from_opt(Suffix)) of
+ {[Opt|_], Opts} -> [Opt | Opts];
+ {[], Opts} -> Opts
+ end.
+
+ensure_outdir(Dir, Opts0) ->
+ {[Opt|_], Opts} = lists:partition(fun is_outdir_opt/1,
+ Opts0++[{outdir,Dir}]),
+ [Opt | Opts].
+
+is_outdir_opt({outdir, _}) -> true;
+is_outdir_opt(_) -> false.
+
+is_from_opt(from_core) -> true;
+is_from_opt(from_asm) -> true;
+is_from_opt(from_beam) -> true;
+is_from_opt(_) -> false.
+
+from_opt(".core") -> [from_core];
+from_opt(".S") -> [from_asm];
+from_opt(".beam") -> [from_beam];
+from_opt(_) -> [].
%%% Obtain the 'outdir' option from the argument. Return "." if no
%%% such option was given.
@@ -111,18 +305,29 @@ outdir([Opt|Rest]) ->
outdir(Rest)
end.
+%% mimic how suffix is selected in compile:file().
+src_suffix([from_core|_]) -> ".core";
+src_suffix([from_asm|_]) -> ".S";
+src_suffix([from_beam|_]) -> ".beam";
+src_suffix([_|Opts]) -> src_suffix(Opts);
+src_suffix([]) -> ".erl".
+
%%% We have compiled File with options Opts. Find out where the
-%%% output file went to, and load it.
-machine_load(Mod, File, Opts) ->
+%%% output file went and load it, purging any old version.
+purge_and_load(Mod, File, Opts) ->
Dir = outdir(Opts),
- File2 = filename:join(Dir, filename:basename(File, ".erl")),
+ Base = filename:basename(File, src_suffix(Opts)),
+ OutFile = filename:join(Dir, Base),
case compile:output_generated(Opts) of
true ->
- Base = atom_to_list(Mod),
- case filename:basename(File, ".erl") of
+ case atom_to_list(Mod) of
Base ->
code:purge(Mod),
- check_load(code:load_abs(File2,Mod), Mod);
+ %% Note that load_abs() adds the object file suffix
+ case code:load_abs(OutFile, Mod) of
+ {error, _R}=Error -> Error;
+ _ -> {ok, Mod}
+ end;
_OtherMod ->
format("** Module name '~p' does not match file name '~tp' **~n",
[Mod,File]),
@@ -133,13 +338,6 @@ machine_load(Mod, File, Opts) ->
ok
end.
-%%% This function previously warned if the loaded module was
-%%% 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, _) -> Error;
-check_load(_, Mod) -> {ok, Mod}.
-
%% Compile a list of modules
%% enables the nice unix shell cmd
%% erl -s c lc f1 f2 f3 @d c1=v1 @c2 @i IDir @o ODir -s erlang halt
@@ -202,7 +400,7 @@ split_def([], Res) -> {d, list_to_atom(reverse(Res))}.
make_term(Str) ->
case erl_scan:string(Str) of
{ok, Tokens, _} ->
- case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
+ case erl_parse:parse_term(Tokens ++ [{dot, erl_anno:new(1)}]) of
{ok, Term} -> Term;
{error, {_,_,Reason}} ->
io:format("~ts: ~ts~n", [Reason, Str]),
@@ -350,7 +548,7 @@ mfa_string(Fun) when is_function(Fun) ->
{arity,A} = erlang:fun_info(Fun, arity),
mfa_string({M,F,A});
mfa_string({M,F,A}) ->
- io_lib:format("~w:~w/~w", [M,F,A]);
+ io_lib:format("~w:~tw/~w", [M,F,A]);
mfa_string(X) ->
w(X).
@@ -374,7 +572,7 @@ display_info(Pid) ->
w(Reds), w(LM)),
iformat(case fetch(registered_name, Info) of
0 -> "";
- X -> w(X)
+ X -> io_lib:format("~tw", [X])
end,
mfa_string(Curr),
w(SS),
@@ -396,7 +594,7 @@ initial_call(Info) ->
end.
iformat(A1, A2, A3, A4, A5) ->
- format("~-21s ~-33s ~8s ~8s ~4s~n", [A1,A2,A3,A4,A5]).
+ format("~-21ts ~-33ts ~8s ~8s ~4s~n", [A1,A2,A3,A4,A5]).
all_procs() ->
case is_alive() of
@@ -459,6 +657,16 @@ m() ->
mformat(A1, A2) ->
format("~-20s ~ts\n", [A1,A2]).
+-spec mm() -> [module()].
+
+mm() ->
+ code:modified_modules().
+
+-spec lm() -> [code:load_ret()].
+
+lm() ->
+ [l(M) || M <- mm()].
+
%% erlangrc(Home)
%% Try to run a ".erlang" file, first in the current directory
%% else in home directory.
@@ -559,7 +767,7 @@ print_exports(X) when length(X) > 16 ->
split_print_exports(X);
print_exports([]) -> ok;
print_exports([{F, A} |Tail]) ->
- format(" ~w/~w~n",[F, A]),
+ format(" ~tw/~w~n",[F, A]),
print_exports(Tail).
split_print_exports(L) ->
@@ -571,11 +779,11 @@ split_print_exports(L) ->
split_print_exports([], [{F, A}|T]) ->
Str = " ",
- format("~-30s~w/~w~n", [Str, F, A]),
+ format("~-30ts~tw/~w~n", [Str, F, A]),
split_print_exports([], T);
split_print_exports([{F1, A1}|T1], [{F2, A2} | T2]) ->
- Str = flatten(io_lib:format("~w/~w", [F1, A1])),
- format("~-30s~w/~w~n", [Str, F2, A2]),
+ Str = flatten(io_lib:format("~tw/~w", [F1, A1])),
+ format("~-30ts~tw/~w~n", [Str, F2, A2]),
split_print_exports(T1, T2);
split_print_exports([], []) -> ok.
@@ -675,22 +883,22 @@ procline(Name, Info, Pid) ->
Call = initial_call(Info),
Reds = fetch(reductions, Info),
LM = length(fetch(messages, Info)),
- procformat(io_lib:format("~w",[Name]),
+ procformat(io_lib:format("~tw",[Name]),
io_lib:format("~w",[Pid]),
- io_lib:format("~s",[mfa_string(Call)]),
+ io_lib:format("~ts",[mfa_string(Call)]),
integer_to_list(Reds), integer_to_list(LM)).
procformat(Name, Pid, Call, Reds, LM) ->
- format("~-21s ~-12s ~-25s ~12s ~4s~n", [Name,Pid,Call,Reds,LM]).
+ format("~-21ts ~-12s ~-25ts ~12s ~4s~n", [Name,Pid,Call,Reds,LM]).
portline(Name, Info, Id) ->
Cmd = fetch(name, Info),
- portformat(io_lib:format("~w",[Name]),
+ portformat(io_lib:format("~tw",[Name]),
erlang:port_to_list(Id),
Cmd).
portformat(Name, Id, Cmd) ->
- format("~-21s ~-15s ~-40s~n", [Name,Id,Cmd]).
+ format("~-21ts ~-15s ~-40ts~n", [Name,Id,Cmd]).
%% pwd()
%% cd(Directory)