Skip to content

Commit

Permalink
Merge branch 'yiannist/hipe-llvm-backend'
Browse files Browse the repository at this point in the history
* yiannist/hipe-llvm-backend:
  Support the LLVM backend in HiPE
  Implement the LLVM backend
  Extend RTL API to support the LLVM backend
  Add support for llvm unique symbols in hipe_gensym
  Add a BIF that only returns the atom ok
  Move some common code in hipe_pack_constants
  Add better specs in hipe_pack_constants and cleanup

OTP-11801
  • Loading branch information
proxyles committed Mar 21, 2014
2 parents bbe92ec + b326df0 commit 9d46875
Show file tree
Hide file tree
Showing 27 changed files with 5,365 additions and 232 deletions.
7 changes: 7 additions & 0 deletions erts/emulator/hipe/hipe_bif2.c
Expand Up @@ -182,3 +182,10 @@ BIF_RETTYPE hipe_bifs_debug_native_called_2(BIF_ALIST_2)
BIF_RET(am_ok);
}

/* Stub-BIF for LLVM:
* Reloads BP, SP (in llvm unwind label) */

BIF_RETTYPE hipe_bifs_llvm_fix_pinned_regs_0(BIF_ALIST_0)
{
BIF_RET(am_ok);
}
1 change: 1 addition & 0 deletions erts/emulator/hipe/hipe_bif2.tab
Expand Up @@ -30,3 +30,4 @@ bif hipe_bifs:in_native/0
bif hipe_bifs:modeswitch_debug_on/0
bif hipe_bifs:modeswitch_debug_off/0
bif hipe_bifs:debug_native_called/2
bif hipe_bifs:llvm_fix_pinned_regs/0
2 changes: 1 addition & 1 deletion lib/hipe/Makefile
Expand Up @@ -22,7 +22,7 @@ include $(ERL_TOP)/make/target.mk
include $(ERL_TOP)/make/$(TARGET)/otp.mk

