aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/beam_lib_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/beam_lib_SUITE.erl')
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl91
1 files changed, 55 insertions, 36 deletions
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 4521ecc0ef..73219f8fd8 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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.
@@ -81,14 +81,12 @@ normal(Conf) when is_list(Conf) ->
NoOfTables = length(ets:all()),
P0 = pps(),
- CompileFlags = [{outdir,PrivDir}, debug_info],
- {ok,_} = compile:file(Source, CompileFlags),
- {ok, Binary} = file:read_file(BeamFile),
-
- do_normal(BeamFile),
- do_normal(Binary),
+ do_normal(Source, PrivDir, BeamFile, []),
+ do_normal(Source, PrivDir, BeamFile, [no_utf8_atoms]),
{ok,_} = compile:file(Source, [{outdir,PrivDir}, no_debug_info]),
+ {ok, {simple, [{debug_info, {debug_info_v1, erl_abstract_code, {none, _}}}]}} =
+ beam_lib:chunks(BeamFile, [debug_info]),
{ok, {simple, [{abstract_code, no_abstract_code}]}} =
beam_lib:chunks(BeamFile, [abstract_code]),
@@ -101,7 +99,15 @@ normal(Conf) when is_list(Conf) ->
true = (P0 == pps()),
ok.
-do_normal(BeamFile) ->
+do_normal(Source, PrivDir, BeamFile, Opts) ->
+ CompileFlags = [{outdir,PrivDir}, debug_info | Opts],
+ {ok,_} = compile:file(Source, CompileFlags),
+ {ok, Binary} = file:read_file(BeamFile),
+
+ do_normal(BeamFile, Opts),
+ do_normal(Binary, Opts).
+
+do_normal(BeamFile, Opts) ->
Imports = {imports, [{erlang, get_module_info, 1},
{erlang, get_module_info, 2},
{lists, member, 2}]},
@@ -126,24 +132,37 @@ do_normal(BeamFile) ->
{ok, {simple, [{labeled_locals, _LLocals}]}} =
beam_lib:chunks(BeamFile, [labeled_locals]),
{ok, {simple, [_Vsn]}} = beam_lib:version(BeamFile),
- {ok, {simple, [{abstract_code, _}]}} =
+ {ok, {simple, [{abstract_code, {_, _}}]}} =
beam_lib:chunks(BeamFile, [abstract_code]),
+ {ok, {simple, [{debug_info, {debug_info_v1, erl_abstract_code, _}}]}} =
+ beam_lib:chunks(BeamFile, [debug_info]),
%% Test reading optional chunks.
- All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT"],
+ All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT", "AtU8"],
{ok,{simple,Chunks}} = beam_lib:chunks(BeamFile, All, [allow_missing_chunks]),
- verify_simple(Chunks).
+ case {verify_simple(Chunks),Opts} of
+ {{missing_chunk, AtomBin}, []} when is_binary(AtomBin) -> ok;
+ {{AtomBin, missing_chunk}, [no_utf8_atoms]} when is_binary(AtomBin) -> ok
+ end,
+
+ %% Make sure that reading the atom chunk works when the 'allow_missing_chunks'
+ %% option is used.
+ Some = ["Code",atoms,"ExpT","LitT"],
+ {ok,{simple,SomeChunks}} = beam_lib:chunks(BeamFile, Some, [allow_missing_chunks]),
+ [{"Code",<<_/binary>>},{atoms,[_|_]},{"ExpT",<<_/binary>>},{"LitT",missing_chunk}] =
+ SomeChunks.
-verify_simple([{"Atom", AtomBin},
+verify_simple([{"Atom", PlainAtomChunk},
{"Code", CodeBin},
{"StrT", StrBin},
{"ImpT", ImpBin},
{"ExpT", ExpBin},
{"FunT", missing_chunk},
- {"LitT", missing_chunk}])
- when is_binary(AtomBin), is_binary(CodeBin), is_binary(StrBin),
+ {"LitT", missing_chunk},
+ {"AtU8", AtU8Chunk}])
+ when is_binary(CodeBin), is_binary(StrBin),
is_binary(ImpBin), is_binary(ExpBin) ->
- ok.
+ {PlainAtomChunk, AtU8Chunk}.
%% Read invalid beam files.
error(Conf) when is_list(Conf) ->
@@ -182,11 +201,11 @@ error(Conf) when is_list(Conf) ->
LastChunk = last_chunk(Binary),
verify(chunk_too_big, beam_lib:chunks(Binary1, [LastChunk])),
Chunks = chunk_info(Binary),
- {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
- {Binary2, _} = split_binary(Binary, AbstractStart),
- verify(chunk_too_big, beam_lib:chunks(Binary2, ["Abst"])),
- {Binary3, _} = split_binary(Binary, AbstractStart-4),
- verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Abst"])),
+ {value, {_, DebugInfoStart, _}} = lists:keysearch("Dbgi", 1, Chunks),
+ {Binary2, _} = split_binary(Binary, DebugInfoStart),
+ verify(chunk_too_big, beam_lib:chunks(Binary2, ["Dbgi"])),
+ {Binary3, _} = split_binary(Binary, DebugInfoStart-4),
+ verify(invalid_beam_file, beam_lib:chunks(Binary3, ["Dbgi"])),
%% Instead of the 5:32 field below, there used to be control characters
%% (including zero bytes) directly in the string. Because inferior programs
@@ -211,9 +230,9 @@ last_chunk(Bin) ->
do_error(BeamFile, ACopy) ->
%% evil tests
Chunks = chunk_info(BeamFile),
- {value, {_, AtomStart, _}} = lists:keysearch("Atom", 1, Chunks),
+ {value, {_, AtomStart, _}} = lists:keysearch("AtU8", 1, Chunks),
{value, {_, ImportStart, _}} = lists:keysearch("ImpT", 1, Chunks),
- {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
+ {value, {_, DebugInfoStart, _}} = lists:keysearch("Dbgi", 1, Chunks),
{value, {_, AttributesStart, _}} =
lists:keysearch("Attr", 1, Chunks),
{value, {_, CompileInfoStart, _}} =
@@ -223,9 +242,9 @@ do_error(BeamFile, ACopy) ->
verify(invalid_chunk, beam_lib:chunks(BF2, [imports])),
BF3 = set_byte(ACopy, BeamFile, AtomStart-6, 17),
verify(missing_chunk, beam_lib:chunks(BF3, [imports])),
- BF4 = set_byte(ACopy, BeamFile, AbstractStart+10, 17),
- verify(invalid_chunk, beam_lib:chunks(BF4, [abstract_code])),
- BF5 = set_byte(ACopy, BeamFile, AttributesStart+10, 17),
+ BF4 = set_byte(ACopy, BeamFile, DebugInfoStart+10, 17),
+ verify(invalid_chunk, beam_lib:chunks(BF4, [debug_info])),
+ BF5 = set_byte(ACopy, BeamFile, AttributesStart+8, 17),
verify(invalid_chunk, beam_lib:chunks(BF5, [attributes])),
BF6 = set_byte(ACopy, BeamFile, 1, 17),
@@ -234,9 +253,9 @@ do_error(BeamFile, ACopy) ->
verify(not_a_beam_file, beam_lib:info(BF7)),
BF8 = set_byte(ACopy, BeamFile, 13, 17),
- verify(missing_chunk, beam_lib:chunks(BF8, ["Atom"])),
+ verify(missing_chunk, beam_lib:chunks(BF8, ["AtU8"])),
- BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+10, 17),
+ BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+8, 17),
verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])).
@@ -535,11 +554,11 @@ encrypted_abstr_1(Conf) ->
ok.
do_encrypted_abstr(Beam, Key) ->
- verify(key_missing_or_invalid, beam_lib:chunks(Beam, [abstract_code])),
+ verify(key_missing_or_invalid, beam_lib:chunks(Beam, [debug_info])),
- %% The raw chunk "Abst" can still be read even without a key.
- {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
- <<0:8,8:8,"des3_cbc",_/binary>> = Abst,
+ %% The raw chunk "Dbgi" can still be read even without a key.
+ {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]),
+ <<0:8,8:8,"des3_cbc",_/binary>> = Dbgi,
%% Try som invalid funs.
bad_fun(badfun, fun() -> ok end),
@@ -570,7 +589,7 @@ do_encrypted_abstr(Beam, Key) ->
{ok,_} = beam_lib:clear_crypto_key_fun(),
ok = beam_lib:crypto_key_fun(simple_crypto_fun(Key)),
verify_abstract(Beam),
- {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
+ {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]),
%% Installing a new key fun is not possible without clearing the old.
verify(exists, beam_lib:crypto_key_fun(ets_crypto_fun(Key))),
@@ -579,7 +598,7 @@ do_encrypted_abstr(Beam, Key) ->
{ok,_} = beam_lib:clear_crypto_key_fun(),
ok = beam_lib:crypto_key_fun(ets_crypto_fun(Key)),
verify_abstract(Beam),
- {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]),
+ {ok,{simple,[{"Dbgi",Dbgi}]}} = beam_lib:chunks(Beam, ["Dbgi"]),
{ok,cleared} = beam_lib:clear_crypto_key_fun(),
@@ -602,10 +621,10 @@ bad_fun(F) ->
bad_fun(S, F) ->
verify(S, beam_lib:crypto_key_fun(F)).
-
verify_abstract(Beam) ->
- {ok,{simple,[Chunk]}} = beam_lib:chunks(Beam, [abstract_code]),
- {abstract_code,{raw_abstract_v1,_}} = Chunk.
+ {ok,{simple,[Abst, Dbgi]}} = beam_lib:chunks(Beam, [abstract_code, debug_info]),
+ {abstract_code,{raw_abstract_v1,_}} = Abst,
+ {debug_info,{debug_info_v1,erl_abstract_code,_}} = Dbgi.
simple_crypto_fun(Key) ->
fun(init) -> ok;