Skip to content

Commit

Permalink
Added abstraction for LLVM insertvalue instruction
Browse files Browse the repository at this point in the history
  • Loading branch information
Chris Stavrakakis authored and yiannist committed Mar 5, 2014
1 parent 19ab54d commit 9bdd55b
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 0 deletions.
28 changes: 28 additions & 0 deletions lib/hipe/llvm/hipe_llvm.erl
Expand Up @@ -168,6 +168,15 @@
extractvalue_idx/1,
extractvalue_idxs/1,

mk_insertvalue/7,
insertvalue_dst/1,
insertvalue_val_type/1,
insertvalue_val/1,
insertvalue_elem_type/1,
insertvalue_elem/1,
insertvalue_idx/1,
insertvalue_idxs/1,

mk_alloca/4,
alloca_dst/1,
alloca_type/1,
Expand Down Expand Up @@ -605,6 +614,20 @@ extractvalue_val(#llvm_extractvalue{val=Val})-> Val.
extractvalue_idx(#llvm_extractvalue{idx=Idx})-> Idx.
extractvalue_idxs(#llvm_extractvalue{idxs=Idxs})-> Idxs.

%%
%% insertvalue
%%
mk_insertvalue(Dst, Val_type, Val, Elem_type, Elem, Idx, Idxs) ->
#llvm_insertvalue{dst=Dst, val_type=Val_type, val=Val, elem_type=Elem_type,
elem=Elem, idx=Idx, idxs=Idxs}.
insertvalue_dst(#llvm_insertvalue{dst=Dst}) -> Dst.
insertvalue_val_type(#llvm_insertvalue{val_type=Val_type}) -> Val_type.
insertvalue_val(#llvm_insertvalue{val=Val}) -> Val.
insertvalue_elem_type(#llvm_insertvalue{elem_type=Elem_type}) -> Elem_type.
insertvalue_elem(#llvm_insertvalue{elem=Elem}) -> Elem.
insertvalue_idx(#llvm_insertvalue{idx=Idx}) -> Idx.
insertvalue_idxs(#llvm_insertvalue{idxs=Idxs}) -> Idxs.

%%
%% alloca
%%
Expand Down Expand Up @@ -912,6 +935,11 @@ pp_ins(Dev, I) ->
%%TODO Print idxs
[extractvalue_dst(I), extractvalue_type(I), extractvalue_val(I),
extractvalue_idx(I)]);
#llvm_insertvalue{} ->
io:format(Dev, "~s = insertvalue ~s ~s, ~s ~s, ~s~n",
%%TODO Print idxs
[insertvalue_dst(I), insertvalue_val_type(I), insertvalue_val(I),
insertvalue_elem_type(I), insertvalue_elem(I), insertvalue_idx(I)]);
#llvm_alloca{} ->
io:format(Dev, "~s = alloca ~s ", [alloca_dst(I), alloca_type(I)]),
case alloca_num(I) of
Expand Down
1 change: 1 addition & 0 deletions lib/hipe/llvm/hipe_llvm.hrl
Expand Up @@ -38,6 +38,7 @@
%-record(llvm_xor, {dst, type, src1, src2}).
%% 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 = [],
Expand Down

0 comments on commit 9bdd55b

Please sign in to comment.