ifdef HIPE_ENABLED
HIPE_SUBDIRS = regalloc sparc ppc x86 amd64 arm opt tools
HIPE_SUBDIRS = regalloc sparc ppc x86 amd64 arm opt tools llvm
else
HIPE_SUBDIRS =
endif
Expand Down
48 changes: 3 additions & 45 deletions lib/hipe/arm/hipe_arm_assemble.erl
Expand Up @@ -44,8 +44,8 @@ assemble(CompiledCode, Closures, Exports, Options) ->
print("Total num bytes=~w\n", [CodeSize], Options),
%%
SC = hipe_pack_constants:slim_constmap(ConstMap),
DataRelocs = mk_data_relocs(RefsFromConsts, LabelMap),
SSE = slim_sorted_exportmap(ExportMap,Closures,Exports),
DataRelocs = hipe_pack_constants:mk_data_relocs(RefsFromConsts, LabelMap),
SSE = hipe_pack_constants:slim_sorted_exportmap(ExportMap,Closures,Exports),
SlimRefs = hipe_pack_constants:slim_refs(AccRefs),
Bin = term_to_binary([{?VERSION_STRING(),?HIPE_SYSTEM_CRC},
ConstAlign, ConstSize,
Expand Down Expand Up @@ -320,7 +320,7 @@ do_pseudo_li(I, MFA, ConstMap, Address, PrevImms, PendImms) ->
Atom when is_atom(Atom) ->
{load_atom, Atom};
{Label,constant} ->
ConstNo = find_const({MFA,Label}, ConstMap),
ConstNo = hipe_pack_constants:find_const({MFA,Label}, ConstMap),
{load_address, {constant,ConstNo}};
{Label,closure} ->
{load_address, {closure,Label}};
Expand Down Expand Up @@ -518,37 +518,6 @@ fix_pc_refs(I, InsnAddress, FunAddress, LabelMap) ->

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

mk_data_relocs(RefsFromConsts, LabelMap) ->
lists:flatten(mk_data_relocs(RefsFromConsts, LabelMap, [])).

mk_data_relocs([{MFA,Labels} | Rest], LabelMap, Acc) ->
Map = [case Label of
{L,Pos} ->
Offset = find({MFA,L}, LabelMap),
{Pos,Offset};
{sorted,Base,OrderedLabels} ->
{sorted, Base, [begin
Offset = find({MFA,L}, LabelMap),
{Order, Offset}
end
|| {L,Order} <- OrderedLabels]}
end
|| Label <- Labels],
%% msg("Map: ~w Map\n",[Map]),
mk_data_relocs(Rest, LabelMap, [Map,Acc]);
mk_data_relocs([],_,Acc) -> Acc.

find({_MFA,_L} = MFAL, LabelMap) ->
gb_trees:get(MFAL, LabelMap).

slim_sorted_exportmap([{Addr,M,F,A}|Rest], Closures, Exports) ->
IsClosure = lists:member({M,F,A}, Closures),
IsExported = is_exported(F, A, Exports),
[Addr,M,F,A,IsClosure,IsExported | slim_sorted_exportmap(Rest, Closures, Exports)];
slim_sorted_exportmap([],_,_) -> [].

is_exported(F, A, Exports) -> lists:member({F,A}, Exports).

%%%
%%% Assembly listing support (pp_asm option).
%%%
Expand Down Expand Up @@ -594,17 +563,6 @@ fill_spaces(N) when N > 0 ->
fill_spaces(0) ->
[].

%%%
%%% Lookup a constant in a ConstMap.
%%%

find_const({MFA,Label},[{pcm_entry,MFA,Label,ConstNo,_,_,_}|_]) ->
ConstNo;
find_const(N,[_|R]) ->
find_const(N,R);
find_const(C,[]) ->
?EXIT({constant_not_found,C}).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%%%
Expand Down
109 changes: 109 additions & 0 deletions lib/hipe/llvm/Makefile
@@ -0,0 +1,109 @@
#
# %CopyrightBegin%
#
# Copyright Ericsson AB 2001-2014. All Rights Reserved.
#
# The contents of this file are subject to the Erlang Public License,
# Version 1.1, (the "License"); you may not use this file except in
# compliance with the License. You should have received a copy of the
# Erlang Public License along with this software. If not, it can be
# retrieved online at http://www.erlang.org/.
#
# Software distributed under the License is distributed on an "AS IS"
# basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
# the License for the specific language governing rights and limitations
# under the License.
#
# %CopyrightEnd%
#

ifndef EBIN
EBIN = ../ebin
endif

include $(ERL_TOP)/make/target.mk
include $(ERL_TOP)/make/$(TARGET)/otp.mk

# ----------------------------------------------------
# Application version
# ----------------------------------------------------
include ../vsn.mk
VSN=$(HIPE_VSN)

# ----------------------------------------------------
# Release directory specification
# ----------------------------------------------------
RELSYSDIR = $(RELEASE_PATH)/lib/hipe-$(VSN)

# ----------------------------------------------------
# Target Specs
# ----------------------------------------------------
ifdef HIPE_ENABLED
HIPE_MODULES = hipe_rtl_to_llvm \
hipe_llvm \
elf_format \
hipe_llvm_main \
hipe_llvm_merge \
hipe_llvm_liveness
else
HIPE_MODULES =
endif

MODULES = $(HIPE_MODULES)

HRL_FILES= elf_format.hrl elf32_format.hrl elf64_format.hrl \
hipe_llvm_arch.hrl
ERL_FILES= $(MODULES:%=%.erl)
TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))

# APP_FILE=
# App_SRC= $(APP_FILE).src
# APP_TARGET= $(EBIN)/$(APP_FILE)
#
# APPUP_FILE=
# APPUP_SRC= $(APPUP_FILE).src
# APPUP_TARGET= $(EBIN)/$(APPUP_FILE)

# ----------------------------------------------------
# FLAGS: Please keep +inline below
# ----------------------------------------------------

include ../native.mk

ERL_COMPILE_FLAGS += +inline #+warn_missing_spec

