Skip to content

Commit

Permalink
Store abstract code in the Dbgi chunk
Browse files Browse the repository at this point in the history
  • Loading branch information
José Valim committed Apr 6, 2017
1 parent b1b8a8d commit 3ffa8d6
Show file tree
Hide file tree
Showing 5 changed files with 169 additions and 97 deletions.
70 changes: 34 additions & 36 deletions lib/compiler/src/compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -310,7 +310,7 @@ format_error_reason(Reason) ->
ofile="" :: file:filename(),
module=[] :: module() | [],
core_code=[] :: cerl:c_module() | [],
abstract_code=[] :: binary() | [], %Abstract code for debugger.
abstract_code=[] :: abstract_code(), %Abstract code for debugger.
options=[] :: [option()], %Options for compilation
mod_options=[] :: [option()], %Options for module_info
encoding=none :: none | epp:source_encoding(),
Expand Down Expand Up @@ -1321,44 +1321,42 @@ core_inline_module(Code0, #compile{options=Opts}=St) ->
Code = cerl_inline:core_transform(Code0, Opts),
{ok,Code,St}.

save_abstract_code(Code, #compile{ifile=File}=St) ->
case abstract_code(Code, St) of
{ok,Abstr} ->
{ok,Code,St#compile{abstract_code=Abstr}};
{error,Es} ->
{error,St#compile{errors=St#compile.errors ++ [{File,Es}]}}
end.
save_abstract_code(Code, St) ->
{ok,Code,St#compile{abstract_code=erl_parse:anno_to_term(Code)}}.

abstract_code(Code0, #compile{options=Opts,ofile=OFile}) ->
Code = erl_parse:anno_to_term(Code0),
Abstr = erlang:term_to_binary({raw_abstract_v1,Code}, [compressed]),
case member(encrypt_debug_info, Opts) of
debug_info(#compile{module=Module,mod_options=Opts0,ofile=OFile,abstract_code=Abst}) ->
Opts1 = proplists:delete(debug_info, Opts0),
{Backend,Metadata,Opts2} =
case proplists:get_value(debug_info, Opts0, false) of
{OptBackend,OptMetadata} when is_atom(OptBackend) -> {OptBackend,OptMetadata,Opts1};
false -> {erl_abstract_code,none,Opts1};
true -> {erl_abstract_code,Abst,[debug_info | Opts1]}
end,
DebugInfo = erlang:term_to_binary({debug_info_v1,Backend,Metadata}, [compressed]),

case member(encrypt_debug_info, Opts2) of
true ->
case keyfind(debug_info_key, 1, Opts) of
{_,Key} ->
encrypt_abs_code(Abstr, Key);
case lists:keytake(debug_info_key, 1, Opts2) of
{value,{_, Key},Opts3} ->
encrypt_debug_info(DebugInfo, Key, [{debug_info_key,'********'} | Opts3]);
false ->
%% Note: #compile.module has not been set yet.
%% Here is an approximation that should work for
%% all valid cases.
Module = list_to_atom(filename:rootname(filename:basename(OFile))),
Mode = proplists:get_value(crypto_mode, Opts, des3_cbc),
Mode = proplists:get_value(crypto_mode, Opts2, des3_cbc),
case beam_lib:get_crypto_key({debug_info, Mode, Module, OFile}) of
error ->
{error, [{none,?MODULE,no_crypto_key}]};
Key ->
encrypt_abs_code(Abstr, {Mode, Key})
encrypt_debug_info(DebugInfo, {Mode, Key}, Opts2)
end
end;
false ->
{ok,Abstr}
{ok,DebugInfo,Opts2}
end.

encrypt_abs_code(Abstr, Key0) ->
encrypt_debug_info(DebugInfo, Key, Opts) ->
try
RealKey = generate_key(Key0),
RealKey = generate_key(Key),
case start_crypto() of
ok -> {ok,encrypt(RealKey, Abstr)};
ok -> {ok,encrypt(RealKey, DebugInfo),Opts};
{error,_}=E -> E
end
catch
Expand Down Expand Up @@ -1392,16 +1390,16 @@ encrypt({des3_cbc=Type,Key,IVec,BlockSize}, Bin0) ->
save_core_code(Code, St) ->
{ok,Code,St#compile{core_code=cerl:from_records(Code)}}.

beam_asm(Code0, #compile{ifile=File,abstract_code=Abst,extra_chunks=ExtraChunks,
options=CompilerOpts,mod_options=Opts0}=St) ->
Source = paranoid_absname(File),
Opts1 = lists:map(fun({debug_info_key,_}) -> {debug_info_key,'********'};
(Other) -> Other
end, Opts0),
Opts2 = [O || O <- Opts1, effects_code_generation(O)],
Chunks = [{<<"Abst">>, Abst} | ExtraChunks],
case beam_asm:module(Code0, Chunks, Source, Opts2, CompilerOpts) of
{ok,Code} -> {ok,Code,St#compile{abstract_code=[]}}
beam_asm(Code0, #compile{ifile=File,extra_chunks=ExtraChunks,options=CompilerOpts}=St) ->
case debug_info(St) of
{ok,DebugInfo,Opts0} ->
Source = paranoid_absname(File),
Opts1 = [O || O <- Opts0, effects_code_generation(O)],
Chunks = [{<<"Dbgi">>, DebugInfo} | ExtraChunks],
{ok,Code} = beam_asm:module(Code0, Chunks, Source, Opts1, CompilerOpts),
{ok,Code,St#compile{abstract_code=[]}};
{error,Es} ->
{error,St#compile{errors=St#compile.errors ++ [{File,Es}]}}
end.

paranoid_absname(""=File) ->
Expand Down Expand Up @@ -1485,7 +1483,7 @@ embed_native_code(Code, {Architecture,NativeCode}) ->
%% errors will be reported).

effects_code_generation(Option) ->
case Option of
case Option of
beam -> false;
report_warnings -> false;
report_errors -> false;
Expand Down
44 changes: 36 additions & 8 deletions lib/compiler/test/compile_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
app_test/1,appup_test/1,
debug_info/4, custom_debug_info/1,
file_1/1, forms_2/1, module_mismatch/1, big_file/1, outdir/1,
binary/1, makedep/1, cond_and_ifdef/1, listings/1, listings_big/1,
other_output/1, kernel_listing/1, encrypted_abstr/1,
Expand All @@ -51,7 +52,7 @@ all() ->
strict_record, utf8_atoms, extra_chunks,
cover, env, core, core_roundtrip, asm, optimized_guards,
sys_pre_attributes, dialyzer, warnings, pre_load_check,
env_compiler_options].
env_compiler_options, custom_debug_info].

groups() ->
[].
Expand Down Expand Up @@ -504,17 +505,23 @@ encrypted_abstr_1(Simple, Target) ->
{ok,simple} = compile:file(Simple,
[debug_info,{debug_info_key,Key},
{outdir,TargetDir}]),
verify_abstract(Target),
verify_abstract(Target, erl_abstract_code),

{ok,simple} = compile:file(Simple,
[{debug_info_key,Key},
{outdir,TargetDir}]),
verify_abstract(Target),
verify_abstract(Target, erl_abstract_code),

{ok,simple} = compile:file(Simple,
[debug_info,{debug_info_key,{des3_cbc,Key}},
{outdir,TargetDir}]),
verify_abstract(Target),
verify_abstract(Target, erl_abstract_code),

{ok,simple} = compile:file(Simple,
[{debug_info,{?MODULE,ok}},
{debug_info_key,Key},
{outdir,TargetDir}]),
verify_abstract(Target, ?MODULE),

{ok,{simple,[{compile_info,CInfo}]}} =
beam_lib:chunks(Target, [compile_info]),
Expand All @@ -539,7 +546,7 @@ encrypted_abstr_1(Simple, Target) ->
NewKey = "better use another key here",
write_crypt_file(["[{debug_info,des3_cbc,simple,\"",NewKey,"\"}].\n"]),
{ok,simple} = compile:file(Simple, [encrypt_debug_info,report]),
verify_abstract("simple.beam"),
verify_abstract("simple.beam", erl_abstract_code),
ok = file:delete(".erlang.crypt"),
beam_lib:clear_crypto_key_fun(),
{error,beam_lib,{key_missing_or_invalid,"simple.beam",abstract_code}} =
Expand Down Expand Up @@ -572,9 +579,10 @@ encrypted_abstr_no_crypto(Simple, Target) ->
{outdir,TargetDir},report]),
ok.

verify_abstract(Target) ->
{ok,{simple,[Chunk]}} = beam_lib:chunks(Target, [abstract_code]),
{abstract_code,{raw_abstract_v1,_}} = Chunk.
verify_abstract(Beam, Backend) ->
{ok,{simple,[Abst, Dbgi]}} = beam_lib:chunks(Beam, [abstract_code, debug_info]),
{abstract_code,{raw_abstract_v1,_}} = Abst,
{debug_info,{debug_info_v1,Backend,_}} = Dbgi.

has_crypto() ->
try
Expand All @@ -593,6 +601,26 @@ install_crypto_key(Key) ->
ok = beam_lib:crypto_key_fun(F).

%% Miscellanous tests, mainly to get better coverage.
debug_info(erlang, Module, ok, _Opts) ->
{ok, [Module]};
debug_info(erlang, Module, error, _Opts) ->
{error, unknown_format}.

custom_debug_info(Config) when is_list(Config) ->
{Simple,_} = get_files(Config, simple, "file_1"),

{ok,simple,OkBin} = compile:file(Simple, [binary, {debug_info,{?MODULE,ok}}]), %Coverage
{ok,{simple,[{abstract_code,{raw_abstract_v1,[simple]}}]}} =
beam_lib:chunks(OkBin, [abstract_code]),
{ok,{simple,[{debug_info,{debug_info_v1,?MODULE,ok}}]}} =
beam_lib:chunks(OkBin, [debug_info]),

{ok,simple,ErrorBin} = compile:file(Simple, [binary, {debug_info,{?MODULE,error}}]), %Coverage
{ok,{simple,[{abstract_code,no_abstract_code}]}} =
beam_lib:chunks(ErrorBin, [abstract_code]),
{ok,{simple,[{debug_info,{debug_info_v1,?MODULE,error}}]}} =
beam_lib:chunks(ErrorBin, [debug_info]).

cover(Config) when is_list(Config) ->
io:format("~p\n", [compile:options()]),
ok.
Expand Down
Loading

0 comments on commit 3ffa8d6

Please sign in to comment.