From 3d9b2a2b4ad7f24b7297fe2133ac65dafd297f87 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Wed, 4 May 2016 15:15:31 +0200 Subject: hipe_llvm: Syntax compatibility with 3.7-3.8 --- lib/hipe/llvm/hipe_llvm.erl | 49 +++++++++++++++++++++++++++++----------- lib/hipe/llvm/hipe_llvm_main.erl | 3 ++- lib/hipe/main/hipe.erl | 24 ++++++++++++++------ 3 files changed, 55 insertions(+), 21 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/hipe_llvm.erl b/lib/hipe/llvm/hipe_llvm.erl index 5e33731a2b..b2997f2d92 100644 --- a/lib/hipe/llvm/hipe_llvm.erl +++ b/lib/hipe/llvm/hipe_llvm.erl @@ -234,7 +234,7 @@ function_arg_type_list/1 ]). --export([pp_ins_list/2, pp_ins/2]). +-export([pp_ins_list/3, pp_ins/3]). %%----------------------------------------------------------------------------- @@ -765,13 +765,17 @@ function_arg_type_list(#llvm_fun{arg_type_list=Arg_type_list}) -> %% Pretty-printer Functions %%---------------------------------------------------------------------------- -%% @doc Pretty-print a list of LLVM instructions to a Device. -pp_ins_list(_Dev, []) -> ok; -pp_ins_list(Dev, [I|Is]) -> - pp_ins(Dev, I), - pp_ins_list(Dev, Is). +-type llvm_version() :: {Major :: integer(), Minor :: integer()}. -pp_ins(Dev, I) -> +%% @doc Pretty-print a list of LLVM instructions to a Device, using syntax +%% compatible with LLVM v. Major.Minor +-spec pp_ins_list(file:io_device(), llvm_version(), [llvm_instr()]) -> ok. +pp_ins_list(_Dev, _Ver, []) -> ok; +pp_ins_list(Dev, Ver={_,_}, [I|Is]) -> + pp_ins(Dev, Ver, I), + pp_ins_list(Dev, Ver, Is). + +pp_ins(Dev, Ver, I) -> case indent(I) of true -> write(Dev, " "); false -> ok @@ -861,6 +865,10 @@ pp_ins(Dev, I) -> true -> write(Dev, "volatile "); false -> ok end, + case Ver >= {3,7} of false -> ok; true -> + pp_type(Dev, pointer_type(load_p_type(I))), + write(Dev, ", ") + end, pp_type(Dev, load_p_type(I)), write(Dev, [" ", load_pointer(I), " "]), case load_alignment(I) of @@ -897,6 +905,10 @@ pp_ins(Dev, I) -> true -> write(Dev, "inbounds "); false -> ok end, + case Ver >= {3,7} of false -> ok; true -> + pp_type(Dev, pointer_type(getelementptr_p_type(I))), + write(Dev, ", ") + end, pp_type(Dev, getelementptr_p_type(I)), write(Dev, [" ", getelementptr_value(I)]), pp_typed_idxs(Dev, getelementptr_typed_idxs(I)), @@ -958,12 +970,16 @@ pp_ins(Dev, I) -> pp_args(Dev, fun_def_arglist(I)), write(Dev, ") "), pp_options(Dev, fun_def_fn_attrs(I)), + case Ver >= {3,7} of false -> ok; true -> + write(Dev, "personality i32 (i32, i64, i8*,i8*)* " + "@__gcc_personality_v0 ") + end, case fun_def_align(I) of [] -> ok; N -> write(Dev, ["align ", N]) end, write(Dev, "{\n"), - pp_ins_list(Dev, fun_def_body(I)), + pp_ins_list(Dev, Ver, fun_def_body(I)), write(Dev, "}\n"); #llvm_fun_decl{} -> write(Dev, "declare "), @@ -992,8 +1008,12 @@ pp_ins(Dev, I) -> pp_type(Dev, const_decl_type(I)), write(Dev, [" ", const_decl_value(I), "\n"]); #llvm_landingpad{} -> - write(Dev, "landingpad { i8*, i32 } personality i32 (i32, i64, i8*,i8*)* - @__gcc_personality_v0 cleanup\n"); + write(Dev, "landingpad { i8*, i32 } "), + case Ver < {3,7} of false -> ok; true -> + write(Dev, "personality i32 (i32, i64, i8*,i8*)* " + "@__gcc_personality_v0 ") + end, + write(Dev, "cleanup\n"); #llvm_asm{} -> write(Dev, [asm_instruction(I), "\n"]); #llvm_adj_stack{} -> @@ -1002,9 +1022,12 @@ pp_ins(Dev, I) -> pp_type(Dev, adj_stack_type(I)), write(Dev, [" ", adj_stack_offset(I),")\n"]); #llvm_branch_meta{} -> - write(Dev, ["!", branch_meta_id(I), " = metadata !{metadata !\"branch_weights\", - i32 ", branch_meta_true_weight(I), ", i32 ", - branch_meta_false_weight(I), "}\n"]); + write(Dev, ["!", branch_meta_id(I), " = "]), + if Ver < {3,6} -> write(Dev, "metadata !{metadata "); + Ver >= {3,6} -> write(Dev, "!{ ") + end, + write(Dev, ["!\"branch_weights\", i32 ", branch_meta_true_weight(I), + ", i32 ", branch_meta_false_weight(I), "}\n"]); Other -> exit({?MODULE, pp_ins, {"Unknown LLVM instruction", Other}}) end. diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index 3c24425828..ac1f49c73b 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -78,7 +78,8 @@ compile_with_llvm(FunName, Arity, LLVMCode, Options, UseBuffer) -> false -> [] end, {ok, File_llvm} = file:open(Dir ++ Filename ++ ".ll", OpenOpts), - hipe_llvm:pp_ins_list(File_llvm, LLVMCode), + Ver = hipe:get_llvm_version(), %% Should probably cache this + hipe_llvm:pp_ins_list(File_llvm, Ver, LLVMCode), %% delayed_write can cause file:close not to do a close, hence the two calls ok = file:close(File_llvm), __ = file:close(File_llvm), diff --git a/lib/hipe/main/hipe.erl b/lib/hipe/main/hipe.erl index 0e32da1d36..01b7f34b3c 100644 --- a/lib/hipe/main/hipe.erl +++ b/lib/hipe/main/hipe.erl @@ -200,8 +200,9 @@ compile/4, compile_core/4, file/1, - file/2, - llvm_support_available/0, + file/2, + get_llvm_version/0, + llvm_support_available/0, load/1, help/0, help_hiper/0, @@ -1538,18 +1539,27 @@ check_options(Opts) -> -spec llvm_support_available() -> boolean(). llvm_support_available() -> - get_llvm_version() >= 3.4. + get_llvm_version() >= {3,4}. +-type llvm_version() :: {Major :: integer(), Minor :: integer()}. + +-spec get_llvm_version() -> llvm_version() | {0, 0}. get_llvm_version() -> OptStr = os:cmd("opt -version"), SubStr = "LLVM version ", N = length(SubStr), case string:str(OptStr, SubStr) of 0 -> % No opt available - 0.0; + {0, 0}; S -> - case string:to_float(string:sub_string(OptStr, S + N)) of - {error, _} -> 0.0; %XXX: Assumes no revision numbers in versioning - {Float, _} -> Float + case string:tokens(string:sub_string(OptStr, S + N), ".") of + [MajorS, MinorS | _] -> + case {string:to_integer(MajorS), string:to_integer(MinorS)} of + {{Major, ""}, {Minor, _}} + when is_integer(Major), is_integer(Minor) -> + {Major, Minor}; + _ -> {0, 0} + end; + _ -> {0, 0} %XXX: Assumes no revision numbers in versioning end end. -- cgit v1.2.3 From 56ec17296fb350f1eed5486b8d9b575be5afb7a8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Mon, 9 May 2016 12:53:05 +0200 Subject: hipe: Remove runtime elf_format class switching The elf_format module was written in such a way that some of the customisation to ELF-32 vs ELF-64 was made at compile-time and some of it at run-time. As such it was not actually possible to read 32-bit files with a module compiled for 64-bit support, or vice versa. As the run-time selection uses some process dictionary ugliness, it was removed, shifting all the customisation to be compile-time. --- lib/hipe/llvm/elf_format.erl | 170 +++++++++++++++++---------------------- lib/hipe/llvm/hipe_llvm_main.erl | 26 +++--- 2 files changed, 82 insertions(+), 114 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index 260da9b5e6..9fc9da9203 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -24,10 +24,7 @@ %% Executable code extract_text/1, %% GCC Exception Table - get_exn_handlers/1, - %% Misc. - set_architecture_flag/1, - is64bit/0 + get_exn_handlers/1 ]). -include("elf_format.hrl"). @@ -110,16 +107,19 @@ -type elf_sym() :: #elf_sym{}. %% Relocations +-ifdef(BIT32). -record(elf_rel, {r_offset :: offset(), % Address of reference r_info :: info() % Symbol index and type of relocation }). --type elf_rel() :: #elf_rel{}. +-type reloc() :: #elf_rel{}. +-else. -record(elf_rela, {r_offset :: offset(), % Address of reference r_info :: info(), % Symbol index and type of relocation r_addend :: offset() % Constant part of expression }). --type elf_rela() :: #elf_rela{}. +-type reloc() :: #elf_rela{}. +-endif. %% %% Program header table %% -record(elf_phdr, {type, % Type of segment @@ -215,28 +215,36 @@ sym_name(#elf_sym{name = Name}) -> Name. %%%------------------------- %%% Relocations %%%------------------------- --spec mk_rel(offset(), info()) -> elf_rel(). -mk_rel(Offset, Info) -> - #elf_rel{r_offset = Offset, r_info = Info}. + %% The following two functions capitalize on the fact that the two kinds of %% relocation records (for 32- and 64-bit architectures have similar structure. +-spec r_offset(reloc()) -> offset(). +-spec r_info(reloc()) -> info(). --spec r_offset(elf_rel() | elf_rela()) -> offset(). -r_offset(#elf_rel{r_offset = Offset}) -> Offset; -r_offset(#elf_rela{r_offset = Offset}) -> Offset. +-ifdef(BIT32). --spec r_info(elf_rel() | elf_rela()) -> info(). -r_info(#elf_rel{r_info = Info}) -> Info; -r_info(#elf_rela{r_info = Info}) -> Info. +-spec mk_rel(offset(), info()) -> reloc(). +mk_rel(Offset, Info) -> + #elf_rel{r_offset = Offset, r_info = Info}. --spec mk_rela(offset(), info(), offset()) -> elf_rela(). +r_offset(#elf_rel{r_offset = Offset}) -> Offset. +r_info(#elf_rel{r_info = Info}) -> Info. + +-else.%%BIT32 + +-spec mk_rela(offset(), info(), offset()) -> reloc(). mk_rela(Offset, Info, Addend) -> #elf_rela{r_offset = Offset, r_info = Info, r_addend = Addend}. --spec rela_addend(elf_rela()) -> offset(). +r_offset(#elf_rela{r_offset = Offset}) -> Offset. +r_info(#elf_rela{r_info = Info}) -> Info. + +-spec rela_addend(reloc()) -> offset(). rela_addend(#elf_rela{r_addend = Addend}) -> Addend. +-endif.%%BIT32 + %% %%%------------------------- %% %%% GCC exception table %% %%%------------------------- @@ -388,29 +396,29 @@ get_symtab_entries(<<>>, Acc) -> lists:reverse(Acc); get_symtab_entries(Symtab_bin, Acc) -> <> = Symtab_bin, - case is64bit() of - true -> - <<%% Structural pattern matching on fields. - Name:?bits(?ST_NAME_SIZE)/integer-little, - Info:?bits(?ST_INFO_SIZE)/integer-little, - Other:?bits(?ST_OTHER_SIZE)/integer-little, - Shndx:?bits(?ST_SHNDX_SIZE)/integer-little, - Value:?bits(?ST_VALUE_SIZE)/integer-little, - Size:?bits(?ST_SIZE_SIZE)/integer-little - >> = SymE_bin; - false -> - << %% Same fields in different order: - Name:?bits(?ST_NAME_SIZE)/integer-little, - Value:?bits(?ST_VALUE_SIZE)/integer-little, - Size:?bits(?ST_SIZE_SIZE)/integer-little, - Info:?bits(?ST_INFO_SIZE)/integer-little, - Other:?bits(?ST_OTHER_SIZE)/integer-little, - Shndx:?bits(?ST_SHNDX_SIZE)/integer-little - >> = SymE_bin - end, - SymE = mk_sym(Name, Info, Other, Shndx, Value, Size), + SymE = parse_sym(SymE_bin), get_symtab_entries(MoreSymE, [SymE | Acc]). +-ifdef(BIT32). +parse_sym(<<%% Structural pattern matching on fields. + Name:?bits(?ST_NAME_SIZE)/integer-little, + Value:?bits(?ST_VALUE_SIZE)/integer-little, + Size:?bits(?ST_SIZE_SIZE)/integer-little, + Info:?bits(?ST_INFO_SIZE)/integer-little, + Other:?bits(?ST_OTHER_SIZE)/integer-little, + Shndx:?bits(?ST_SHNDX_SIZE)/integer-little>>) -> + mk_sym(Name, Info, Other, Shndx, Value, Size). +-else. +parse_sym(<<%% Same fields in different order: + Name:?bits(?ST_NAME_SIZE)/integer-little, + Info:?bits(?ST_INFO_SIZE)/integer-little, + Other:?bits(?ST_OTHER_SIZE)/integer-little, + Shndx:?bits(?ST_SHNDX_SIZE)/integer-little, + Value:?bits(?ST_VALUE_SIZE)/integer-little, + Size:?bits(?ST_SIZE_SIZE)/integer-little>>) -> + mk_sym(Name, Info, Other, Shndx, Value, Size). +-endif. + %% @doc Extracts a specific entry from the Symbol Table (as binary). %% This function takes as arguments the Symbol Table (`SymTab') %% and the entry's serial number and returns that entry (`sym'). @@ -447,20 +455,16 @@ get_strtab_entry(Strtab, Offset) -> %% with all .rela.rodata labels (i.e. constants and literals in code) %% or an empty list if no ".rela.rodata" section exists in code. -spec get_rodata_relocs(elf()) -> [offset()]. +-spec get_rela_addends([reloc()]) -> [offset()]. +-ifdef(BIT32). get_rodata_relocs(Elf) -> - case is64bit() of - true -> - %% Only care about the addends (== offsets): - get_rela_addends(extract_rela(Elf, ?RODATA)); - false -> - %% Find offsets hardcoded in ".rodata" entry - %%XXX: Treat all 0s as padding and skip them! - [SkipPadding || SkipPadding <- extract_rodata(Elf), SkipPadding =/= 0] - end. + [SkipPadding || SkipPadding <- extract_rodata(Elf), SkipPadding =/= 0]. +get_rela_addends(_RelaEntries) -> error(notsup). +-else. +get_rodata_relocs(Elf) -> get_rela_addends(extract_rela(Elf, ?RODATA)). +get_rela_addends(RelaEntries) -> [rela_addend(E) || E <- RelaEntries]. +-endif. --spec get_rela_addends([elf_rela()]) -> [offset()]. -get_rela_addends(RelaEntries) -> - [rela_addend(E) || E <- RelaEntries]. %% @doc Extract a list of the form `[{SymbolName, Offset}]' with all relocatable %% symbols and their offsets in the code from the ".text" section. @@ -488,37 +492,23 @@ get_text_relocs(Elf) -> %% @doc Extract the Relocations segment for section `Name' (that is passed %% as second argument) from an ELF formated Object file binary. --spec extract_rela(elf(), name()) -> [elf_rel() | elf_rela()]. +-spec extract_rela(elf(), name()) -> [reloc()]. + +-ifdef(BIT32). extract_rela(Elf, Name) -> - SegName = - case is64bit() of - true -> ?RELA(Name); % ELF-64 uses ".rela" - false -> ?REL(Name) % ...while ELF-32 uses ".rel" - end, - Rela_bin = extract_segment_by_name(Elf, SegName), - get_rela_entries(Rela_bin, []). - -get_rela_entries(<<>>, Acc) -> - lists:reverse(Acc); -get_rela_entries(Bin, Acc) -> - E = case is64bit() of - true -> - <<%% Structural pattern matching on fields of a Rela Entry. - Offset:?bits(?R_OFFSET_SIZE)/integer-little, - Info:?bits(?R_INFO_SIZE)/integer-little, - Addend:?bits(?R_ADDEND_SIZE)/integer-little, - Rest/binary - >> = Bin, - mk_rela(Offset, Info, Addend); - false -> - <<%% Structural pattern matching on fields of a Rel Entry. - Offset:?bits(?R_OFFSET_SIZE)/integer-little, - Info:?bits(?R_INFO_SIZE)/integer-little, - Rest/binary - >> = Bin, - mk_rel(Offset, Info) - end, - get_rela_entries(Rest, [E | Acc]). + %% Structural pattern matching on fields of a Rel Entry. + [mk_rel(Offset, Info) + || <> <= extract_segment_by_name(Elf, ?REL(Name))]. +-else. +extract_rela(Elf, Name) -> + [mk_rela(Offset, Info, Addend) + || <> <= extract_segment_by_name(Elf, ?RELA(Name))]. +-endif. %% %% @doc Extract the `EntryNum' (serial number) Relocation Entry. %% get_rela_entry(Rela, EntryNum) -> @@ -617,6 +607,7 @@ get_gccexntab_callsites(CSTab, Acc) -> %%------------------------------------------------------------------------------ %% Functions to manipulate Read-only Data (.rodata) %%------------------------------------------------------------------------------ +-ifdef(BIT32). extract_rodata(Elf) -> Rodata_bin = extract_segment_by_name(Elf, ?RODATA), get_rodata_entries(Rodata_bin, []). @@ -626,6 +617,7 @@ get_rodata_entries(<<>>, Acc) -> get_rodata_entries(Rodata_bin, Acc) -> <> = Rodata_bin, get_rodata_entries(More, [Num | Acc]). +-endif. %%------------------------------------------------------------------------------ %% Helper functions @@ -770,21 +762,3 @@ leb128_decode(LebNum, NoOfBits, Acc) -> <> = <>, {Num, MoreLebNums} end. - -%% @doc Extract ELF Class from ELF header and export symbol to process -%% dictionary. --spec set_architecture_flag(elf()) -> 'ok'. -set_architecture_flag(Elf) -> - %% Extract information about ELF Class from ELF Header - <<16#7f, $E, $L, $F, EI_Class, _MoreHeader/binary>> - = get_binary_segment(Elf, 0, ?ELF_EHDR_SIZE), - put(elf_class, EI_Class), - ok. - -%% @doc Read from object file header if the file class is ELF32 or ELF64. --spec is64bit() -> boolean(). -is64bit() -> - case get(elf_class) of - ?ELFCLASS64 -> true; - ?ELFCLASS32 -> false - end. diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index ac1f49c73b..9e025929b5 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -24,8 +24,6 @@ rtl_to_native(MFA, RTL, Roots, Options) -> %% Extract information from object file %% ObjBin = open_object_file(ObjectFile), - %% Read and set the ELF class - elf_format:set_architecture_flag(ObjBin), %% Get labels info (for switches and jump tables) Labels = elf_format:get_rodata_relocs(ObjBin), {Switches, Closures} = get_tables(ObjBin), @@ -278,14 +276,8 @@ get_sdescs(Elf) -> _LiveRootCount:(?bits(?SP_LIVEROOTCNT_SIZE))/integer-little, % Skip Roots/binary>> = NoteGC_bin, LiveRoots = get_liveroots(Roots, []), - %% Extract information about the safe point addresses: - SPOffs = - case elf_format:is64bit() of - true -> %% Find offsets in ".rela.note.gc": - elf_format:get_rela_addends(RelaNoteGC); - false -> %% Find offsets in SPAddrs (in ".note.gc"): - get_spoffs(SPAddrs, []) - end, + %% Extract the safe point offsets: + SPOffs = get_reloc_addends(SPAddrs, RelaNoteGC), %% Extract Exception Handler labels: ExnHandlers = elf_format:get_exn_handlers(Elf), %% Combine ExnHandlers and Safe point addresses (return addresses): @@ -301,12 +293,14 @@ get_liveroots(<>, Acc) -> get_liveroots(MoreRoots, [Root | Acc]). -%% @doc Extracts a bunch of integers (safepoint offsets) from a binary. Returns -%% a tuple as need for stack descriptors. -get_spoffs(<<>>, Acc) -> - lists:reverse(Acc); -get_spoffs(<>, Acc) -> - get_spoffs(More, [SPOff | Acc]). +-ifdef(BIT32). +%% ELF32 x86 uses implicit addends. +get_reloc_addends(Table, _Relocs) -> + [Add || <> <= Table]. +-else. +%% ELF64 x64 uses explicit addends. +get_reloc_addends(_Table, Relocs) -> elf_format:get_rela_addends(Relocs). +-endif. combine_ras_and_exns(_, [], Acc) -> lists:reverse(Acc); -- cgit v1.2.3 From 34ac363e14498fce8f0d04c9296eb3d53d531069 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Wed, 4 May 2016 19:04:16 +0200 Subject: hipe: Cleanup elf_format module --- lib/hipe/llvm/elf_format.erl | 266 +++++++++++---------------------------- lib/hipe/llvm/hipe_llvm_main.erl | 11 +- 2 files changed, 80 insertions(+), 197 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index 9fc9da9203..13a00bfd38 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -24,7 +24,9 @@ %% Executable code extract_text/1, %% GCC Exception Table - get_exn_handlers/1 + get_exn_handlers/1, + %% Main interface + read/1 ]). -include("elf_format.hrl"). @@ -33,7 +35,9 @@ %% Types %%------------------------------------------------------------------------------ --type elf() :: binary(). +-export_type([elf/0]). + +-opaque elf() :: binary(). -type lp() :: non_neg_integer(). % landing pad -type num() :: non_neg_integer(). @@ -47,8 +51,6 @@ -type valueoff() :: offset(). -type name() :: string(). --type name_size() :: {name(), size()}. --type name_sizes() :: [name_size()]. %%------------------------------------------------------------------------------ %% Abstract Data Types and Accessors for ELF Structures. @@ -83,7 +85,7 @@ %% -type elf_ehdr_ident() :: #elf_ehdr_ident{}. %% Section header entries --record(elf_shdr, {name, % Section name +-record(elf_shdr, {name :: string(), % Section name type, % Section type flags, % Section attributes addr, % Virtual address in memory @@ -94,7 +96,7 @@ addralign, % Address align boundary entsize % Size of entries, if section has table }). -%% -type elf_shdr() :: #elf_shdr{}. +-type elf_shdr() :: #elf_shdr{}. %% Symbol table entries -record(elf_sym, {name :: nameoff(), % Symbol name @@ -270,6 +272,14 @@ mk_gccexntab_callsite(Start, Size, LP, Action) -> %% -spec gccexntab_callsite_lp(elf_gccexntab_callsite()) -> lp(). %% gccexntab_callsite_lp(#elf_gccexntab_callsite{lp = LP}) -> LP. +%%------------------------------------------------------------------------------ +%% Main interface function +%%------------------------------------------------------------------------------ + +%% @doc Parses an ELF file. +-spec read(binary()) -> elf(). +read(ElfBin) -> ElfBin. + %%------------------------------------------------------------------------------ %% Functions to manipulate the ELF File Header %%------------------------------------------------------------------------------ @@ -308,19 +318,31 @@ extract_header(Elf) -> %% Functions to manipulate Section Header Entries %%------------------------------------------------------------------------------ +-type shdrtab() :: [elf_shdr()]. + %% @doc Extracts the Section Header Table from an ELF formated Object File. +-spec extract_shdrtab(elf()) -> shdrtab(). extract_shdrtab(Elf) -> %% Extract File Header to get info about Section Header Offset (in bytes), %% Entry Size (in bytes) and Number of entries - #elf_ehdr{shoff = ShOff, shentsize = ShEntsize, shnum = ShNum} = - extract_header(Elf), + #elf_ehdr{shoff = ShOff, shentsize = ShEntsize, shnum = ShNum + ,shstrndx = ShStrNdx} = extract_header(Elf), %% Get actual Section header table (binary) ShdrBin = get_binary_segment(Elf, ShOff, ShNum * ShEntsize), - get_shdrtab_entries(ShdrBin, []). - -get_shdrtab_entries(<<>>, Acc) -> - lists:reverse(Acc); -get_shdrtab_entries(ShdrBin, Acc) -> + %% We need to lookup the offset and size of the section header string table + %% before we can fully parse the section table. We compute its offset and + %% extract the fields we need here. + ShStrEntryOffset = ShStrNdx * ?ELF_SHDRENTRY_SIZE, + <<_:ShStrEntryOffset/binary, _:?SH_NAME_SIZE/binary, + _:?SH_TYPE_SIZE/binary, _:?SH_FLAGS_SIZE/binary, _:?SH_ADDR_SIZE/binary, + ShStrOffset:?bits(?SH_OFFSET_SIZE)/little, + ShStrSize:?bits(?SH_SIZE_SIZE)/little, + _/binary>> = ShdrBin, + ShStrTab = parse_strtab(get_binary_segment(Elf, ShStrOffset, ShStrSize)), + get_shdrtab_entries(ShdrBin, ShStrTab). + +get_shdrtab_entries(<<>>, _ShStrTab) -> []; +get_shdrtab_entries(ShdrTab, ShStrTab) -> <<%% Structural pattern matching on fields. Name:?bits(?SH_NAME_SIZE)/integer-little, Type:?bits(?SH_TYPE_SIZE)/integer-little, @@ -332,56 +354,21 @@ get_shdrtab_entries(ShdrBin, Acc) -> Info:?bits(?SH_INFO_SIZE)/integer-little, Addralign:?bits(?SH_ADDRALIGN_SIZE)/integer-little, Entsize:?bits(?SH_ENTSIZE_SIZE)/integer-little, - MoreShdrE/binary - >> = ShdrBin, - ShdrE = mk_shdr(Name, Type, Flags, Addr, Offset, + Rest/binary + >> = ShdrTab, + Entry = mk_shdr(get_strtab_entry(Name, ShStrTab), Type, Flags, Addr, Offset, Size, Link, Info, Addralign, Entsize), - get_shdrtab_entries(MoreShdrE, [ShdrE | Acc]). - -%% @doc Extracts a specific Entry of a Section Header Table. This function -%% takes as argument the Section Header Table (`SHdrTab') and the entry's -%% serial number (`EntryNum') and returns the entry (`shdr'). -get_shdrtab_entry(SHdrTab, EntryNum) -> - lists:nth(EntryNum + 1, SHdrTab). - -%%------------------------------------------------------------------------------ -%% Functions to manipulate Section Header String Table -%%------------------------------------------------------------------------------ - -%% @doc Extracts the Section Header String Table. This section is not a known -%% ELF Object File section. It is just a "hidden" table storing the -%% names of all sections that exist in current object file. --spec extract_shstrtab(elf()) -> [name()]. -extract_shstrtab(Elf) -> - %% Extract Section Name String Table Index - #elf_ehdr{shstrndx = ShStrNdx} = extract_header(Elf), - ShHdrTab = extract_shdrtab(Elf), - %% Extract Section header entry and get actual Section-header String Table - #elf_shdr{offset = ShStrOffset, size = ShStrSize} = - get_shdrtab_entry(ShHdrTab, ShStrNdx), - case get_binary_segment(Elf, ShStrOffset, ShStrSize) of - <<>> -> %% Segment empty - []; - ShStrTab -> %% Convert to string table - [Name || {Name, _Size} <- get_names(ShStrTab)] - end. + [Entry | get_shdrtab_entries(Rest, ShStrTab)]. %%------------------------------------------------------------------------------ -spec get_tab_entries(elf()) -> [{name(), valueoff(), size()}]. get_tab_entries(Elf) -> SymTab = extract_symtab(Elf), - Ts = [{Name, Value, Size div ?ELF_XWORD_SIZE} - || #elf_sym{name = Name, value = Value, size = Size} <- SymTab, - Name =/= 0], - {NameIndices, ValueOffs, Sizes} = lists:unzip3(Ts), - %% Find the names of the symbols. - %% Get string table entries ([{Name, Offset in strtab section}]). Keep only - %% relevant entries: StrTab = extract_strtab(Elf), - Relevant = [get_strtab_entry(StrTab, Off) || Off <- NameIndices], - %% Zip back to {Name, ValueOff, Size} - lists:zip3(Relevant, ValueOffs, Sizes). + [{get_strtab_entry(Name, StrTab), Value, Size div ?ELF_XWORD_SIZE} + || #elf_sym{name = Name, value = Value, size = Size} <- SymTab, + Name =/= 0]. %%------------------------------------------------------------------------------ %% Functions to manipulate Symbol Table @@ -389,15 +376,8 @@ get_tab_entries(Elf) -> %% @doc Function that extracts Symbol Table from an ELF Object file. extract_symtab(Elf) -> - Symtab_bin = extract_segment_by_name(Elf, ?SYMTAB), - get_symtab_entries(Symtab_bin, []). - -get_symtab_entries(<<>>, Acc) -> - lists:reverse(Acc); -get_symtab_entries(Symtab_bin, Acc) -> - <> = Symtab_bin, - SymE = parse_sym(SymE_bin), - get_symtab_entries(MoreSymE, [SymE | Acc]). + Symtab = extract_segment_by_name(Elf, ?SYMTAB), + [parse_sym(Sym) || <> <= Symtab]. -ifdef(BIT32). parse_sym(<<%% Structural pattern matching on fields. @@ -429,23 +409,22 @@ get_symtab_entry(SymTab, EntryNum) -> %% Functions to manipulate String Table %%------------------------------------------------------------------------------ +%% ADT: get_strtab_entry/1 must be used to consume this type. +-type strtab() :: binary(). + %% @doc Extracts String Table from an ELF formated Object File. --spec extract_strtab(elf()) -> [{string(), offset()}]. +-spec extract_strtab(elf()) -> strtab(). extract_strtab(Elf) -> - Strtab_bin = extract_segment_by_name(Elf, ?STRTAB), - NamesSizes = get_names(Strtab_bin), - make_offsets(NamesSizes). - -%% @doc Returns the name of the symbol at the given offset. The string table -%% contains entries of the form {Name, Offset}. If no such offset exists -%% returns the empty string (`""'). -%% XXX: There might be a bug here because of the "compact" saving the ELF -%% format uses: e.g. only stores ".rela.text" for ".rela.text" and ".text". -get_strtab_entry(Strtab, Offset) -> - case lists:keyfind(Offset, 2, Strtab) of - {Name, Offset} -> Name; - false -> "" - end. + parse_strtab(extract_segment_by_name(Elf, ?STRTAB)). + +-spec parse_strtab(binary()) -> strtab(). +parse_strtab(StrTabSectionBin) -> StrTabSectionBin. + +%% @doc Returns the name of the symbol at the given offset. +-spec get_strtab_entry(non_neg_integer(), strtab()) -> string(). +get_strtab_entry(Offset, StrTab) -> + <<_:Offset/binary, StrBin/binary>> = StrTab, + bin_get_string(StrBin). %%------------------------------------------------------------------------------ %% Functions to manipulate Relocations @@ -470,25 +449,15 @@ get_rela_addends(RelaEntries) -> [rela_addend(E) || E <- RelaEntries]. %% symbols and their offsets in the code from the ".text" section. -spec get_text_relocs(elf()) -> [{name(), offset()}]. get_text_relocs(Elf) -> - %% Only care about the symbol table index and the offset: - NameOffsetTemp = [{?ELF_R_SYM(r_info(E)), r_offset(E)} - || E <- extract_rela(Elf, ?TEXT)], - {NameIndices, ActualOffsets} = lists:unzip(NameOffsetTemp), - %% Find the names of the symbols: - %% - %% Get those symbol table entries that are related to Text relocs: Symtab = extract_symtab(Elf), - SymtabEs = [get_symtab_entry(Symtab, Index) || Index <- NameIndices], - %XXX: not zero-indexed! - %% Symbol table entries contain the offset of the name of the symbol in - %% String Table: - SymtabEs2 = [sym_name(E) || E <- SymtabEs], %XXX: Do we need to sort SymtabE? - %% Get string table entries ([{Name, Offset in strtab section}]). Keep only - %% relevant entries: Strtab = extract_strtab(Elf), - Relevant = [get_strtab_entry(Strtab, Off) || Off <- SymtabEs2], - %% Zip back with actual offsets: - lists:zip(Relevant, ActualOffsets). + [begin + %% Find the names of the symbols: + Symbol = get_symtab_entry(Symtab, ?ELF_R_SYM(r_info(E))), + Name = get_strtab_entry(sym_name(Symbol), Strtab), + %% Only care about the name and the offset: + {Name, r_offset(E)} + end || E <- extract_rela(Elf, ?TEXT)]. %% @doc Extract the Relocations segment for section `Name' (that is passed %% as second argument) from an ELF formated Object file binary. @@ -510,10 +479,6 @@ extract_rela(Elf, Name) -> >> <= extract_segment_by_name(Elf, ?RELA(Name))]. -endif. -%% %% @doc Extract the `EntryNum' (serial number) Relocation Entry. -%% get_rela_entry(Rela, EntryNum) -> -%% lists:nth(EntryNum + 1, Rela). - %%------------------------------------------------------------------------------ %% Functions to manipulate Executable Code segment %%------------------------------------------------------------------------------ @@ -640,105 +605,22 @@ get_binary_segment(Bin, Offset, Size) -> %% Section Names. -spec extract_segment_by_name(elf(), string()) -> binary(). extract_segment_by_name(Elf, SectionName) -> - %% Extract Section Header Table and Section Header String Table from binary + %% Extract Section Header Table from binary SHdrTable = extract_shdrtab(Elf), - Names = extract_shstrtab(Elf), - %% Zip to a list of (Name,ShdrE) - [_Zero | ShdrEs] = lists:keysort(2, SHdrTable), % Skip first entry (zeros). - L = lists:zip(Names, ShdrEs), %% Find Section Header Table entry by name - case lists:keyfind(SectionName, 1, L) of - {SectionName, ShdrE} -> %% Note: Same name. - #elf_shdr{offset = Offset, size = Size} = ShdrE, + case lists:keyfind(SectionName, #elf_shdr.name, SHdrTable) of + %% Note: Same name. + #elf_shdr{name = SectionName, offset = Offset, size = Size} -> get_binary_segment(Elf, Offset, Size); false -> %% Not found. <<>> end. -%% @doc Extracts a list of strings with (zero-separated) names from a binary. -%% Returns tuples of `{Name, Size}'. -%% XXX: Skip trailing 0. --spec get_names(<<_:8,_:_*8>>) -> name_sizes(). -get_names(<<0, Bin/binary>>) -> - NamesSizes = get_names(Bin, []), - fix_names(NamesSizes, []). - -get_names(<<>>, Acc) -> - lists:reverse(Acc); -get_names(Bin, Acc) -> - {Name, MoreNames} = bin_get_string(Bin), - get_names(MoreNames, [{Name, length(Name)} | Acc]). - -%% @doc Fix names: -%% e.g. If ".rela.text" exists, ".text" does not. Same goes for -%% ".rel.text". In that way, the Section Header String Table is more -%% compact. Add ".text" just *before* the corresponding rela-field, -%% etc. --spec fix_names(name_sizes(), name_sizes()) -> name_sizes(). -fix_names([], Acc) -> - lists:reverse(Acc); -fix_names([{Name, Size}=T | Names], Acc) -> - case is64bit() of - true -> - case string:str(Name, ".rela") =:= 1 of - true -> %% Name starts with ".rela": - Section = string:substr(Name, 6), - fix_names(Names, [{Section, Size - 5} - | [T | Acc]]); % XXX: Is order ok? (".text" - % always before ".rela.text") - false -> %% Name does not start with ".rela": - fix_names(Names, [T | Acc]) - end; - false -> - case string:str(Name, ".rel") =:= 1 of - true -> %% Name starts with ".rel": - Section = string:substr(Name, 5), - fix_names(Names, [{Section, Size - 4} - | [T | Acc]]); % XXX: Is order ok? (".text" - % always before ".rela.text") - false -> %% Name does not start with ".rel": - fix_names(Names, [T | Acc]) - end - end. - - -%% @doc A function that byte-reverses a binary. This might be needed because of -%% little (fucking!) endianess. --spec bin_reverse(binary()) -> binary(). -bin_reverse(Bin) when is_binary(Bin) -> - bin_reverse(Bin, <<>>). - --spec bin_reverse(binary(), binary()) -> binary(). -bin_reverse(<<>>, Acc) -> - Acc; -bin_reverse(<>, Acc) -> - bin_reverse(More, <>). - -%% @doc A function that extracts a null-terminated string from a binary. It -%% returns the found string along with the rest of the binary. --spec bin_get_string(binary()) -> {string(), binary()}. -bin_get_string(Bin) -> - bin_get_string(Bin, <<>>). - -bin_get_string(<<>>, BinAcc) -> - Bin = bin_reverse(BinAcc), % little endian! - {binary_to_list(Bin), <<>>}; -bin_get_string(<<0, MoreBin/binary>>, BinAcc) -> - Bin = bin_reverse(BinAcc), % little endian! - {binary_to_list(Bin), MoreBin}; -bin_get_string(<>, BinAcc) -> - bin_get_string(Tail, <>). - -%% @doc -make_offsets(NamesSizes) -> - {Names, Sizes} = lists:unzip(NamesSizes), - Offsets = make_offsets_from_sizes(Sizes, 1, []), - lists:zip(Names, Offsets). - -make_offsets_from_sizes([], _, Acc) -> - lists:reverse(Acc); -make_offsets_from_sizes([Size | Sizes], Cur, Acc) -> - make_offsets_from_sizes(Sizes, Size+Cur+1, [Cur | Acc]). % For the "."! +%% @doc Extracts a null-terminated string from a binary. +-spec bin_get_string(binary()) -> string(). +%% FIXME: No regard for encoding (just happens to work for ASCII and Latin-1) +bin_get_string(<<0, _/binary>>) -> []; +bin_get_string(<>) -> [Char|bin_get_string(Rest)]. %% @doc Little-Endian Base 128 (LEB128) Decoder %% This function extracts the first LEB128-encoded integer in a diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index 9e025929b5..1a2fed0c6f 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -24,9 +24,10 @@ rtl_to_native(MFA, RTL, Roots, Options) -> %% Extract information from object file %% ObjBin = open_object_file(ObjectFile), + Obj = elf_format:read(ObjBin), %% Get labels info (for switches and jump tables) - Labels = elf_format:get_rodata_relocs(ObjBin), - {Switches, Closures} = get_tables(ObjBin), + Labels = elf_format:get_rodata_relocs(Obj), + {Switches, Closures} = get_tables(Obj), %% Associate Labels with Switches and Closures with stack args {SwitchInfos, ExposedClosures} = correlate_labels(Switches ++ Closures, Labels), @@ -37,19 +38,19 @@ rtl_to_native(MFA, RTL, Roots, Options) -> %% used for switch's jump tables LabelMap = create_labelmap(MFA, SwitchInfos, RelocsDict), %% Get relocation info - TextRelocs = elf_format:get_text_relocs(ObjBin), + TextRelocs = elf_format:get_text_relocs(Obj), %% AccRefs contains the offsets of all references to relocatable symbols in %% the code: AccRefs = fix_relocations(TextRelocs, RelocsDict, MFA), %% Get stack descriptors - SDescs = get_sdescs(ObjBin), + SDescs = get_sdescs(Obj), %% FixedSDescs are the stack descriptors after correcting calls that have %% arguments in the stack FixedSDescs = fix_stack_descriptors(RelocsDict, AccRefs, SDescs, ExposedClosures), Refs = AccRefs ++ FixedSDescs, %% Get binary code from object file - BinCode = elf_format:extract_text(ObjBin), + BinCode = elf_format:extract_text(Obj), %% Remove temp files (if needed) ok = remove_temp_folder(Dir, Options), %% Return the code together with information that will be used in the -- cgit v1.2.3 From 3dc060d7b6e0f2ea55e6649b23a47d226874b9d4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Tue, 10 May 2016 12:49:58 +0200 Subject: hipe: Restructure elf_format module --- lib/hipe/llvm/elf_format.erl | 237 +++++++++++++++++---------------------- lib/hipe/llvm/hipe_llvm_main.erl | 13 +-- 2 files changed, 103 insertions(+), 147 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index 13a00bfd38..e56ccce626 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -37,25 +37,32 @@ -export_type([elf/0]). --opaque elf() :: binary(). - -type lp() :: non_neg_integer(). % landing pad -type num() :: non_neg_integer(). -type index() :: non_neg_integer(). -type offset() :: non_neg_integer(). -type size() :: non_neg_integer(). -type start() :: non_neg_integer(). +-type reloc_type() :: atom(). --type info() :: index(). --type nameoff() :: offset(). -type valueoff() :: offset(). -type name() :: string(). +-type tuple(X) :: {} | {X} | {X, X} | tuple(). + %%------------------------------------------------------------------------------ %% Abstract Data Types and Accessors for ELF Structures. %%------------------------------------------------------------------------------ +-record(elf, {file :: binary() + ,sec_idx :: tuple(elf_shdr()) + ,sec_nam :: #{string() => elf_shdr()} + ,sym_idx :: undefined | tuple(elf_sym()) + }). + +-opaque elf() :: #elf{}. + %% File header -record(elf_ehdr, {ident, % ELF identification type, % Object file type @@ -99,29 +106,22 @@ -type elf_shdr() :: #elf_shdr{}. %% Symbol table entries --record(elf_sym, {name :: nameoff(), % Symbol name +-record(elf_sym, {name :: string(), % Symbol name info, % Type and Binding attributes other, % Reserved - shndx, % Section table index + section :: undefined | abs | elf_shdr(), value :: valueoff(), % Symbol value size :: size() % Size of object }). -type elf_sym() :: #elf_sym{}. %% Relocations --ifdef(BIT32). --record(elf_rel, {r_offset :: offset(), % Address of reference - r_info :: info() % Symbol index and type of relocation - }). --type reloc() :: #elf_rel{}. --else. - --record(elf_rela, {r_offset :: offset(), % Address of reference - r_info :: info(), % Symbol index and type of relocation - r_addend :: offset() % Constant part of expression - }). --type reloc() :: #elf_rela{}. --endif. +-record(elf_rel, {offset :: offset() + ,type :: reloc_type() + ,addend :: offset() | undefined + ,symbol :: elf_sym() + }). +-type elf_rel() :: #elf_rel{}. %% %% Program header table %% -record(elf_phdr, {type, % Type of segment @@ -201,11 +201,11 @@ mk_shdr(Name, Type, Flags, Addr, Offset, Size, Link, Info, AddrAlign, EntSize) - %%%------------------------- %%% Symbol Table Entries %%%------------------------- -mk_sym(Name, Info, Other, Shndx, Value, Size) -> +mk_sym(Name, Info, Other, Section, Value, Size) -> #elf_sym{name = Name, info = Info, other = Other, - shndx = Shndx, value = Value, size = Size}. + section = Section, value = Value, size = Size}. --spec sym_name(elf_sym()) -> nameoff(). +-spec sym_name(elf_sym()) -> string(). sym_name(#elf_sym{name = Name}) -> Name. %% -spec sym_value(elf_sym()) -> valueoff(). @@ -214,39 +214,6 @@ sym_name(#elf_sym{name = Name}) -> Name. %% -spec sym_size(elf_sym()) -> size(). %% sym_size(#elf_sym{size = Size}) -> Size. -%%%------------------------- -%%% Relocations -%%%------------------------- - - -%% The following two functions capitalize on the fact that the two kinds of -%% relocation records (for 32- and 64-bit architectures have similar structure. --spec r_offset(reloc()) -> offset(). --spec r_info(reloc()) -> info(). - --ifdef(BIT32). - --spec mk_rel(offset(), info()) -> reloc(). -mk_rel(Offset, Info) -> - #elf_rel{r_offset = Offset, r_info = Info}. - -r_offset(#elf_rel{r_offset = Offset}) -> Offset. -r_info(#elf_rel{r_info = Info}) -> Info. - --else.%%BIT32 - --spec mk_rela(offset(), info(), offset()) -> reloc(). -mk_rela(Offset, Info, Addend) -> - #elf_rela{r_offset = Offset, r_info = Info, r_addend = Addend}. - -r_offset(#elf_rela{r_offset = Offset}) -> Offset. -r_info(#elf_rela{r_info = Info}) -> Info. - --spec rela_addend(reloc()) -> offset(). -rela_addend(#elf_rela{r_addend = Addend}) -> Addend. - --endif.%%BIT32 - %% %%%------------------------- %% %%% GCC exception table %% %%%------------------------- @@ -278,7 +245,14 @@ mk_gccexntab_callsite(Start, Size, LP, Action) -> %% @doc Parses an ELF file. -spec read(binary()) -> elf(). -read(ElfBin) -> ElfBin. +read(ElfBin) -> + Header = extract_header(ElfBin), + [_UndefinedSec|Sections] = extract_shdrtab(ElfBin, Header), + SecNam = maps:from_list( + [{Name, Sec} || Sec = #elf_shdr{name=Name} <- Sections]), + Elf0 = #elf{file=ElfBin, sec_idx=list_to_tuple(Sections), sec_nam=SecNam}, + [_UndefinedSym|Symbols] = extract_symtab(Elf0, extract_strtab(Elf0)), + Elf0#elf{sym_idx=list_to_tuple(Symbols)}. %%------------------------------------------------------------------------------ %% Functions to manipulate the ELF File Header @@ -287,9 +261,9 @@ read(ElfBin) -> ElfBin. %% @doc Extracts the File Header from an ELF formatted object file. Also sets %% the ELF class variable in the process dictionary (used by many functions %% in this and hipe_llvm_main modules). --spec extract_header(elf()) -> elf_ehdr(). -extract_header(Elf) -> - Ehdr_bin = get_binary_segment(Elf, 0, ?ELF_EHDR_SIZE), +-spec extract_header(binary()) -> elf_ehdr(). +extract_header(ElfBin) -> + Ehdr_bin = get_binary_segment(ElfBin, 0, ?ELF_EHDR_SIZE), << %% Structural pattern matching on fields. Ident_bin:?E_IDENT_SIZE/binary, Type:?bits(?E_TYPE_SIZE)/integer-little, @@ -321,14 +295,11 @@ extract_header(Elf) -> -type shdrtab() :: [elf_shdr()]. %% @doc Extracts the Section Header Table from an ELF formated Object File. --spec extract_shdrtab(elf()) -> shdrtab(). -extract_shdrtab(Elf) -> - %% Extract File Header to get info about Section Header Offset (in bytes), - %% Entry Size (in bytes) and Number of entries - #elf_ehdr{shoff = ShOff, shentsize = ShEntsize, shnum = ShNum - ,shstrndx = ShStrNdx} = extract_header(Elf), +-spec extract_shdrtab(binary(), elf_ehdr()) -> shdrtab(). +extract_shdrtab(ElfBin, #elf_ehdr{shoff=ShOff, shentsize=?ELF_SHDRENTRY_SIZE, + shnum=ShNum, shstrndx=ShStrNdx}) -> %% Get actual Section header table (binary) - ShdrBin = get_binary_segment(Elf, ShOff, ShNum * ShEntsize), + ShdrBin = get_binary_segment(ElfBin, ShOff, ShNum * ?ELF_SHDRENTRY_SIZE), %% We need to lookup the offset and size of the section header string table %% before we can fully parse the section table. We compute its offset and %% extract the fields we need here. @@ -338,7 +309,7 @@ extract_shdrtab(Elf) -> ShStrOffset:?bits(?SH_OFFSET_SIZE)/little, ShStrSize:?bits(?SH_SIZE_SIZE)/little, _/binary>> = ShdrBin, - ShStrTab = parse_strtab(get_binary_segment(Elf, ShStrOffset, ShStrSize)), + ShStrTab = parse_strtab(get_binary_segment(ElfBin, ShStrOffset, ShStrSize)), get_shdrtab_entries(ShdrBin, ShStrTab). get_shdrtab_entries(<<>>, _ShStrTab) -> []; @@ -360,24 +331,28 @@ get_shdrtab_entries(ShdrTab, ShStrTab) -> Size, Link, Info, Addralign, Entsize), [Entry | get_shdrtab_entries(Rest, ShStrTab)]. +-spec elf_section(non_neg_integer(), elf()) -> undefined | abs | elf_shdr(). +elf_section(0, #elf{}) -> undefined; +elf_section(?SHN_ABS, #elf{}) -> abs; +elf_section(Index, #elf{sec_idx=SecIdx}) when Index =< tuple_size(SecIdx) -> + element(Index, SecIdx). + %%------------------------------------------------------------------------------ -spec get_tab_entries(elf()) -> [{name(), valueoff(), size()}]. -get_tab_entries(Elf) -> - SymTab = extract_symtab(Elf), - StrTab = extract_strtab(Elf), - [{get_strtab_entry(Name, StrTab), Value, Size div ?ELF_XWORD_SIZE} - || #elf_sym{name = Name, value = Value, size = Size} <- SymTab, - Name =/= 0]. +get_tab_entries(#elf{sym_idx=SymIdx}) -> + [{Name, Value, Size div ?ELF_XWORD_SIZE} + || #elf_sym{name = Name, value = Value, size = Size} + <- tuple_to_list(SymIdx), Name =/= ""]. %%------------------------------------------------------------------------------ %% Functions to manipulate Symbol Table %%------------------------------------------------------------------------------ %% @doc Function that extracts Symbol Table from an ELF Object file. -extract_symtab(Elf) -> +extract_symtab(Elf, StrTab) -> Symtab = extract_segment_by_name(Elf, ?SYMTAB), - [parse_sym(Sym) || <> <= Symtab]. + [parse_sym(Sym, Elf, StrTab) || <> <= Symtab]. -ifdef(BIT32). parse_sym(<<%% Structural pattern matching on fields. @@ -386,8 +361,10 @@ parse_sym(<<%% Structural pattern matching on fields. Size:?bits(?ST_SIZE_SIZE)/integer-little, Info:?bits(?ST_INFO_SIZE)/integer-little, Other:?bits(?ST_OTHER_SIZE)/integer-little, - Shndx:?bits(?ST_SHNDX_SIZE)/integer-little>>) -> - mk_sym(Name, Info, Other, Shndx, Value, Size). + Shndx:?bits(?ST_SHNDX_SIZE)/integer-little>>, + Elf, StrTab) -> + mk_sym(get_strtab_entry(Name, StrTab), Info, Other, elf_section(Shndx, Elf), + Value, Size). -else. parse_sym(<<%% Same fields in different order: Name:?bits(?ST_NAME_SIZE)/integer-little, @@ -395,15 +372,17 @@ parse_sym(<<%% Same fields in different order: Other:?bits(?ST_OTHER_SIZE)/integer-little, Shndx:?bits(?ST_SHNDX_SIZE)/integer-little, Value:?bits(?ST_VALUE_SIZE)/integer-little, - Size:?bits(?ST_SIZE_SIZE)/integer-little>>) -> - mk_sym(Name, Info, Other, Shndx, Value, Size). + Size:?bits(?ST_SIZE_SIZE)/integer-little>>, + Elf, StrTab) -> + mk_sym(get_strtab_entry(Name, StrTab), Info, Other, elf_section(Shndx, Elf), + Value, Size). -endif. -%% @doc Extracts a specific entry from the Symbol Table (as binary). -%% This function takes as arguments the Symbol Table (`SymTab') -%% and the entry's serial number and returns that entry (`sym'). -get_symtab_entry(SymTab, EntryNum) -> - lists:nth(EntryNum + 1, SymTab). +%% @doc Extracts a specific entry from the Symbol Table. +-spec elf_symbol(0, elf()) -> undefined; + (pos_integer(), elf()) -> elf_sym(). +elf_symbol(0, #elf{}) -> undefined; +elf_symbol(Index, #elf{sym_idx=SymIdx}) -> element(Index, SymIdx). %%------------------------------------------------------------------------------ %% Functions to manipulate String Table @@ -426,6 +405,12 @@ get_strtab_entry(Offset, StrTab) -> <<_:Offset/binary, StrBin/binary>> = StrTab, bin_get_string(StrBin). +%% @doc Extracts a null-terminated string from a binary. +-spec bin_get_string(binary()) -> string(). +%% FIXME: No regard for encoding (just happens to work for ASCII and Latin-1) +bin_get_string(<<0, _/binary>>) -> []; +bin_get_string(<>) -> [Char|bin_get_string(Rest)]. + %%------------------------------------------------------------------------------ %% Functions to manipulate Relocations %%------------------------------------------------------------------------------ @@ -434,50 +419,54 @@ get_strtab_entry(Offset, StrTab) -> %% with all .rela.rodata labels (i.e. constants and literals in code) %% or an empty list if no ".rela.rodata" section exists in code. -spec get_rodata_relocs(elf()) -> [offset()]. --spec get_rela_addends([reloc()]) -> [offset()]. --ifdef(BIT32). -get_rodata_relocs(Elf) -> - [SkipPadding || SkipPadding <- extract_rodata(Elf), SkipPadding =/= 0]. -get_rela_addends(_RelaEntries) -> error(notsup). --else. get_rodata_relocs(Elf) -> get_rela_addends(extract_rela(Elf, ?RODATA)). -get_rela_addends(RelaEntries) -> [rela_addend(E) || E <- RelaEntries]. --endif. +-spec get_rela_addends([elf_rel()]) -> [offset()]. +get_rela_addends(RelaEntries) -> [A || #elf_rel{addend=A} <- RelaEntries]. %% @doc Extract a list of the form `[{SymbolName, Offset}]' with all relocatable %% symbols and their offsets in the code from the ".text" section. -spec get_text_relocs(elf()) -> [{name(), offset()}]. get_text_relocs(Elf) -> - Symtab = extract_symtab(Elf), - Strtab = extract_strtab(Elf), - [begin - %% Find the names of the symbols: - Symbol = get_symtab_entry(Symtab, ?ELF_R_SYM(r_info(E))), - Name = get_strtab_entry(sym_name(Symbol), Strtab), - %% Only care about the name and the offset: - {Name, r_offset(E)} - end || E <- extract_rela(Elf, ?TEXT)]. + [{sym_name(Symbol), Offset} + || #elf_rel{offset=Offset, symbol=Symbol} <- extract_rela(Elf, ?TEXT)]. %% @doc Extract the Relocations segment for section `Name' (that is passed %% as second argument) from an ELF formated Object file binary. --spec extract_rela(elf(), name()) -> [reloc()]. +-spec extract_rela(elf(), name()) -> [elf_rel()]. -ifdef(BIT32). extract_rela(Elf, Name) -> - %% Structural pattern matching on fields of a Rel Entry. - [mk_rel(Offset, Info) + SecData = extract_segment_by_name(Elf, Name), + [#elf_rel{offset=Offset, symbol=elf_symbol(?ELF_R_SYM(Info), Elf), + type=decode_reloc_type(?ELF_R_TYPE(Info)), + addend=read_implicit_addend(Offset, SecData)} || <> <= extract_segment_by_name(Elf, ?REL(Name))]. --else. + +%% The only types HiPE knows how to patch +decode_reloc_type(1) -> '32'; +decode_reloc_type(2) -> 'pc32'. + +read_implicit_addend(Offset, Section) -> + %% All x86 relocation types uses 'word32' relocation fields; i.e. 32-bit LE. + <<_:Offset/binary, Addend:32/little, _/binary>> = Section, + Addend. + +-else. %% BIT32 extract_rela(Elf, Name) -> - [mk_rela(Offset, Info, Addend) + [#elf_rel{offset=Offset, symbol=elf_symbol(?ELF_R_SYM(Info), Elf), + type=decode_reloc_type(?ELF_R_TYPE(Info)), addend=Addend} || <> <= extract_segment_by_name(Elf, ?RELA(Name))]. --endif. + +decode_reloc_type(1) -> '64'; +decode_reloc_type(2) -> 'pc32'; +decode_reloc_type(10) -> '32'. +-endif. %% BIT32 %%------------------------------------------------------------------------------ %% Functions to manipulate Executable Code segment @@ -569,21 +558,6 @@ get_gccexntab_callsites(CSTab, Acc) -> GccCS = mk_gccexntab_callsite(Start, Size, LP, OnAction), get_gccexntab_callsites(More, [GccCS | Acc]). -%%------------------------------------------------------------------------------ -%% Functions to manipulate Read-only Data (.rodata) -%%------------------------------------------------------------------------------ --ifdef(BIT32). -extract_rodata(Elf) -> - Rodata_bin = extract_segment_by_name(Elf, ?RODATA), - get_rodata_entries(Rodata_bin, []). - -get_rodata_entries(<<>>, Acc) -> - lists:reverse(Acc); -get_rodata_entries(Rodata_bin, Acc) -> - <> = Rodata_bin, - get_rodata_entries(More, [Num | Acc]). --endif. - %%------------------------------------------------------------------------------ %% Helper functions %%------------------------------------------------------------------------------ @@ -604,24 +578,15 @@ get_binary_segment(Bin, Offset, Size) -> %% There are handy macros defined in elf_format.hrl for all Standard %% Section Names. -spec extract_segment_by_name(elf(), string()) -> binary(). -extract_segment_by_name(Elf, SectionName) -> - %% Extract Section Header Table from binary - SHdrTable = extract_shdrtab(Elf), +extract_segment_by_name(#elf{file=ElfBin, sec_nam=SecNam}, SectionName) -> %% Find Section Header Table entry by name - case lists:keyfind(SectionName, #elf_shdr.name, SHdrTable) of - %% Note: Same name. - #elf_shdr{name = SectionName, offset = Offset, size = Size} -> - get_binary_segment(Elf, Offset, Size); - false -> %% Not found. + case SecNam of + #{SectionName := #elf_shdr{offset=Offset, size=Size}} -> + get_binary_segment(ElfBin, Offset, Size); + #{} -> %% Not found. <<>> end. -%% @doc Extracts a null-terminated string from a binary. --spec bin_get_string(binary()) -> string(). -%% FIXME: No regard for encoding (just happens to work for ASCII and Latin-1) -bin_get_string(<<0, _/binary>>) -> []; -bin_get_string(<>) -> [Char|bin_get_string(Rest)]. - %% @doc Little-Endian Base 128 (LEB128) Decoder %% This function extracts the first LEB128-encoded integer in a %% binary and returns that integer along with the remaining binary. This is diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index 1a2fed0c6f..60833d4af9 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -271,14 +271,14 @@ get_sdescs(Elf) -> T = SPCount * ?SP_ADDR_SIZE, %% Pattern match fields of ".note.gc": <> = NoteGC_bin, LiveRoots = get_liveroots(Roots, []), %% Extract the safe point offsets: - SPOffs = get_reloc_addends(SPAddrs, RelaNoteGC), + SPOffs = elf_format:get_rela_addends(RelaNoteGC), %% Extract Exception Handler labels: ExnHandlers = elf_format:get_exn_handlers(Elf), %% Combine ExnHandlers and Safe point addresses (return addresses): @@ -294,15 +294,6 @@ get_liveroots(<>, Acc) -> get_liveroots(MoreRoots, [Root | Acc]). --ifdef(BIT32). -%% ELF32 x86 uses implicit addends. -get_reloc_addends(Table, _Relocs) -> - [Add || <> <= Table]. --else. -%% ELF64 x64 uses explicit addends. -get_reloc_addends(_Table, Relocs) -> elf_format:get_rela_addends(Relocs). --endif. - combine_ras_and_exns(_, [], Acc) -> lists:reverse(Acc); combine_ras_and_exns(ExnHandlers, [RA | MoreRAs], Acc) -> -- cgit v1.2.3 From 0f489445070cf65d96db7938f80ad118921c1f6a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Tue, 10 May 2016 17:22:25 +0200 Subject: hipe: Extract some records into elf_format.hrl This allows for much more robust interpretation of relocations, symbols and sections in hipe_llvm_main, without the clunkiness of an abstract interface between two internal modules that belong to the same subsystem anyway. --- lib/hipe/llvm/Makefile | 8 +++ lib/hipe/llvm/elf32_format.hrl | 6 ++ lib/hipe/llvm/elf64_format.hrl | 6 ++ lib/hipe/llvm/elf_format.erl | 140 ++++++++++++++++----------------------- lib/hipe/llvm/elf_format.hrl | 52 +++++++++++++++ lib/hipe/llvm/hipe_llvm_main.erl | 131 +++++++++++++++++++----------------- 6 files changed, 197 insertions(+), 146 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/Makefile b/lib/hipe/llvm/Makefile index d2d39fb9e3..d172e37b02 100644 --- a/lib/hipe/llvm/Makefile +++ b/lib/hipe/llvm/Makefile @@ -108,3 +108,11 @@ release_spec: opt $(INSTALL_DATA) $(TARGET_FILES) $(RELSYSDIR)/ebin release_docs_spec: + +$(EBIN)/elf_format.beam: elf_format.hrl elf32_format.hrl elf64_format.hrl +$(EBIN)/hipe_llvm_main.beam: ../../kernel/src/hipe_ext_format.hrl \ + hipe_llvm_arch.hrl elf_format.hrl elf32_format.hrl elf64_format.hrl +$(EBIN)/hipe_llvm_merge.beam: ../../kernel/src/hipe_ext_format.hrl \ + hipe_llvm_arch.hrl ../rtl/hipe_literals.hrl ../main/hipe.hrl +$(EBIN)/hipe_rtl_to_llvm.beam: ../rtl/hipe_rtl.hrl ../rtl/hipe_literals.hrl \ + hipe_llvm_arch.hrl diff --git a/lib/hipe/llvm/elf32_format.hrl b/lib/hipe/llvm/elf32_format.hrl index af1d95bf5b..1158cb6434 100644 --- a/lib/hipe/llvm/elf32_format.hrl +++ b/lib/hipe/llvm/elf32_format.hrl @@ -57,3 +57,9 @@ -define(P_MEMSZ_OFFSET, (?P_FILESZ_OFFSET + ?P_FILESZ_SIZE) ). -define(P_FLAGS_OFFSET, (?P_TYPE_OFFSET + ?P_TYPE_SIZE) ). -define(P_ALIGN_OFFSET, (?P_MEMSZ_OFFSET + ?P_MEMSZ_SIZE) ). + +%%------------------------------------------------------------------------------ +%% Exported record and type declarations for 'elf_format' module +%%------------------------------------------------------------------------------ + +-type reloc_type() :: '32' | 'pc32'. diff --git a/lib/hipe/llvm/elf64_format.hrl b/lib/hipe/llvm/elf64_format.hrl index 794746ffdc..0136e7f381 100644 --- a/lib/hipe/llvm/elf64_format.hrl +++ b/lib/hipe/llvm/elf64_format.hrl @@ -56,3 +56,9 @@ -define(P_FILESZ_OFFSET, (?P_PVADDR_OFFSET + ?P_PVADDR_SIZE) ). -define(P_MEMSZ_OFFSET, (?P_FILESZ_OFFSET + ?P_FILESZ_SIZE) ). -define(P_ALIGN_OFFSET, (?P_MEMSZ_OFFSET + ?P_MEMSZ_SIZE) ). + +%%------------------------------------------------------------------------------ +%% Exported record and type declarations for 'elf_format' module +%%------------------------------------------------------------------------------ + +-type reloc_type() :: '64' | 'pc32' | '32'. diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index e56ccce626..4155dff7c4 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -13,18 +13,16 @@ -module(elf_format). --export([get_tab_entries/1, - %% Relocations - get_rodata_relocs/1, - get_text_relocs/1, +-export([%% Relocations extract_rela/2, - get_rela_addends/1, %% Note extract_note/2, %% Executable code extract_text/1, %% GCC Exception Table get_exn_handlers/1, + %% Symbols + elf_symbols/1, %% Main interface read/1 ]). @@ -40,14 +38,7 @@ -type lp() :: non_neg_integer(). % landing pad -type num() :: non_neg_integer(). -type index() :: non_neg_integer(). --type offset() :: non_neg_integer(). --type size() :: non_neg_integer(). -type start() :: non_neg_integer(). --type reloc_type() :: atom(). - --type valueoff() :: offset(). - --type name() :: string(). -type tuple(X) :: {} | {X} | {X, X} | tuple(). @@ -91,38 +82,6 @@ }). %% -type elf_ehdr_ident() :: #elf_ehdr_ident{}. -%% Section header entries --record(elf_shdr, {name :: string(), % Section name - type, % Section type - flags, % Section attributes - addr, % Virtual address in memory - offset :: offset(), % Offset in file - size :: size(), % Size of section - link, % Link to other section - info, % Miscellaneous information - addralign, % Address align boundary - entsize % Size of entries, if section has table - }). --type elf_shdr() :: #elf_shdr{}. - -%% Symbol table entries --record(elf_sym, {name :: string(), % Symbol name - info, % Type and Binding attributes - other, % Reserved - section :: undefined | abs | elf_shdr(), - value :: valueoff(), % Symbol value - size :: size() % Size of object - }). --type elf_sym() :: #elf_sym{}. - -%% Relocations --record(elf_rel, {offset :: offset() - ,type :: reloc_type() - ,addend :: offset() | undefined - ,symbol :: elf_sym() - }). --type elf_rel() :: #elf_rel{}. - %% %% Program header table %% -record(elf_phdr, {type, % Type of segment %% flags, % Segment attributes @@ -201,13 +160,13 @@ mk_shdr(Name, Type, Flags, Addr, Offset, Size, Link, Info, AddrAlign, EntSize) - %%%------------------------- %%% Symbol Table Entries %%%------------------------- -mk_sym(Name, Info, Other, Section, Value, Size) -> - #elf_sym{name = Name, info = Info, other = Other, +mk_sym(Name, Bind, Type, Section, Value, Size) -> + #elf_sym{name = Name, bind = Bind, type = Type, section = Section, value = Value, size = Size}. --spec sym_name(elf_sym()) -> string(). -sym_name(#elf_sym{name = Name}) -> Name. - +%% -spec sym_name(elf_sym()) -> string(). +%% sym_name(#elf_sym{name = Name}) -> Name. +%% %% -spec sym_value(elf_sym()) -> valueoff(). %% sym_value(#elf_sym{value = Value}) -> Value. %% @@ -327,24 +286,32 @@ get_shdrtab_entries(ShdrTab, ShStrTab) -> Entsize:?bits(?SH_ENTSIZE_SIZE)/integer-little, Rest/binary >> = ShdrTab, - Entry = mk_shdr(get_strtab_entry(Name, ShStrTab), Type, Flags, Addr, Offset, - Size, Link, Info, Addralign, Entsize), + Entry = mk_shdr(get_strtab_entry(Name, ShStrTab), decode_shdr_type(Type), + Flags, Addr, Offset, Size, Link, Info, Addralign, Entsize), [Entry | get_shdrtab_entries(Rest, ShStrTab)]. +decode_shdr_type(?SHT_NULL) -> 'null'; +decode_shdr_type(?SHT_PROGBITS) -> 'progbits'; +decode_shdr_type(?SHT_SYMTAB) -> 'symtab'; +decode_shdr_type(?SHT_STRTAB) -> 'strtab'; +decode_shdr_type(?SHT_RELA) -> 'rela'; +decode_shdr_type(?SHT_HASH) -> 'hash'; %unused +decode_shdr_type(?SHT_DYNAMIC) -> 'dynamic'; %unused +decode_shdr_type(?SHT_NOTE) -> 'note'; %unused +decode_shdr_type(?SHT_NOBITS) -> 'nobits'; +decode_shdr_type(?SHT_REL) -> 'rel'; +decode_shdr_type(?SHT_SHLIB) -> 'shlib'; %unused +decode_shdr_type(?SHT_DYNSYM) -> 'dynsym'; %unused +decode_shdr_type(OS) when ?SHT_LOOS =< OS, OS =< ?SHT_HIOS -> {os, OS}; +decode_shdr_type(Proc) when ?SHT_LOPROC =< Proc, Proc =< ?SHT_HIPROC -> + {proc, Proc}. + -spec elf_section(non_neg_integer(), elf()) -> undefined | abs | elf_shdr(). elf_section(0, #elf{}) -> undefined; elf_section(?SHN_ABS, #elf{}) -> abs; elf_section(Index, #elf{sec_idx=SecIdx}) when Index =< tuple_size(SecIdx) -> element(Index, SecIdx). -%%------------------------------------------------------------------------------ - --spec get_tab_entries(elf()) -> [{name(), valueoff(), size()}]. -get_tab_entries(#elf{sym_idx=SymIdx}) -> - [{Name, Value, Size div ?ELF_XWORD_SIZE} - || #elf_sym{name = Name, value = Value, size = Size} - <- tuple_to_list(SymIdx), Name =/= ""]. - %%------------------------------------------------------------------------------ %% Functions to manipulate Symbol Table %%------------------------------------------------------------------------------ @@ -360,30 +327,51 @@ parse_sym(<<%% Structural pattern matching on fields. Value:?bits(?ST_VALUE_SIZE)/integer-little, Size:?bits(?ST_SIZE_SIZE)/integer-little, Info:?bits(?ST_INFO_SIZE)/integer-little, - Other:?bits(?ST_OTHER_SIZE)/integer-little, + _Other:?bits(?ST_OTHER_SIZE)/integer-little, Shndx:?bits(?ST_SHNDX_SIZE)/integer-little>>, Elf, StrTab) -> - mk_sym(get_strtab_entry(Name, StrTab), Info, Other, elf_section(Shndx, Elf), - Value, Size). + mk_sym(get_strtab_entry(Name, StrTab), decode_symbol_bind(?ELF_ST_BIND(Info)), + decode_symbol_type(?ELF_ST_TYPE(Info)), elf_section(Shndx, Elf), Value, + Size). -else. parse_sym(<<%% Same fields in different order: Name:?bits(?ST_NAME_SIZE)/integer-little, Info:?bits(?ST_INFO_SIZE)/integer-little, - Other:?bits(?ST_OTHER_SIZE)/integer-little, + _Other:?bits(?ST_OTHER_SIZE)/integer-little, Shndx:?bits(?ST_SHNDX_SIZE)/integer-little, Value:?bits(?ST_VALUE_SIZE)/integer-little, Size:?bits(?ST_SIZE_SIZE)/integer-little>>, Elf, StrTab) -> - mk_sym(get_strtab_entry(Name, StrTab), Info, Other, elf_section(Shndx, Elf), - Value, Size). + mk_sym(get_strtab_entry(Name, StrTab), decode_symbol_bind(?ELF_ST_BIND(Info)), + decode_symbol_type(?ELF_ST_TYPE(Info)), elf_section(Shndx, Elf), Value, + Size). -endif. +decode_symbol_bind(?STB_LOCAL) -> 'local'; +decode_symbol_bind(?STB_GLOBAL) -> 'global'; +decode_symbol_bind(?STB_WEAK) -> 'weak'; %unused +decode_symbol_bind(OS) when ?STB_LOOS =< OS, OS =< ?STB_HIOS -> {os, OS}; +decode_symbol_bind(Proc) when ?STB_LOPROC =< Proc, Proc =< ?STB_HIPROC -> + {proc, Proc}. + +decode_symbol_type(?STT_NOTYPE) -> 'notype'; +decode_symbol_type(?STT_OBJECT) -> 'object'; +decode_symbol_type(?STT_FUNC) -> 'func'; +decode_symbol_type(?STT_SECTION) -> 'section'; +decode_symbol_type(?STT_FILE) -> 'file'; +decode_symbol_type(OS) when ?STT_LOOS =< OS, OS =< ?STT_HIOS -> {os, OS}; +decode_symbol_type(Proc) when ?STT_LOPROC =< Proc, Proc =< ?STT_HIPROC -> + {proc, Proc}. + %% @doc Extracts a specific entry from the Symbol Table. -spec elf_symbol(0, elf()) -> undefined; (pos_integer(), elf()) -> elf_sym(). elf_symbol(0, #elf{}) -> undefined; elf_symbol(Index, #elf{sym_idx=SymIdx}) -> element(Index, SymIdx). +-spec elf_symbols(elf()) -> [elf_sym()]. +elf_symbols(#elf{sym_idx=SymIdx}) -> tuple_to_list(SymIdx). + %%------------------------------------------------------------------------------ %% Functions to manipulate String Table %%------------------------------------------------------------------------------ @@ -415,22 +403,6 @@ bin_get_string(<>) -> [Char|bin_get_string(Rest)]. %% Functions to manipulate Relocations %%------------------------------------------------------------------------------ -%% @doc This function gets as argument an ELF binary file and returns a list -%% with all .rela.rodata labels (i.e. constants and literals in code) -%% or an empty list if no ".rela.rodata" section exists in code. --spec get_rodata_relocs(elf()) -> [offset()]. -get_rodata_relocs(Elf) -> get_rela_addends(extract_rela(Elf, ?RODATA)). - --spec get_rela_addends([elf_rel()]) -> [offset()]. -get_rela_addends(RelaEntries) -> [A || #elf_rel{addend=A} <- RelaEntries]. - -%% @doc Extract a list of the form `[{SymbolName, Offset}]' with all relocatable -%% symbols and their offsets in the code from the ".text" section. --spec get_text_relocs(elf()) -> [{name(), offset()}]. -get_text_relocs(Elf) -> - [{sym_name(Symbol), Offset} - || #elf_rel{offset=Offset, symbol=Symbol} <- extract_rela(Elf, ?TEXT)]. - %% @doc Extract the Relocations segment for section `Name' (that is passed %% as second argument) from an ELF formated Object file binary. -spec extract_rela(elf(), name()) -> [elf_rel()]. @@ -442,7 +414,7 @@ extract_rela(Elf, Name) -> type=decode_reloc_type(?ELF_R_TYPE(Info)), addend=read_implicit_addend(Offset, SecData)} || <> <= extract_segment_by_name(Elf, ?REL(Name))]. %% The only types HiPE knows how to patch @@ -451,7 +423,7 @@ decode_reloc_type(2) -> 'pc32'. read_implicit_addend(Offset, Section) -> %% All x86 relocation types uses 'word32' relocation fields; i.e. 32-bit LE. - <<_:Offset/binary, Addend:32/little, _/binary>> = Section, + <<_:Offset/binary, Addend:32/signed-little, _/binary>> = Section, Addend. -else. %% BIT32 @@ -460,7 +432,7 @@ extract_rela(Elf, Name) -> type=decode_reloc_type(?ELF_R_TYPE(Info)), addend=Addend} || <> <= extract_segment_by_name(Elf, ?RELA(Name))]. decode_reloc_type(1) -> '64'; diff --git a/lib/hipe/llvm/elf_format.hrl b/lib/hipe/llvm/elf_format.hrl index 7a3cdfead6..5074682ae6 100644 --- a/lib/hipe/llvm/elf_format.hrl +++ b/lib/hipe/llvm/elf_format.hrl @@ -486,3 +486,55 @@ %% Misc. %%------------------------------------------------------------------------------ -define(bits(Bytes), ((Bytes) bsl 3)). + +%%------------------------------------------------------------------------------ +%% Exported record and type declarations for 'elf_format' module +%%------------------------------------------------------------------------------ + +-type offset() :: non_neg_integer(). +-type size() :: non_neg_integer(). +-type addend() :: integer() | undefined. +-type sym_bind() :: 'local' | 'global' | 'weak' | {os, ?STB_LOOS..?STB_HIOS} + | {proc, ?STB_LOPROC..?STB_HIPROC}. +-type sym_type() :: 'notype' | 'object' | 'func' | 'section' | 'file' + | {os, ?STT_LOOS..?STT_HIOS} + | {proc, ?STT_LOPROC..?STT_HIPROC}. +-type shdr_type() :: 'null' | 'progbits' | 'symtab' | 'strtab' | 'rela' + | 'hash' | 'dynamic' | 'note' | 'nobits' | 'rel' | 'shlib' + | 'dynsym' | {os, ?SHT_LOOS..?SHT_HIOS} + | {proc, ?SHT_LOPROC..?SHT_HIPROC}. + +-type valueoff() :: offset(). +-type name() :: string(). + +%% Section header entries +-record(elf_shdr, {name :: name() % Section name + ,type :: shdr_type()% Section type + ,flags % Section attributes + ,addr % Virtual address in memory + ,offset :: offset() % Offset in file + ,size :: size() % Size of section + ,link % Link to other section + ,info % Miscellaneous information + ,addralign % Address align boundary + ,entsize % Size of entries, if section has table + }). +-type elf_shdr() :: #elf_shdr{}. + +%% Symbol table entries +-record(elf_sym, {name :: name() % Symbol name + ,bind :: sym_bind() % Symbol binding + ,type :: sym_type() % Symbol type + ,value :: valueoff() % Symbol value + ,size :: size() % Size of object + ,section :: undefined | abs | elf_shdr() + }). +-type elf_sym() :: #elf_sym{}. + +%% Relocations +-record(elf_rel, {offset :: offset() + ,type :: reloc_type() + ,addend :: addend() + ,symbol :: elf_sym() + }). +-type elf_rel() :: #elf_rel{}. diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index 60833d4af9..3ab213f94c 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -26,11 +26,10 @@ rtl_to_native(MFA, RTL, Roots, Options) -> ObjBin = open_object_file(ObjectFile), Obj = elf_format:read(ObjBin), %% Get labels info (for switches and jump tables) - Labels = elf_format:get_rodata_relocs(Obj), - {Switches, Closures} = get_tables(Obj), + Labels = elf_format:extract_rela(Obj, ?RODATA), + Tables = get_tables(Obj), %% Associate Labels with Switches and Closures with stack args - {SwitchInfos, ExposedClosures} = - correlate_labels(Switches ++ Closures, Labels), + {SwitchInfos, ExposedClosures} = correlate_labels(Tables, Labels), %% SwitchInfos: [{"table_50", [Labels]}] %% ExposedClosures: [{"table_closures", [Labels]}] @@ -38,7 +37,7 @@ rtl_to_native(MFA, RTL, Roots, Options) -> %% used for switch's jump tables LabelMap = create_labelmap(MFA, SwitchInfos, RelocsDict), %% Get relocation info - TextRelocs = elf_format:get_text_relocs(Obj), + TextRelocs = elf_format:extract_rela(Obj, ?TEXT), %% AccRefs contains the offsets of all references to relocatable symbols in %% the code: AccRefs = fix_relocations(TextRelocs, RelocsDict, MFA), @@ -158,12 +157,10 @@ trans_optlev_flag(Tool, Options) -> %%------------------------------------------------------------------------------ %% @doc Get switch table and closure table. +-spec get_tables(elf_format:elf()) -> [elf_sym()]. get_tables(Elf) -> - %% Search Symbol Table for an entry with name prefixed with "table_": - Triples = elf_format:get_tab_entries(Elf), - Switches = [T || T={"table_" ++ _, _, _} <- Triples], - Closures = [T || T={"table_closures" ++ _, _, _} <- Switches], - {Switches, Closures}. + %% Search Symbol Table for entries where name is prefixed with "table_": + [S || S=#elf_sym{name="table_" ++ _} <- elf_format:elf_symbols(Elf)]. %% @doc This function associates symbols who point to some table of labels with %% the corresponding offsets of the labels in the code. These tables can @@ -171,14 +168,12 @@ get_tables(Elf) -> %% of blocks that contain closure calls with more than ?NR_ARG_REGS. correlate_labels([], _L) -> {[], []}; correlate_labels(Tables, Labels) -> - %% Sort "Tables" based on "ValueOffsets" - OffsetSortedTb = lists:ukeysort(2, Tables), - %% Unzip offset-sorted list of "Switches" - {Names, _Offsets, TablesSizeList} = lists:unzip3(OffsetSortedTb), - %% Associate switch names with labels - L = split_list(Labels, TablesSizeList), - %% Zip back! (to [{SwitchName, Values}]) - NamesValues = lists:zip(Names, L), + %% Assumes that the relocations are sorted + RelocTree = gb_trees:from_orddict( + [{Rel#elf_rel.offset, Rel#elf_rel.addend} || Rel <- Labels]), + %% Lookup all relocations pertaining to each symbol + NamesValues = [{Name, lookup_range(Value, Value+Size, RelocTree)} + || #elf_sym{name=Name, value=Value, size=Size} <- Tables], case lists:keytake("table_closures", 1, NamesValues) of false -> %% No closures in the code, no closure table {NamesValues, []}; @@ -186,6 +181,17 @@ correlate_labels(Tables, Labels) -> {SwitchesNV, ClosureTableNV} end. +%% Fetches all values with a key in [Low, Hi) +-spec lookup_range(_::K, _::K, gb_trees:tree(K,V)) -> [_::V]. +lookup_range(Low, Hi, Tree) -> + lookup_range_1(Hi, gb_trees:iterator_from(Low, Tree)). + +lookup_range_1(Hi, Iter0) -> + case gb_trees:next(Iter0) of + {Key, Value, Iter} when Key < Hi -> [Value | lookup_range_1(Hi, Iter)]; + _ -> [] + end. + %% @doc Create a gb_tree which contains information about the labels that used %% for switch's jump tables. The keys of the gb_tree are of the form %% {MFA, Label} and the values are the actual Offsets. @@ -216,37 +222,53 @@ insert_to_labelmap([{Key, Value}|Rest], LabelMap) -> %% @doc Correlate object file relocation symbols with info from translation to %% llvm code. fix_relocations(Relocs, RelocsDict, MFA) -> - fix_relocs(Relocs, RelocsDict, MFA, []). - -fix_relocs([], _, _, RelocAcc) -> RelocAcc; -fix_relocs([{Name, Offset}|Rs], RelocsDict, {ModName,_,_}=MFA, RelocAcc) -> + lists:map(fun(Reloc) -> fix_reloc(Reloc, RelocsDict, MFA) end, Relocs). + +%% Relocation types and expected addends for x86 and amd64 +-define(PCREL_T, 'pc32'). +-define(PCREL_A, -4). %% Hard-coded in hipe_x86.c and hipe_amd64.c +-ifdef(BIT32). +-define(ABS_T, '32'). +-define(ABS_A, _). %% We support any addend +-else. +-define(ABS_T, '64'). +-define(ABS_A, 0). +-endif. + +fix_reloc(#elf_rel{symbol=#elf_sym{name=Name, section=undefined, type=notype}, + offset=Offset, type=?PCREL_T, addend=?PCREL_A}, + RelocsDict, {ModName,_,_}) when Name =/= "" -> case dict:fetch(Name, RelocsDict) of - {atom, AtomName} -> - fix_relocs(Rs, RelocsDict, MFA, - [{?LOAD_ATOM, Offset, AtomName}|RelocAcc]); - {constant, Label} -> - fix_relocs(Rs, RelocsDict, MFA, - [{?LOAD_ADDRESS, Offset, {constant, Label}}|RelocAcc]); - {switch, _, JTabLab} -> %% Treat switch exactly as constant - fix_relocs(Rs, RelocsDict, MFA, - [{?LOAD_ADDRESS, Offset, {constant, JTabLab}}|RelocAcc]); - {closure, _}=Closure -> - fix_relocs(Rs, RelocsDict, MFA, - [{?LOAD_ADDRESS, Offset, Closure}|RelocAcc]); - {call, {bif, BifName, _}} -> - fix_relocs(Rs, RelocsDict, MFA, - [{?CALL_LOCAL, Offset, BifName}|RelocAcc]); + {call, {bif, BifName, _}} -> {?CALL_LOCAL, Offset, BifName}; %% MFA calls to functions in the same module are of type 3, while all %% other MFA calls are of type 2. - {call, {ModName,_F,_A}=CallMFA} -> - fix_relocs(Rs, RelocsDict, MFA, - [{?CALL_LOCAL, Offset, CallMFA}|RelocAcc]); - {call, CallMFA} -> - fix_relocs(Rs, RelocsDict, MFA, - [{?CALL_REMOTE, Offset, CallMFA}|RelocAcc]); - Other -> - exit({?MODULE, fix_relocs, - {"Relocation not in relocation dictionary", Other}}) + %% XXX: Does this code break hot code loading (by transforming external + %% calls into local calls?) + {call, {ModName,_F,_A}=CallMFA} -> {?CALL_LOCAL, Offset, CallMFA}; + {call, CallMFA} -> {?CALL_REMOTE, Offset, CallMFA} + end; +fix_reloc(#elf_rel{symbol=#elf_sym{name=Name, section=undefined, type=notype}, + offset=Offset, type=?ABS_T, addend=?ABS_A}, + RelocsDict, _) when Name =/= "" -> + case dict:fetch(Name, RelocsDict) of + {atom, AtomName} -> {?LOAD_ATOM, Offset, AtomName}; + {constant, Label} -> {?LOAD_ADDRESS, Offset, {constant, Label}}; + {closure, _}=Closure -> {?LOAD_ADDRESS, Offset, Closure} + end; +fix_reloc(#elf_rel{symbol=#elf_sym{name=Name, section=#elf_shdr{name=?TEXT}, + type=func}, + offset=Offset, type=?PCREL_T, addend=?PCREL_A}, + RelocsDict, MFA) when Name =/= "" -> + case dict:fetch(Name, RelocsDict) of + {call, MFA} -> {?CALL_LOCAL, Offset, MFA} + end; +fix_reloc(#elf_rel{symbol=#elf_sym{name=Name, section=#elf_shdr{name=?RODATA}, + type=object}, + offset=Offset, type=?ABS_T, addend=?ABS_A}, + RelocsDict, _) when Name =/= "" -> + case dict:fetch(Name, RelocsDict) of + {switch, _, JTabLab} -> %% Treat switch exactly as constant + {?LOAD_ADDRESS, Offset, {constant, JTabLab}} end. %%------------------------------------------------------------------------------ @@ -278,7 +300,7 @@ get_sdescs(Elf) -> Roots/binary>> = NoteGC_bin, LiveRoots = get_liveroots(Roots, []), %% Extract the safe point offsets: - SPOffs = elf_format:get_rela_addends(RelaNoteGC), + SPOffs = [A || #elf_rel{addend=A} <- RelaNoteGC], %% Extract Exception Handler labels: ExnHandlers = elf_format:get_exn_handlers(Elf), %% Combine ExnHandlers and Safe point addresses (return addresses): @@ -476,18 +498,3 @@ unique_folder(FunName, Arity, Options) -> dir_exists(Filename) -> {Flag, Info} = file:read_file_info(Filename), (Flag =:= ok) andalso (element(3, Info) =:= directory). - -%% @doc Function that takes as arguments a list of integers and a list with -%% numbers indicating how many items should each tuple have and splits -%% the original list to a list of lists of integers (with the specified -%% number of elements), i.e. [ [...], [...] ]. --spec split_list([integer()], [integer()]) -> [ [integer()] ]. -split_list(List, ElemsPerTuple) -> - split_list(List, ElemsPerTuple, []). - --spec split_list([integer()], [integer()], [ [integer()] ]) -> [ [integer()] ]. -split_list([], [], Acc) -> - lists:reverse(Acc); -split_list(List, [NumOfElems | MoreNums], Acc) -> - {L1, L2} = lists:split(NumOfElems, List), - split_list(L2, MoreNums, [ L1 | Acc]). -- cgit v1.2.3 From 7814ec18b095d40af95f362ff668a68915982e45 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Wed, 11 May 2016 13:39:53 +0200 Subject: hipe_llvm: Allow LLVM-generated constants Since 3.7, LLVM sometimes generates SSE constants in a special constant section with the requisite alignment (".rodata.cst16"). This broke hipe_llvm since it assumed that all constants that were linked from the text section were constants generated by hipe_llvm. As this is the first time alignments larger than 8 have been required, some small changes were required to hipe_consttab and hipe_bifs:alloc_data/2. Note that hipe_bifs:alloc_data/2 still assumes that erl_alloc will provide the requisite alignment. --- lib/hipe/llvm/elf_format.erl | 7 +++++++ lib/hipe/llvm/hipe_llvm_main.erl | 31 ++++++++++++++++++++++++++++--- lib/hipe/misc/hipe_consttab.erl | 13 ++++++++++++- lib/hipe/misc/hipe_consttab.hrl | 2 +- 4 files changed, 48 insertions(+), 5 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index 4155dff7c4..b3c5ecddab 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -23,6 +23,8 @@ get_exn_handlers/1, %% Symbols elf_symbols/1, + %% Sections + section_contents/2, %% Main interface read/1 ]). @@ -312,6 +314,11 @@ elf_section(?SHN_ABS, #elf{}) -> abs; elf_section(Index, #elf{sec_idx=SecIdx}) when Index =< tuple_size(SecIdx) -> element(Index, SecIdx). +%% Reads the contents of a section from an object +-spec section_contents(elf_shdr(), elf()) -> binary(). +section_contents(#elf_shdr{offset=Offset, size=Size}, #elf{file=ElfBin}) -> + get_binary_segment(ElfBin, Offset, Size). + %%------------------------------------------------------------------------------ %% Functions to manipulate Symbol Table %%------------------------------------------------------------------------------ diff --git a/lib/hipe/llvm/hipe_llvm_main.erl b/lib/hipe/llvm/hipe_llvm_main.erl index 3ab213f94c..476d6fb49c 100644 --- a/lib/hipe/llvm/hipe_llvm_main.erl +++ b/lib/hipe/llvm/hipe_llvm_main.erl @@ -13,7 +13,7 @@ %% chain is invoked in order to produce an object file. rtl_to_native(MFA, RTL, Roots, Options) -> %% Compile to LLVM and get Instruction List (along with infos) - {LLVMCode, RelocsDict, ConstTab} = + {LLVMCode, RelocsDict0, ConstTab0} = hipe_rtl_to_llvm:translate(RTL, Roots), %% Fix function name to an acceptable LLVM identifier (needed for closures) {_Module, Fun, Arity} = hipe_rtl_to_llvm:fix_mfa_name(MFA), @@ -32,10 +32,11 @@ rtl_to_native(MFA, RTL, Roots, Options) -> {SwitchInfos, ExposedClosures} = correlate_labels(Tables, Labels), %% SwitchInfos: [{"table_50", [Labels]}] %% ExposedClosures: [{"table_closures", [Labels]}] - + %% Labelmap contains the offsets of the labels in the code that are %% used for switch's jump tables - LabelMap = create_labelmap(MFA, SwitchInfos, RelocsDict), + LabelMap = create_labelmap(MFA, SwitchInfos, RelocsDict0), + {RelocsDict, ConstTab} = extract_constants(RelocsDict0, ConstTab0, Obj), %% Get relocation info TextRelocs = elf_format:extract_rela(Obj, ?TEXT), %% AccRefs contains the offsets of all references to relocatable symbols in @@ -219,6 +220,25 @@ insert_to_labelmap([{Key, Value}|Rest], LabelMap) -> insert_to_labelmap(Rest, LabelMap) end. +%% Find any LLVM-generated constants and add them to the constant table +extract_constants(RelocsDict0, ConstTab0, Obj) -> + TextRelocs = elf_format:extract_rela(Obj, ?TEXT), + AnonConstSections = + lists:usort([{Sec, Offset} + || #elf_rel{symbol=#elf_sym{type=section, section=Sec}, + addend=Offset} <- TextRelocs]), + lists:foldl( + fun({#elf_shdr{name=Name, type=progbits, addralign=Align, entsize=EntSize, + size=Size} = Section, Offset}, {RelocsDict1, ConstTab1}) + when EntSize > 0, 0 =:= Size rem EntSize, 0 =:= Offset rem EntSize -> + SectionBin = elf_format:section_contents(Section, Obj), + Constant = binary:part(SectionBin, Offset, EntSize), + {ConstTab, ConstLbl} = + hipe_consttab:insert_binary_const(ConstTab1, Align, Constant), + {dict:store({anon, Name, Offset}, {constant, ConstLbl}, RelocsDict1), + ConstTab} + end, {RelocsDict0, ConstTab0}, AnonConstSections). + %% @doc Correlate object file relocation symbols with info from translation to %% llvm code. fix_relocations(Relocs, RelocsDict, MFA) -> @@ -269,6 +289,11 @@ fix_reloc(#elf_rel{symbol=#elf_sym{name=Name, section=#elf_shdr{name=?RODATA}, case dict:fetch(Name, RelocsDict) of {switch, _, JTabLab} -> %% Treat switch exactly as constant {?LOAD_ADDRESS, Offset, {constant, JTabLab}} + end; +fix_reloc(#elf_rel{symbol=#elf_sym{type=section, section=#elf_shdr{name=Name}}, + offset=Offset, type=?ABS_T, addend=Addend}, RelocsDict, _) -> + case dict:fetch({anon, Name, Addend}, RelocsDict) of + {constant, Label} -> {?LOAD_ADDRESS, Offset, {constant, Label}} end. %%------------------------------------------------------------------------------ diff --git a/lib/hipe/misc/hipe_consttab.erl b/lib/hipe/misc/hipe_consttab.erl index f361edc79c..226b20fa46 100644 --- a/lib/hipe/misc/hipe_consttab.erl +++ b/lib/hipe/misc/hipe_consttab.erl @@ -87,7 +87,8 @@ % {NewTab, Lbl} insert_sorted_block/4, insert_block/3, - %% insert_global_word/2, + insert_binary_const/3, + %% insert_global_word/2, %% insert_global_block/4, %% update_word/3, % update_word(ConstTab, Value) -> {NewTab, Lbl} %% update_block/5, @@ -196,6 +197,16 @@ insert_block({ConstTab, RefToLabels, NextLabel}, ElementType, InitList) -> {ElementType,InitList}), {insert_backrefs(NewTa, Id, ReferredLabels), Id}. +%% @doc Inserts a binary constant literal into the const table. +-spec insert_binary_const(hipe_consttab(), ct_alignment(), binary()) -> + {hipe_consttab(), hipe_constlbl()}. +insert_binary_const(ConstTab, Alignment, Binary) + when (Alignment =:= 4 orelse Alignment =:= 8 orelse Alignment =:= 16 + orelse Alignment =:= 32), is_binary(Binary), + size(Binary) rem Alignment =:= 0 -> + insert_const(ConstTab, block, Alignment, false, + {byte, binary_to_list(Binary)}). + %% @spec (ConstTab::hipe_consttab(), ElementType::element_type(), %% InitList::block(), SortOrder) -> {hipe_consttab(), hipe_constlbl()} diff --git a/lib/hipe/misc/hipe_consttab.hrl b/lib/hipe/misc/hipe_consttab.hrl index d2dbbe509c..550da0455c 100644 --- a/lib/hipe/misc/hipe_consttab.hrl +++ b/lib/hipe/misc/hipe_consttab.hrl @@ -20,7 +20,7 @@ %% %%----------------------------------------------------------------------------- --type ct_alignment() :: 4 | 8. +-type ct_alignment() :: 4 | 8 | 16 | 32. -type hipe_constlbl() :: non_neg_integer(). -type hipe_consttab() :: {dict:dict(), [hipe_constlbl()], hipe_constlbl()}. -- cgit v1.2.3 From ea308bc26d4664705895ff3be31687dc5235cc79 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Wed, 11 May 2016 17:25:03 +0200 Subject: hipe_llvm: Disable floats for x86 A bug in LLVM miscompiles x86 functions that have floats are spilled to stack. We work around it by disabling (inlined) floats when using llvm on x86. Once a LLVM version in which the bug is fixed is released, we can make the workaround conditional depending on the version. --- lib/hipe/main/hipe.erl | 24 ++++++++++++++++-------- 1 file changed, 16 insertions(+), 8 deletions(-) (limited to 'lib') diff --git a/lib/hipe/main/hipe.erl b/lib/hipe/main/hipe.erl index 01b7f34b3c..77cf39460a 100644 --- a/lib/hipe/main/hipe.erl +++ b/lib/hipe/main/hipe.erl @@ -1480,18 +1480,25 @@ opt_expansions(TargetArch) -> [{o1, o1_opts(TargetArch)}, {o2, o2_opts(TargetArch)}, {o3, o3_opts(TargetArch)}, - {to_llvm, llvm_opts(o3)}, - {{to_llvm, o0}, llvm_opts(o0)}, - {{to_llvm, o1}, llvm_opts(o1)}, - {{to_llvm, o2}, llvm_opts(o2)}, - {{to_llvm, o3}, llvm_opts(o3)}, + {to_llvm, llvm_opts(o3, TargetArch)}, + {{to_llvm, o0}, llvm_opts(o0, TargetArch)}, + {{to_llvm, o1}, llvm_opts(o1, TargetArch)}, + {{to_llvm, o2}, llvm_opts(o2, TargetArch)}, + {{to_llvm, o3}, llvm_opts(o3, TargetArch)}, {x87, [x87, inline_fp]}, {inline_fp, case TargetArch of %% XXX: Temporary until x86 has sse2 x86 -> [x87, inline_fp]; _ -> [inline_fp] end}]. -llvm_opts(O) -> - [to_llvm, {llvm_opt, O}, {llvm_llc, O}]. +llvm_opts(O, TargetArch) -> + Base = [to_llvm, {llvm_opt, O}, {llvm_llc, O}], + case TargetArch of + %% A llvm bug present in 3.4 through (at least) 3.8 miscompiles x86 + %% functions that have floats are spilled to stack by clobbering the process + %% pointer (ebp) trying to realign the stack pointer. + x86 -> [no_inline_fp | Base]; + _ -> Base + end. %% This expands "basic" options, which may be tested early and cannot be %% in conflict with options found in the source code. @@ -1521,7 +1528,8 @@ expand_options(Opts, TargetArch) -> proplists:normalize(Opts, [{negations, opt_negations()}, {aliases, opt_aliases()}, {expand, opt_basic_expansions()}, - {expand, opt_expansions(TargetArch)}]). + {expand, opt_expansions(TargetArch)}, + {negations, opt_negations()}]). -spec check_options(comp_options()) -> 'ok'. -- cgit v1.2.3 From 8914b835d26cc3b513eaef0a19cd9b39d1d2ccae Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Magnus=20L=C3=A5ng?= Date: Wed, 18 May 2016 18:59:24 +0200 Subject: hipe_llvm: Move elf_format.hrl types to module Named types, except those for the records in the header files, have been moved from elf*_format.hrl to elf_format.erl. Also: * Use lists instead of element/2-indexed tuples for ELF section and symbol tables. * Enable +warn_export_vars for hipe/llvm/ subdirectory and fix warning. * Extract duplicated code in hipe_llvm module into help function pp_dereference_type/3. --- lib/hipe/llvm/Makefile | 8 ++--- lib/hipe/llvm/elf32_format.hrl | 6 ---- lib/hipe/llvm/elf64_format.hrl | 6 ---- lib/hipe/llvm/elf_format.erl | 70 +++++++++++++++++++++++++++----------- lib/hipe/llvm/elf_format.hrl | 66 +++++++++++++++-------------------- lib/hipe/llvm/hipe_llvm.erl | 23 +++++++------ lib/hipe/llvm/hipe_rtl_to_llvm.erl | 23 +++++++------ 7 files changed, 106 insertions(+), 96 deletions(-) (limited to 'lib') diff --git a/lib/hipe/llvm/Makefile b/lib/hipe/llvm/Makefile index d172e37b02..25b47a580f 100644 --- a/lib/hipe/llvm/Makefile +++ b/lib/hipe/llvm/Makefile @@ -40,12 +40,12 @@ RELSYSDIR = $(RELEASE_PATH)/lib/hipe-$(VSN) # Target Specs # ---------------------------------------------------- ifdef HIPE_ENABLED -HIPE_MODULES = hipe_rtl_to_llvm \ +HIPE_MODULES = elf_format \ hipe_llvm \ - elf_format \ + hipe_llvm_liveness \ hipe_llvm_main \ hipe_llvm_merge \ - hipe_llvm_liveness + hipe_rtl_to_llvm else HIPE_MODULES = endif @@ -71,7 +71,7 @@ TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR)) include ../native.mk -ERL_COMPILE_FLAGS += +inline #+warn_missing_spec +ERL_COMPILE_FLAGS += +inline +warn_export_vars #+warn_missing_spec # if in 32 bit backend define BIT32 symbol ARCH = $(shell echo $(TARGET) | sed 's/^\(x86_64\)-.*/64bit/') diff --git a/lib/hipe/llvm/elf32_format.hrl b/lib/hipe/llvm/elf32_format.hrl index 1158cb6434..af1d95bf5b 100644 --- a/lib/hipe/llvm/elf32_format.hrl +++ b/lib/hipe/llvm/elf32_format.hrl @@ -57,9 +57,3 @@ -define(P_MEMSZ_OFFSET, (?P_FILESZ_OFFSET + ?P_FILESZ_SIZE) ). -define(P_FLAGS_OFFSET, (?P_TYPE_OFFSET + ?P_TYPE_SIZE) ). -define(P_ALIGN_OFFSET, (?P_MEMSZ_OFFSET + ?P_MEMSZ_SIZE) ). - -%%------------------------------------------------------------------------------ -%% Exported record and type declarations for 'elf_format' module -%%------------------------------------------------------------------------------ - --type reloc_type() :: '32' | 'pc32'. diff --git a/lib/hipe/llvm/elf64_format.hrl b/lib/hipe/llvm/elf64_format.hrl index 0136e7f381..794746ffdc 100644 --- a/lib/hipe/llvm/elf64_format.hrl +++ b/lib/hipe/llvm/elf64_format.hrl @@ -56,9 +56,3 @@ -define(P_FILESZ_OFFSET, (?P_PVADDR_OFFSET + ?P_PVADDR_SIZE) ). -define(P_MEMSZ_OFFSET, (?P_FILESZ_OFFSET + ?P_FILESZ_SIZE) ). -define(P_ALIGN_OFFSET, (?P_MEMSZ_OFFSET + ?P_MEMSZ_SIZE) ). - -%%------------------------------------------------------------------------------ -%% Exported record and type declarations for 'elf_format' module -%%------------------------------------------------------------------------------ - --type reloc_type() :: '64' | 'pc32' | '32'. diff --git a/lib/hipe/llvm/elf_format.erl b/lib/hipe/llvm/elf_format.erl index b3c5ecddab..8cf6ea6250 100644 --- a/lib/hipe/llvm/elf_format.erl +++ b/lib/hipe/llvm/elf_format.erl @@ -35,25 +35,55 @@ %% Types %%------------------------------------------------------------------------------ --export_type([elf/0]). - --type lp() :: non_neg_integer(). % landing pad --type num() :: non_neg_integer(). --type index() :: non_neg_integer(). --type start() :: non_neg_integer(). - --type tuple(X) :: {} | {X} | {X, X} | tuple(). +-export_type([elf/0 + ,addend/0 + ,bitflags/0 + ,name/0 + ,offset/0 + ,reloc_type/0 + ,shdr_type/0 + ,size/0 + ,sym_bind/0 + ,sym_type/0 + ,valueoff/0 + ]). + +-type bitflags() :: non_neg_integer(). +-type index() :: non_neg_integer(). +-type lp() :: non_neg_integer(). % landing pad +-type num() :: non_neg_integer(). +-type offset() :: non_neg_integer(). +-type size() :: non_neg_integer(). +-type start() :: non_neg_integer(). + +-type addend() :: integer() | undefined. +-type name() :: string(). +-type shdr_type() :: 'null' | 'progbits' | 'symtab' | 'strtab' | 'rela' + | 'hash' | 'dynamic' | 'note' | 'nobits' | 'rel' | 'shlib' + | 'dynsym' | {os, ?SHT_LOOS..?SHT_HIOS} + | {proc, ?SHT_LOPROC..?SHT_HIPROC}. +-type sym_bind() :: 'local' | 'global' | 'weak' | {os, ?STB_LOOS..?STB_HIOS} + | {proc, ?STB_LOPROC..?STB_HIPROC}. +-type sym_type() :: 'notype' | 'object' | 'func' | 'section' | 'file' + | {os, ?STT_LOOS..?STT_HIOS} + | {proc, ?STT_LOPROC..?STT_HIPROC}. +-type valueoff() :: offset(). + +-ifdef(BIT32). % 386 +-type reloc_type() :: '32' | 'pc32'. +-else. % X86_64 +-type reloc_type() :: '64' | 'pc32' | '32'. +-endif. %%------------------------------------------------------------------------------ %% Abstract Data Types and Accessors for ELF Structures. %%------------------------------------------------------------------------------ -record(elf, {file :: binary() - ,sec_idx :: tuple(elf_shdr()) + ,sections :: [elf_shdr()] ,sec_nam :: #{string() => elf_shdr()} - ,sym_idx :: undefined | tuple(elf_sym()) + ,symbols :: undefined | [elf_sym()] }). - -opaque elf() :: #elf{}. %% File header @@ -211,9 +241,9 @@ read(ElfBin) -> [_UndefinedSec|Sections] = extract_shdrtab(ElfBin, Header), SecNam = maps:from_list( [{Name, Sec} || Sec = #elf_shdr{name=Name} <- Sections]), - Elf0 = #elf{file=ElfBin, sec_idx=list_to_tuple(Sections), sec_nam=SecNam}, + Elf0 = #elf{file=ElfBin, sections=Sections, sec_nam=SecNam}, [_UndefinedSym|Symbols] = extract_symtab(Elf0, extract_strtab(Elf0)), - Elf0#elf{sym_idx=list_to_tuple(Symbols)}. + Elf0#elf{symbols=Symbols}. %%------------------------------------------------------------------------------ %% Functions to manipulate the ELF File Header @@ -311,8 +341,8 @@ decode_shdr_type(Proc) when ?SHT_LOPROC =< Proc, Proc =< ?SHT_HIPROC -> -spec elf_section(non_neg_integer(), elf()) -> undefined | abs | elf_shdr(). elf_section(0, #elf{}) -> undefined; elf_section(?SHN_ABS, #elf{}) -> abs; -elf_section(Index, #elf{sec_idx=SecIdx}) when Index =< tuple_size(SecIdx) -> - element(Index, SecIdx). +elf_section(Index, #elf{sections=SecIdx}) -> + lists:nth(Index, SecIdx). %% Reads the contents of a section from an object -spec section_contents(elf_shdr(), elf()) -> binary(). @@ -374,10 +404,10 @@ decode_symbol_type(Proc) when ?STT_LOPROC =< Proc, Proc =< ?STT_HIPROC -> -spec elf_symbol(0, elf()) -> undefined; (pos_integer(), elf()) -> elf_sym(). elf_symbol(0, #elf{}) -> undefined; -elf_symbol(Index, #elf{sym_idx=SymIdx}) -> element(Index, SymIdx). +elf_symbol(Index, #elf{symbols=Symbols}) -> lists:nth(Index, Symbols). -spec elf_symbols(elf()) -> [elf_sym()]. -elf_symbols(#elf{sym_idx=SymIdx}) -> tuple_to_list(SymIdx). +elf_symbols(#elf{symbols=Symbols}) -> Symbols. %%------------------------------------------------------------------------------ %% Functions to manipulate String Table @@ -418,8 +448,8 @@ bin_get_string(<>) -> [Char|bin_get_string(Rest)]. extract_rela(Elf, Name) -> SecData = extract_segment_by_name(Elf, Name), [#elf_rel{offset=Offset, symbol=elf_symbol(?ELF_R_SYM(Info), Elf), - type=decode_reloc_type(?ELF_R_TYPE(Info)), - addend=read_implicit_addend(Offset, SecData)} + type=decode_reloc_type(?ELF_R_TYPE(Info)), + addend=read_implicit_addend(Offset, SecData)} || <> <= extract_segment_by_name(Elf, ?REL(Name))]. @@ -436,7 +466,7 @@ read_implicit_addend(Offset, Section) -> -else. %% BIT32 extract_rela(Elf, Name) -> [#elf_rel{offset=Offset, symbol=elf_symbol(?ELF_R_SYM(Info), Elf), - type=decode_reloc_type(?ELF_R_TYPE(Info)), addend=Addend} + type=decode_reloc_type(?ELF_R_TYPE(Info)), addend=Addend} || < true -> write(Dev, "volatile "); false -> ok end, - case Ver >= {3,7} of false -> ok; true -> - pp_type(Dev, pointer_type(load_p_type(I))), - write(Dev, ", ") - end, - pp_type(Dev, load_p_type(I)), + pp_dereference_type(Dev, Ver, load_p_type(I)), write(Dev, [" ", load_pointer(I), " "]), case load_alignment(I) of [] -> ok; @@ -905,11 +901,7 @@ pp_ins(Dev, Ver, I) -> true -> write(Dev, "inbounds "); false -> ok end, - case Ver >= {3,7} of false -> ok; true -> - pp_type(Dev, pointer_type(getelementptr_p_type(I))), - write(Dev, ", ") - end, - pp_type(Dev, getelementptr_p_type(I)), + pp_dereference_type(Dev, Ver, getelementptr_p_type(I)), write(Dev, [" ", getelementptr_value(I)]), pp_typed_idxs(Dev, getelementptr_typed_idxs(I)), write(Dev, "\n"); @@ -1032,6 +1024,17 @@ pp_ins(Dev, Ver, I) -> exit({?MODULE, pp_ins, {"Unknown LLVM instruction", Other}}) end. +%% @doc Print the type of a dereference in an LLVM instruction using syntax +%% parsable by the specified LLVM version. +pp_dereference_type(Dev, Ver, Type) -> + case Ver >= {3,7} of + false -> ok; + true -> + pp_type(Dev, pointer_type(Type)), + write(Dev, ", ") + end, + pp_type(Dev, Type). + %% @doc Pretty-print a list of types pp_type_list(_Dev, []) -> ok; pp_type_list(Dev, [T]) -> diff --git a/lib/hipe/llvm/hipe_rtl_to_llvm.erl b/lib/hipe/llvm/hipe_rtl_to_llvm.erl index d7d8d1b049..b23d756d6c 100644 --- a/lib/hipe/llvm/hipe_rtl_to_llvm.erl +++ b/lib/hipe/llvm/hipe_rtl_to_llvm.erl @@ -266,17 +266,18 @@ trans_alub_overflow(I, Sign, Relocs) -> T2 = mk_temp(), %% T1{1}: Boolean variable indicating overflow I6 = hipe_llvm:mk_extractvalue(T2, ReturnType, T1, "1", []), - case hipe_rtl:alub_cond(I) of - Op when Op =:= overflow orelse Op =:= ltu -> - True_label = mk_jump_label(hipe_rtl:alub_true_label(I)), - False_label = mk_jump_label(hipe_rtl:alub_false_label(I)), - MetaData = branch_metadata(hipe_rtl:alub_pred(I)); - not_overflow -> - True_label = mk_jump_label(hipe_rtl:alub_false_label(I)), - False_label = mk_jump_label(hipe_rtl:alub_true_label(I)), - MetaData = branch_metadata(1 - hipe_rtl:alub_pred(I)) - end, - I7 = hipe_llvm:mk_br_cond(T2, True_label, False_label, MetaData), + {TrueLabel, FalseLabel, MetaData} = + case hipe_rtl:alub_cond(I) of + Op when Op =:= overflow orelse Op =:= ltu -> + {mk_jump_label(hipe_rtl:alub_true_label(I)), + mk_jump_label(hipe_rtl:alub_false_label(I)), + branch_metadata(hipe_rtl:alub_pred(I))}; + not_overflow -> + {mk_jump_label(hipe_rtl:alub_false_label(I)), + mk_jump_label(hipe_rtl:alub_true_label(I)), + branch_metadata(1 - hipe_rtl:alub_pred(I))} + end, + I7 = hipe_llvm:mk_br_cond(T2, TrueLabel, FalseLabel, MetaData), {[I7, I6, I5, I4, I3, I2, I1], NewRelocs}. trans_alub_op(I, Sign) -> -- cgit v1.2.3