# if in 32 bit backend define BIT32 symbol
ARCH = $(shell echo $(TARGET) | sed 's/^\(x86_64\)-.*/64bit/')
ifneq ($(ARCH), 64bit)
ERL_COMPILE_FLAGS += -DBIT32
endif

# ----------------------------------------------------
# Targets
# ----------------------------------------------------

debug opt: $(TARGET_FILES)

docs:

clean:
rm -f $(TARGET_FILES)
rm -f core erl_crash.dump

# ----------------------------------------------------
# Special Build Targets
# ----------------------------------------------------


# ----------------------------------------------------
# Release Target
# ----------------------------------------------------
include $(ERL_TOP)/make/otp_release_targets.mk

release_spec: opt
$(INSTALL_DIR) $(RELSYSDIR)/llvm
$(INSTALL_DATA) $(ERL_FILES) $(HRL_FILES) $(RELSYSDIR)/llvm
$(INSTALL_DIR) $(RELSYSDIR)/ebin
$(INSTALL_DATA) $(TARGET_FILES) $(RELSYSDIR)/ebin

release_docs_spec:
59 changes: 59 additions & 0 deletions lib/hipe/llvm/elf32_format.hrl
@@ -0,0 +1,59 @@
%% -*- erlang-indent-level: 2 -*-

