aboutsummaryrefslogtreecommitdiffstats
path: root/bindings/ocaml/transforms
diff options
context:
space:
mode:
authorStephen Hines <srhines@google.com>2014-02-11 20:01:10 -0800
committerStephen Hines <srhines@google.com>2014-02-11 20:01:10 -0800
commitce9904c6ea8fd669978a8eefb854b330eb9828ff (patch)
tree2418ee2e96ea220977c8fb74959192036ab5b133 /bindings/ocaml/transforms
parentc27b10b198c1d9e9b51f2303994313ec2778edd7 (diff)
parentdbb832b83351cec97b025b61c26536ef50c3181c (diff)
downloadexternal_llvm-ce9904c6ea8fd669978a8eefb854b330eb9828ff.zip
external_llvm-ce9904c6ea8fd669978a8eefb854b330eb9828ff.tar.gz
external_llvm-ce9904c6ea8fd669978a8eefb854b330eb9828ff.tar.bz2
Merge remote-tracking branch 'upstream/release_34' into merge-20140211
Conflicts: lib/Linker/LinkModules.cpp lib/Support/Unix/Signals.inc Change-Id: Ia54f291fa5dc828052d2412736e8495c1282aa64
Diffstat (limited to 'bindings/ocaml/transforms')
-rw-r--r--bindings/ocaml/transforms/Makefile2
-rw-r--r--bindings/ocaml/transforms/ipo/Makefile1
-rw-r--r--bindings/ocaml/transforms/ipo/ipo_ocaml.c10
-rw-r--r--bindings/ocaml/transforms/ipo/llvm_ipo.ml34
-rw-r--r--bindings/ocaml/transforms/ipo/llvm_ipo.mli10
-rw-r--r--bindings/ocaml/transforms/passmgr_builder/Makefile19
-rw-r--r--bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.ml32
-rw-r--r--bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.mli54
-rw-r--r--bindings/ocaml/transforms/passmgr_builder/passmgr_builder_ocaml.c113
-rw-r--r--bindings/ocaml/transforms/scalar/Makefile1
-rw-r--r--bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml5
-rw-r--r--bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli8
-rw-r--r--bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c10
-rw-r--r--bindings/ocaml/transforms/vectorize/Makefile19
-rw-r--r--bindings/ocaml/transforms/vectorize/llvm_vectorize.ml15
-rw-r--r--bindings/ocaml/transforms/vectorize/llvm_vectorize.mli25
-rw-r--r--bindings/ocaml/transforms/vectorize/vectorize_ocaml.c38
17 files changed, 352 insertions, 44 deletions
diff --git a/bindings/ocaml/transforms/Makefile b/bindings/ocaml/transforms/Makefile
index 05fcd90..92c8396 100644
--- a/bindings/ocaml/transforms/Makefile
+++ b/bindings/ocaml/transforms/Makefile
@@ -8,7 +8,7 @@
##===----------------------------------------------------------------------===##
LEVEL := ../../..
-DIRS = scalar ipo
+DIRS = scalar ipo vectorize passmgr_builder
ocamldoc:
$(Verb) for i in $(DIRS) ; do \
diff --git a/bindings/ocaml/transforms/ipo/Makefile b/bindings/ocaml/transforms/ipo/Makefile
index 130d74c..ed67a7c 100644
--- a/bindings/ocaml/transforms/ipo/Makefile
+++ b/bindings/ocaml/transforms/ipo/Makefile
@@ -13,7 +13,6 @@
LEVEL := ../../../..
LIBRARYNAME := llvm_ipo
-DONT_BUILD_RELINKED := 1
UsedComponents := ipo
UsedOcamlInterfaces := llvm
diff --git a/bindings/ocaml/transforms/ipo/ipo_ocaml.c b/bindings/ocaml/transforms/ipo/ipo_ocaml.c
index 612015c..4ad8afb 100644
--- a/bindings/ocaml/transforms/ipo/ipo_ocaml.c
+++ b/bindings/ocaml/transforms/ipo/ipo_ocaml.c
@@ -1,4 +1,4 @@
-/*===-- ipo_ocaml.c - LLVM Ocaml Glue -------------------*- C++ -*-===*\
+/*===-- ipo_ocaml.c - LLVM OCaml Glue ---------------------------*- C++ -*-===*\
|* *|
|* The LLVM Compiler Infrastructure *|
|* *|
@@ -7,7 +7,7 @@
|* *|
|*===----------------------------------------------------------------------===*|
|* *|
-|* This file glues LLVM's ocaml interface to its C interface. These functions *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
|* are by and large transparent wrappers to the corresponding C functions. *|
|* *|
|* Note that these functions intentionally take liberties with the CAMLparamX *|
@@ -50,6 +50,12 @@ CAMLprim value llvm_add_function_inlining(LLVMPassManagerRef PM) {
}
/* [`Module] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_always_inliner(LLVMPassManagerRef PM) {
+ LLVMAddAlwaysInlinerPass(PM);
+ return Val_unit;
+}
+
+/* [`Module] Llvm.PassManager.t -> unit */
CAMLprim value llvm_add_always_inliner_pass(LLVMPassManagerRef PM) {
LLVMAddAlwaysInlinerPass(PM);
return Val_unit;
diff --git a/bindings/ocaml/transforms/ipo/llvm_ipo.ml b/bindings/ocaml/transforms/ipo/llvm_ipo.ml
index 1562d10..93f564a 100644
--- a/bindings/ocaml/transforms/ipo/llvm_ipo.ml
+++ b/bindings/ocaml/transforms/ipo/llvm_ipo.ml
@@ -1,4 +1,4 @@
-(*===-- llvm_ipo.mli - LLVM Ocaml Interface ------------*- OCaml -*-===*
+(*===-- llvm_ipo.ml - LLVM OCaml Interface --------------------*- OCaml -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -7,59 +7,31 @@
*
*===----------------------------------------------------------------------===*)
-(** IPO Transforms.
-
- This interface provides an ocaml API for LLVM interprocedural optimizations, the
- classes in the [LLVMIPO] library. *)
-
-(** See llvm::createAddArgumentPromotionPass *)
external add_argument_promotion : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_argument_promotion"
-
-(** See llvm::createConstantMergePass function. *)
external add_constant_merge : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_constant_merge"
-
-(** See llvm::createDeadArgEliminationPass function. *)
external add_dead_arg_elimination :
[ | `Module ] Llvm.PassManager.t -> unit = "llvm_add_dead_arg_elimination"
-
-(** See llvm::createFunctionAttrsPass function. *)
external add_function_attrs : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_function_attrs"
-
-(** See llvm::createFunctionInliningPass function. *)
external add_function_inlining : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_function_inlining"
-
-(** See llvm::createGlobalDCEPass function. *)
+external add_always_inliner : [ | `Module ] Llvm.PassManager.t -> unit =
+ "llvm_add_always_inliner"
external add_global_dce : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_global_dce"
-
-(** See llvm::createGlobalOptimizerPass function. *)
external add_global_optimizer : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_global_optimizer"
-
-(** See llvm::createIPConstantPropagationPass function. *)
external add_ipc_propagation : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_ipc_propagation"
-
-(** See llvm::createPruneEHPass function. *)
external add_prune_eh : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_prune_eh"
-
-(** See llvm::createIPSCCPPass function. *)
external add_ipsccp : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_ipsccp"
-
-(** See llvm::createInternalizePass function. *)
external add_internalize : [ | `Module ] Llvm.PassManager.t -> bool -> unit =
"llvm_add_internalize"
-
-(** See llvm::createStripDeadPrototypesPass function. *)
external add_strip_dead_prototypes :
[ | `Module ] Llvm.PassManager.t -> unit = "llvm_add_strip_dead_prototypes"
-
-(** See llvm::createStripSymbolsPass function. *)
external add_strip_symbols : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_strip_symbols"
diff --git a/bindings/ocaml/transforms/ipo/llvm_ipo.mli b/bindings/ocaml/transforms/ipo/llvm_ipo.mli
index 636103d..1944c30 100644
--- a/bindings/ocaml/transforms/ipo/llvm_ipo.mli
+++ b/bindings/ocaml/transforms/ipo/llvm_ipo.mli
@@ -1,4 +1,4 @@
-(*===-- llvm_ipo.mli - LLVM Ocaml Interface ------------*- OCaml -*-===*
+(*===-- llvm_ipo.mli - LLVM OCaml Interface -------------------*- OCaml -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -9,13 +9,13 @@
(** IPO Transforms.
- This interface provides an ocaml API for LLVM interprocedural optimizations, the
+ This interface provides an OCaml API for LLVM interprocedural optimizations, the
classes in the [LLVMIPO] library. *)
(** See llvm::createAddArgumentPromotionPass *)
external add_argument_promotion : [ | `Module ] Llvm.PassManager.t -> unit =
-
"llvm_add_argument_promotion"
+
(** See llvm::createConstantMergePass function. *)
external add_constant_merge : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_constant_merge"
@@ -32,6 +32,10 @@ external add_function_attrs : [ | `Module ] Llvm.PassManager.t -> unit =
external add_function_inlining : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_function_inlining"
+(** See llvm::createAlwaysInlinerPass function. *)
+external add_always_inliner : [ | `Module ] Llvm.PassManager.t -> unit =
+ "llvm_add_always_inliner"
+
(** See llvm::createGlobalDCEPass function. *)
external add_global_dce : [ | `Module ] Llvm.PassManager.t -> unit =
"llvm_add_global_dce"
diff --git a/bindings/ocaml/transforms/passmgr_builder/Makefile b/bindings/ocaml/transforms/passmgr_builder/Makefile
new file mode 100644
index 0000000..54099db
--- /dev/null
+++ b/bindings/ocaml/transforms/passmgr_builder/Makefile
@@ -0,0 +1,19 @@
+##===- bindings/ocaml/transforms/passmgr_builder/Makefile --*- Makefile -*-===##
+#
+# The LLVM Compiler Infrastructure
+#
+# This file is distributed under the University of Illinois Open Source
+# License. See LICENSE.TXT for details.
+#
+##===----------------------------------------------------------------------===##
+#
+# This is the makefile for the Objective Caml Llvm_passmgr_builder interface.
+#
+##===----------------------------------------------------------------------===##
+
+LEVEL := ../../../..
+LIBRARYNAME := llvm_passmgr_builder
+UsedComponents := ipo
+UsedOcamlInterfaces := llvm
+
+include ../../Makefile.ocaml
diff --git a/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.ml b/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.ml
new file mode 100644
index 0000000..60df446
--- /dev/null
+++ b/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.ml
@@ -0,0 +1,32 @@
+(*===-- llvm_passmgr_builder.ml - LLVM OCaml Interface --------*- OCaml -*-===*
+ *
+ * The LLVM Compiler Infrastructure
+ *
+ * This file is distributed under the University of Illinois Open Source
+ * License. See LICENSE.TXT for details.
+ *
+ *===----------------------------------------------------------------------===*)
+
+type t
+
+external create : unit -> t
+ = "llvm_pmbuilder_create"
+external set_opt_level : int -> t -> unit
+ = "llvm_pmbuilder_set_opt_level"
+external set_size_level : int -> t -> unit
+ = "llvm_pmbuilder_set_size_level"
+external set_disable_unit_at_a_time : bool -> t -> unit
+ = "llvm_pmbuilder_set_disable_unit_at_a_time"
+external set_disable_unroll_loops : bool -> t -> unit
+ = "llvm_pmbuilder_set_disable_unroll_loops"
+external use_inliner_with_threshold : int -> t -> unit
+ = "llvm_pmbuilder_use_inliner_with_threshold"
+external populate_function_pass_manager
+ : [ `Function ] Llvm.PassManager.t -> t -> unit
+ = "llvm_pmbuilder_populate_function_pass_manager"
+external populate_module_pass_manager
+ : [ `Module ] Llvm.PassManager.t -> t -> unit
+ = "llvm_pmbuilder_populate_module_pass_manager"
+external populate_lto_pass_manager
+ : [ `Module ] Llvm.PassManager.t -> internalize:bool -> run_inliner:bool -> t -> unit
+ = "llvm_pmbuilder_populate_lto_pass_manager" \ No newline at end of file
diff --git a/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.mli b/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.mli
new file mode 100644
index 0000000..66b0981
--- /dev/null
+++ b/bindings/ocaml/transforms/passmgr_builder/llvm_passmgr_builder.mli
@@ -0,0 +1,54 @@
+(*===-- llvm_passmgr_builder.mli - LLVM OCaml Interface -------*- OCaml -*-===*
+ *
+ * The LLVM Compiler Infrastructure
+ *
+ * This file is distributed under the University of Illinois Open Source
+ * License. See LICENSE.TXT for details.
+ *
+ *===----------------------------------------------------------------------===*)
+
+(** Pass Manager Builder.
+
+ This interface provides an OCaml API for LLVM pass manager builder
+ from the [LLVMCore] library. *)
+
+type t
+
+(** See [llvm::PassManagerBuilder]. *)
+external create : unit -> t
+ = "llvm_pmbuilder_create"
+
+(** See [llvm::PassManagerBuilder::OptLevel]. *)
+external set_opt_level : int -> t -> unit
+ = "llvm_pmbuilder_set_opt_level"
+
+(** See [llvm::PassManagerBuilder::SizeLevel]. *)
+external set_size_level : int -> t -> unit
+ = "llvm_pmbuilder_set_size_level"
+
+(** See [llvm::PassManagerBuilder::DisableUnitAtATime]. *)
+external set_disable_unit_at_a_time : bool -> t -> unit
+ = "llvm_pmbuilder_set_disable_unit_at_a_time"
+
+(** See [llvm::PassManagerBuilder::DisableUnrollLoops]. *)
+external set_disable_unroll_loops : bool -> t -> unit
+ = "llvm_pmbuilder_set_disable_unroll_loops"
+
+(** See [llvm::PassManagerBuilder::Inliner]. *)
+external use_inliner_with_threshold : int -> t -> unit
+ = "llvm_pmbuilder_use_inliner_with_threshold"
+
+(** See [llvm::PassManagerBuilder::populateFunctionPassManager]. *)
+external populate_function_pass_manager
+ : [ `Function ] Llvm.PassManager.t -> t -> unit
+ = "llvm_pmbuilder_populate_function_pass_manager"
+
+(** See [llvm::PassManagerBuilder::populateModulePassManager]. *)
+external populate_module_pass_manager
+ : [ `Module ] Llvm.PassManager.t -> t -> unit
+ = "llvm_pmbuilder_populate_module_pass_manager"
+
+(** See [llvm::PassManagerBuilder::populateLTOPassManager]. *)
+external populate_lto_pass_manager
+ : [ `Module ] Llvm.PassManager.t -> internalize:bool -> run_inliner:bool -> t -> unit
+ = "llvm_pmbuilder_populate_lto_pass_manager" \ No newline at end of file
diff --git a/bindings/ocaml/transforms/passmgr_builder/passmgr_builder_ocaml.c b/bindings/ocaml/transforms/passmgr_builder/passmgr_builder_ocaml.c
new file mode 100644
index 0000000..a707856
--- /dev/null
+++ b/bindings/ocaml/transforms/passmgr_builder/passmgr_builder_ocaml.c
@@ -0,0 +1,113 @@
+/*===-- passmgr_builder_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
+|* *|
+|* The LLVM Compiler Infrastructure *|
+|* *|
+|* This file is distributed under the University of Illinois Open Source *|
+|* License. See LICENSE.TXT for details. *|
+|* *|
+|*===----------------------------------------------------------------------===*|
+|* *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
+|* are by and large transparent wrappers to the corresponding C functions. *|
+|* *|
+|* Note that these functions intentionally take liberties with the CAMLparamX *|
+|* macros, since most of the parameters are not GC heap objects. *|
+|* *|
+\*===----------------------------------------------------------------------===*/
+
+#include "llvm-c/Transforms/PassManagerBuilder.h"
+#include "caml/mlvalues.h"
+#include "caml/custom.h"
+#include "caml/misc.h"
+
+#define PMBuilder_val(v) (*(LLVMPassManagerBuilderRef *)(Data_custom_val(v)))
+
+static void llvm_finalize_pmbuilder(value PMB) {
+ LLVMPassManagerBuilderDispose(PMBuilder_val(PMB));
+}
+
+static struct custom_operations pmbuilder_ops = {
+ (char *) "LLVMPassManagerBuilder",
+ llvm_finalize_pmbuilder,
+ custom_compare_default,
+ custom_hash_default,
+ custom_serialize_default,
+ custom_deserialize_default
+#ifdef custom_compare_ext_default
+ , custom_compare_ext_default
+#endif
+};
+
+static value alloc_pmbuilder(LLVMPassManagerBuilderRef Ref) {
+ value Val = alloc_custom(&pmbuilder_ops,
+ sizeof(LLVMPassManagerBuilderRef), 0, 1);
+ PMBuilder_val(Val) = Ref;
+ return Val;
+}
+
+/* t -> unit */
+CAMLprim value llvm_pmbuilder_create(value Unit) {
+ return alloc_pmbuilder(LLVMPassManagerBuilderCreate());
+}
+
+/* int -> t -> unit */
+CAMLprim value llvm_pmbuilder_set_opt_level(value OptLevel, value PMB) {
+ LLVMPassManagerBuilderSetOptLevel(PMBuilder_val(PMB), Int_val(OptLevel));
+ return Val_unit;
+}
+
+/* int -> t -> unit */
+CAMLprim value llvm_pmbuilder_set_size_level(value SizeLevel, value PMB) {
+ LLVMPassManagerBuilderSetSizeLevel(PMBuilder_val(PMB), Int_val(SizeLevel));
+ return Val_unit;
+}
+
+/* int -> t -> unit */
+CAMLprim value llvm_pmbuilder_use_inliner_with_threshold(
+ value Threshold, value PMB) {
+ LLVMPassManagerBuilderSetOptLevel(PMBuilder_val(PMB), Int_val(Threshold));
+ return Val_unit;
+}
+
+/* bool -> t -> unit */
+CAMLprim value llvm_pmbuilder_set_disable_unit_at_a_time(
+ value DisableUnitAtATime, value PMB) {
+ LLVMPassManagerBuilderSetDisableUnitAtATime(
+ PMBuilder_val(PMB), Bool_val(DisableUnitAtATime));
+ return Val_unit;
+}
+
+/* bool -> t -> unit */
+CAMLprim value llvm_pmbuilder_set_disable_unroll_loops(
+ value DisableUnroll, value PMB) {
+ LLVMPassManagerBuilderSetDisableUnrollLoops(
+ PMBuilder_val(PMB), Bool_val(DisableUnroll));
+ return Val_unit;
+}
+
+/* [ `Function ] Llvm.PassManager.t -> t -> unit */
+CAMLprim value llvm_pmbuilder_populate_function_pass_manager(
+ LLVMPassManagerRef PM, value PMB) {
+ LLVMPassManagerBuilderPopulateFunctionPassManager(
+ PMBuilder_val(PMB), PM);
+ return Val_unit;
+}
+
+/* [ `Module ] Llvm.PassManager.t -> t -> unit */
+CAMLprim value llvm_pmbuilder_populate_module_pass_manager(
+ LLVMPassManagerRef PM, value PMB) {
+ LLVMPassManagerBuilderPopulateModulePassManager(
+ PMBuilder_val(PMB), PM);
+ return Val_unit;
+}
+
+/* [ `Module ] Llvm.PassManager.t ->
+ internalize:bool -> run_inliner:bool -> t -> unit */
+CAMLprim value llvm_pmbuilder_populate_lto_pass_manager(
+ LLVMPassManagerRef PM, value Internalize, value RunInliner,
+ value PMB) {
+ LLVMPassManagerBuilderPopulateLTOPassManager(
+ PMBuilder_val(PMB), PM,
+ Bool_val(Internalize), Bool_val(RunInliner));
+ return Val_unit;
+}
diff --git a/bindings/ocaml/transforms/scalar/Makefile b/bindings/ocaml/transforms/scalar/Makefile
index cbaffa4..6e250f6 100644
--- a/bindings/ocaml/transforms/scalar/Makefile
+++ b/bindings/ocaml/transforms/scalar/Makefile
@@ -13,7 +13,6 @@
LEVEL := ../../../..
LIBRARYNAME := llvm_scalar_opts
-DONT_BUILD_RELINKED := 1
UsedComponents := scalaropts
UsedOcamlInterfaces := llvm
diff --git a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml
index 93ab1de..958939d 100644
--- a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml
+++ b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml
@@ -1,4 +1,4 @@
-(*===-- llvm_scalar_opts.ml - LLVM Ocaml Interface -------------*- OCaml -*-===*
+(*===-- llvm_scalar_opts.ml - LLVM OCaml Interface -------------*- OCaml -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -109,3 +109,6 @@ external
add_basic_alias_analysis : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
= "llvm_add_basic_alias_analysis"
+external
+add_partially_inline_lib_calls : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_partially_inline_lib_calls"
diff --git a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli
index 121b376..d69abe2 100644
--- a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli
+++ b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli
@@ -1,4 +1,4 @@
-(*===-- llvm_scalar_opts.mli - LLVM Ocaml Interface ------------*- OCaml -*-===*
+(*===-- llvm_scalar_opts.mli - LLVM OCaml Interface ------------*- OCaml -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -9,7 +9,7 @@
(** Scalar Transforms.
- This interface provides an ocaml API for LLVM scalar transforms, the
+ This interface provides an OCaml API for LLVM scalar transforms, the
classes in the [LLVMScalarOpts] library. *)
(** See the [llvm::createConstantPropogationPass] function. *)
@@ -162,3 +162,7 @@ external
add_basic_alias_analysis : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
= "llvm_add_basic_alias_analysis"
+(** See the [llvm::createPartiallyInlineLibCallsPass] function. *)
+external
+add_partially_inline_lib_calls : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_partially_inline_lib_calls"
diff --git a/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c b/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c
index 7047ec0..0a71bd7 100644
--- a/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c
+++ b/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c
@@ -1,4 +1,4 @@
-/*===-- scalar_opts_ocaml.c - LLVM Ocaml Glue -------------------*- C++ -*-===*\
+/*===-- scalar_opts_ocaml.c - LLVM OCaml Glue -------------------*- C++ -*-===*\
|* *|
|* The LLVM Compiler Infrastructure *|
|* *|
@@ -7,7 +7,7 @@
|* *|
|*===----------------------------------------------------------------------===*|
|* *|
-|* This file glues LLVM's ocaml interface to its C interface. These functions *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
|* are by and large transparent wrappers to the corresponding C functions. *|
|* *|
|* Note that these functions intentionally take liberties with the CAMLparamX *|
@@ -199,3 +199,9 @@ CAMLprim value llvm_add_basic_alias_analysis(LLVMPassManagerRef PM) {
LLVMAddBasicAliasAnalysisPass(PM);
return Val_unit;
}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_partially_inline_lib_calls(LLVMPassManagerRef PM) {
+ LLVMAddPartiallyInlineLibCallsPass(PM);
+ return Val_unit;
+}
diff --git a/bindings/ocaml/transforms/vectorize/Makefile b/bindings/ocaml/transforms/vectorize/Makefile
new file mode 100644
index 0000000..5a854d1
--- /dev/null
+++ b/bindings/ocaml/transforms/vectorize/Makefile
@@ -0,0 +1,19 @@
+##===- bindings/ocaml/transforms/vectorize/Makefile --------*- Makefile -*-===##
+#
+# The LLVM Compiler Infrastructure
+#
+# This file is distributed under the University of Illinois Open Source
+# License. See LICENSE.TXT for details.
+#
+##===----------------------------------------------------------------------===##
+#
+# This is the makefile for the Objective Caml Llvm_vectorize_opts interface.
+#
+##===----------------------------------------------------------------------===##
+
+LEVEL := ../../../..
+LIBRARYNAME := llvm_vectorize
+UsedComponents := vectorize
+UsedOcamlInterfaces := llvm
+
+include ../../Makefile.ocaml
diff --git a/bindings/ocaml/transforms/vectorize/llvm_vectorize.ml b/bindings/ocaml/transforms/vectorize/llvm_vectorize.ml
new file mode 100644
index 0000000..4fc53c6
--- /dev/null
+++ b/bindings/ocaml/transforms/vectorize/llvm_vectorize.ml
@@ -0,0 +1,15 @@
+(*===-- llvm_vectorize.ml - LLVM OCaml Interface --------------*- OCaml -*-===*
+ *
+ * The LLVM Compiler Infrastructure
+ *
+ * This file is distributed under the University of Illinois Open Source
+ * License. See LICENSE.TXT for details.
+ *
+ *===----------------------------------------------------------------------===*)
+
+external add_bb_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_bb_vectorize"
+external add_loop_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_loop_vectorize"
+external add_slp_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_slp_vectorize"
diff --git a/bindings/ocaml/transforms/vectorize/llvm_vectorize.mli b/bindings/ocaml/transforms/vectorize/llvm_vectorize.mli
new file mode 100644
index 0000000..0253039
--- /dev/null
+++ b/bindings/ocaml/transforms/vectorize/llvm_vectorize.mli
@@ -0,0 +1,25 @@
+(*===-- llvm_vectorize.mli - LLVM OCaml Interface -------------*- OCaml -*-===*
+ *
+ * The LLVM Compiler Infrastructure
+ *
+ * This file is distributed under the University of Illinois Open Source
+ * License. See LICENSE.TXT for details.
+ *
+ *===----------------------------------------------------------------------===*)
+
+(** Vectorize Transforms.
+
+ This interface provides an OCaml API for LLVM vectorize transforms, the
+ classes in the [LLVMVectorize] library. *)
+
+(** See the [llvm::createBBVectorizePass] function. *)
+external add_bb_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_bb_vectorize"
+
+(** See the [llvm::createLoopVectorizePass] function. *)
+external add_loop_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_loop_vectorize"
+
+(** See [llvm::createSLPVectorizerPass] function. *)
+external add_slp_vectorize : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
+ = "llvm_add_slp_vectorize"
diff --git a/bindings/ocaml/transforms/vectorize/vectorize_ocaml.c b/bindings/ocaml/transforms/vectorize/vectorize_ocaml.c
new file mode 100644
index 0000000..1c81049
--- /dev/null
+++ b/bindings/ocaml/transforms/vectorize/vectorize_ocaml.c
@@ -0,0 +1,38 @@
+/*===-- vectorize_ocaml.c - LLVM OCaml Glue ---------------------*- C++ -*-===*\
+|* *|
+|* The LLVM Compiler Infrastructure *|
+|* *|
+|* This file is distributed under the University of Illinois Open Source *|
+|* License. See LICENSE.TXT for details. *|
+|* *|
+|*===----------------------------------------------------------------------===*|
+|* *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
+|* are by and large transparent wrappers to the corresponding C functions. *|
+|* *|
+|* Note that these functions intentionally take liberties with the CAMLparamX *|
+|* macros, since most of the parameters are not GC heap objects. *|
+|* *|
+\*===----------------------------------------------------------------------===*/
+
+#include "llvm-c/Transforms/Vectorize.h"
+#include "caml/mlvalues.h"
+#include "caml/misc.h"
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_bb_vectorize(LLVMPassManagerRef PM) {
+ LLVMAddBBVectorizePass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_loop_vectorize(LLVMPassManagerRef PM) {
+ LLVMAddLoopVectorizePass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_slp_vectorize(LLVMPassManagerRef PM) {
+ LLVMAddSLPVectorizePass(PM);
+ return Val_unit;
+}