Skip to content

Commit

Permalink
Add 'inbounds' as default in getelementptr and fix whitespace/comments
Browse files Browse the repository at this point in the history
  • Loading branch information
yiannist committed Mar 5, 2014
1 parent 5e4828e commit c48d125
Show file tree
Hide file tree
Showing 3 changed files with 103 additions and 97 deletions.
8 changes: 4 additions & 4 deletions lib/hipe/llvm/hipe_llvm.erl
Expand Up @@ -381,8 +381,8 @@ store_volatile(#llvm_store{volatile=Volatile}) -> Volatile.
%% getelementptr
%%
mk_getelementptr(Dst, P_Type, Value, Typed_Idxs, Inbounds) ->
#llvm_getelementptr{dst=Dst,p_type=P_Type, value=Value, typed_idxs=Typed_Idxs,
inbounds=Inbounds}.
#llvm_getelementptr{dst=Dst,p_type=P_Type, value=Value,
typed_idxs=Typed_Idxs, inbounds=Inbounds}.
getelementptr_dst(#llvm_getelementptr{dst=Dst}) -> Dst.
getelementptr_p_type(#llvm_getelementptr{p_type=P_Type}) -> P_Type.
getelementptr_value(#llvm_getelementptr{value=Value}) -> Value.
Expand Down Expand Up @@ -493,7 +493,7 @@ call_fn_attrs(#llvm_call{fn_attrs=Fn_attrs}) -> Fn_attrs.
%% fun_def
%%
mk_fun_def(Linkage, Visibility, Cconv, Ret_attrs, Type, Name, Arglist,
Fn_attrs, Align, Body) ->
Fn_attrs, Align, Body) ->
#llvm_fun_def{
linkage=Linkage,
visibility=Visibility,
Expand Down Expand Up @@ -654,7 +654,7 @@ pp_ins(Dev, I) ->
invoke_unwind_label(I), " \n"]);
#llvm_br_cond{} ->
write(Dev, ["br i1 ", br_cond_cond(I), ", label ", br_cond_true_label(I),
", label ", br_cond_false_label(I)]),
", label ", br_cond_false_label(I)]),
case br_cond_meta(I) of
[] -> ok;
Metadata ->
Expand Down
24 changes: 13 additions & 11 deletions lib/hipe/llvm/hipe_llvm.hrl
@@ -1,12 +1,10 @@
%% -*- erlang-indent-level: 2 -*-

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
%% Provides abstract datatypes for LLVM Assembly.
%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%%---------------------------------------------------------------------
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%% Terminator Instructions
-record(llvm_ret, {ret_list=[]}).
Expand All @@ -15,19 +13,23 @@
-record(llvm_indirectbr, {type, address, label_list}).
-record(llvm_switch, {type, value, default_label, value_label_list=[]}).
-record(llvm_invoke, {dst, cconv=[], ret_attrs=[], type, fnptrval, arglist=[],
fn_attrs=[], to_label, unwind_label}).
fn_attrs=[], to_label, unwind_label}).

%% Binary Operations
-record(llvm_operation, {dst, op, type, src1, src2, options=[]}).

%% Aggregate Operations
-record(llvm_extractvalue, {dst, type, val, idx, idxs=[]}).
-record(llvm_insertvalue, {dst, val_type, val, elem_type, elem, idx, idxs=[]}).

%% Memory Access And Addressing Operations
-record(llvm_alloca, {dst, type, num = [], align = []}).
-record(llvm_load, {dst, p_type, pointer, alignment = [], nontemporal = [],
volatile = false}).
-record(llvm_store, {type, value, p_type, pointer, alignment = [], nontemporal = [],
volatile = false}).
-record(llvm_getelementptr, {dst, p_type, value, typed_idxs = [], inbounds = false}).
-record(llvm_alloca, {dst, type, num=[], align=[]}).
-record(llvm_load, {dst, p_type, pointer, alignment=[], nontemporal=[],
volatile=false}).
-record(llvm_store, {type, value, p_type, pointer, alignment=[],
nontemporal=[], volatile=false}).
-record(llvm_getelementptr, {dst, p_type, value, typed_idxs, inbounds}).

%% Conversion Operations
-record(llvm_conversion, {dst, op, src_type, src, dst_type}).
-record(llvm_sitofp, {dst, src_type, src, dst_type}).
Expand Down

0 comments on commit c48d125

Please sign in to comment.