%%% @copyright 2011-2014 Yiannis Tsiouris <gtsiour@softlab.ntua.gr>,
%%% Chris Stavrakakis <hydralisk.r@gmail.com>
%%% @author Yiannis Tsiouris <gtsiour@softlab.ntua.gr>
%%% [http://www.softlab.ntua.gr/~gtsiour/]

%%% @doc This header file contains very very useful macros for handling
%%% various segments of an ELF-32 formated object file, such as sizes,
%%% offsets and predefined constants. For further information about
%%% each field take a quick look at
%%% "[http://www.sco.com/developers/gabi/latest/contents.html]"
%%% that contain the current HP/Intel definition of the ELF object
%%% file format.

%%------------------------------------------------------------------------------
%% ELF-32 Data Types (in bytes)
%%------------------------------------------------------------------------------
-define(ELF_ADDR_SIZE, 4).
-define(ELF_OFF_SIZE, 4).
-define(ELF_HALF_SIZE, 2).
-define(ELF_WORD_SIZE, 4).
-define(ELF_SWORD_SIZE, 4).
-define(ELF_XWORD_SIZE, ?ELF_WORD_SIZE). % for compatibility
-define(ELF_SXWORD_SIZE, ?ELF_WORD_SIZE).
-define(ELF_UNSIGNED_CHAR_SIZE, 1).

%%------------------------------------------------------------------------------
%% ELF-32 Symbol Table Entries
%%------------------------------------------------------------------------------
%% Precomputed offset for Symbol Table entries in SymTab binary (needed because
%% of the different offsets in 32 and 64 bit formats).
-define(ST_NAME_OFFSET, 0).
-define(ST_VALUE_OFFSET, (?ST_NAME_OFFSET + ?ST_NAME_SIZE) ).
-define(ST_SIZE_OFFSET, (?ST_VALUE_OFFSET + ?ST_VALUE_SIZE) ).
-define(ST_INFO_OFFSET, (?ST_SIZE_OFFSET + ?ST_SIZE_SIZE) ).
-define(ST_OTHER_OFFSET, (?ST_INFO_OFFSET + ?ST_INFO_SIZE) ).
-define(ST_SHNDX_OFFSET, (?ST_OTHER_OFFSET + ?ST_OTHER_SIZE) ).

%%------------------------------------------------------------------------------
%% ELF-64 Relocation Entries
%%------------------------------------------------------------------------------
%% Useful macros to extract information from r_info field
-define(ELF_R_SYM(I), (I bsr 8) ).
-define(ELF_R_TYPE(I), (I band 16#ff) ).
-define(ELF_R_INFO(S, T), ((S bsl 8) + (T band 16#ff)) ).

%%------------------------------------------------------------------------------
%% ELF-64 Program Header Table
%%------------------------------------------------------------------------------
%% Offsets of various fields in a Program Header Table entry binary.
-define(P_TYPE_OFFSET, 0).
-define(P_OFFSET_OFFSET, (?P_FLAGS_OFFSET + ?P_FLAGS_SIZE) ).
-define(P_VADDR_OFFSET, (?P_OFFSET_OFFSET + ?P_OFFSET_SIZE) ).
-define(P_PADDR_OFFSET, (?P_VADDR_OFFSET + ?P_VADDR_SIZE) ).
-define(P_FILESZ_OFFSET, (?P_PVADDR_OFFSET + ?P_PVADDR_SIZE) ).
-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) ).
58 changes: 58 additions & 0 deletions lib/hipe/llvm/elf64_format.hrl
@@ -0,0 +1,58 @@
%% -*- erlang-indent-level: 2 -*-

%%% @copyright 2011-2014 Yiannis Tsiouris <gtsiour@softlab.ntua.gr>,
%%% Chris Stavrakakis <hydralisk.r@gmail.com>
%%% @author Yiannis Tsiouris <gtsiour@softlab.ntua.gr>
%%% [http://www.softlab.ntua.gr/~gtsiour/]

%%% @doc This header file contains very very useful macros for handling
%%% various segments of an ELF-64 formated object file, such as sizes,
%%% offsets and predefined constants. For further information about
%%% each field take a quick look at
%%% "[http://downloads.openwatcom.org/ftp/devel/docs/elf-64-gen.pdf]"
%%% that contain the current HP/Intel definition of the ELF object
%%% file format.

%%------------------------------------------------------------------------------
%% ELF-64 Data Types (in bytes)
%%------------------------------------------------------------------------------
-define(ELF_ADDR_SIZE, 8).
-define(ELF_OFF_SIZE, 8).
-define(ELF_HALF_SIZE, 2).
-define(ELF_WORD_SIZE, 4).
-define(ELF_SWORD_SIZE, 4).
-define(ELF_XWORD_SIZE, 8).
-define(ELF_SXWORD_SIZE, 8).
-define(ELF_UNSIGNED_CHAR_SIZE, 1).

%%------------------------------------------------------------------------------
%% ELF-64 Symbol Table Entries
%%------------------------------------------------------------------------------
%% Precomputed offset for Symbol Table entries in SymTab binary
-define(ST_NAME_OFFSET, 0).
-define(ST_INFO_OFFSET, (?ST_NAME_OFFSET + ?ST_NAME_SIZE) ).
-define(ST_OTHER_OFFSET, (?ST_INFO_OFFSET + ?ST_INFO_SIZE) ).
-define(ST_SHNDX_OFFSET, (?ST_OTHER_OFFSET + ?ST_OTHER_SIZE) ).
-define(ST_VALUE_OFFSET, (?ST_SHNDX_OFFSET + ?ST_SHNDX_SIZE) ).
-define(ST_SIZE_OFFSET, (?ST_VALUE_OFFSET + ?ST_VALUE_SIZE) ).

%%------------------------------------------------------------------------------
%% ELF-64 Relocation Entries
%%------------------------------------------------------------------------------
%% Useful macros to extract information from r_info field
-define(ELF_R_SYM(I), (I bsr 32) ).
-define(ELF_R_TYPE(I), (I band 16#ffffffff) ).
-define(ELF_R_INFO(S, T), ((S bsl 32) + (T band 16#ffffffff)) ).

%%------------------------------------------------------------------------------
%% ELF-64 Program Header Table
%%------------------------------------------------------------------------------
%% Offsets of various fields in a Program Header Table entry binary.
-define(P_TYPE_OFFSET, 0).
-define(P_FLAGS_OFFSET, (?P_TYPE_OFFSET + ?P_TYPE_SIZE) ).
-define(P_OFFSET_OFFSET, (?P_FLAGS_OFFSET + ?P_FLAGS_SIZE) ).
-define(P_VADDR_OFFSET, (?P_OFFSET_OFFSET + ?P_OFFSET_SIZE) ).
-define(P_PADDR_OFFSET, (?P_VADDR_OFFSET + ?P_VADDR_SIZE) ).
-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) ).

0 comments on commit 9d46875

Please sign in to comment.