summaryrefslogtreecommitdiff
path: root/bindings/ocaml/transforms
diff options
context:
space:
mode:
authorGordon Henriksen <gordonhenriksen@mac.com>2008-03-16 16:32:40 +0000
committerGordon Henriksen <gordonhenriksen@mac.com>2008-03-16 16:32:40 +0000
commit41ba1546eb46030e9994ee14f8052a1981ae2c54 (patch)
tree74d0748a279884133b551f3658acc0c9879b0cbe /bindings/ocaml/transforms
parent395b4149061ba7a280b628a23bcfdce94ddbfdf5 (diff)
downloadllvm-41ba1546eb46030e9994ee14f8052a1981ae2c54.tar.gz
llvm-41ba1546eb46030e9994ee14f8052a1981ae2c54.tar.bz2
llvm-41ba1546eb46030e9994ee14f8052a1981ae2c54.tar.xz
C and Objective Caml bindings for several scalar transforms.
Patch originally by Erick Tryzelaar, but has been modified somewhat. git-svn-id: https://llvm.org/svn/llvm-project/llvm/trunk@48419 91177308-0d34-0410-b5e6-96231b3b80d8
Diffstat (limited to 'bindings/ocaml/transforms')
-rw-r--r--bindings/ocaml/transforms/Makefile13
-rw-r--r--bindings/ocaml/transforms/scalar/Makefile20
-rw-r--r--bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml24
-rw-r--r--bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli38
-rw-r--r--bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c50
5 files changed, 145 insertions, 0 deletions
diff --git a/bindings/ocaml/transforms/Makefile b/bindings/ocaml/transforms/Makefile
new file mode 100644
index 0000000000..61800a9bbe
--- /dev/null
+++ b/bindings/ocaml/transforms/Makefile
@@ -0,0 +1,13 @@
+##===- bindings/ocaml/transforms/Makefile ------------------*- Makefile -*-===##
+#
+# The LLVM Compiler Infrastructure
+#
+# This file is distributed under the University of Illinois Open Source
+# License. See LICENSE.TXT for details.
+#
+##===----------------------------------------------------------------------===##
+
+LEVEL := ../../..
+DIRS = scalar
+
+include $(LEVEL)/Makefile.common
diff --git a/bindings/ocaml/transforms/scalar/Makefile b/bindings/ocaml/transforms/scalar/Makefile
new file mode 100644
index 0000000000..cbaffa4ea7
--- /dev/null
+++ b/bindings/ocaml/transforms/scalar/Makefile
@@ -0,0 +1,20 @@
+##===- bindings/ocaml/transforms/scalar/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_scalar_opts interface.
+#
+##===----------------------------------------------------------------------===##
+
+LEVEL := ../../../..
+LIBRARYNAME := llvm_scalar_opts
+DONT_BUILD_RELINKED := 1
+UsedComponents := scalaropts
+UsedOcamlInterfaces := llvm
+
+include ../../Makefile.ocaml
diff --git a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml
new file mode 100644
index 0000000000..8b6b7f9879
--- /dev/null
+++ b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.ml
@@ -0,0 +1,24 @@
+(*===-- llvm_scalar_opts.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_constant_propagation : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_constant_propagation"
+external add_instruction_combining : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_instruction_combining"
+external add_reassociation : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_reassociation"
+external add_gvn : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_gvn"
+external add_cfg_simplification : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_cfg_simplification"
diff --git a/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli
new file mode 100644
index 0000000000..19efaa015e
--- /dev/null
+++ b/bindings/ocaml/transforms/scalar/llvm_scalar_opts.mli
@@ -0,0 +1,38 @@
+(*===-- llvm_scalar_opts.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.
+ *
+ *===----------------------------------------------------------------------===*)
+
+(** Scalar Transforms.
+
+ This interface provides an ocaml API for LLVM scalar transforms, the
+ classes in the [LLVMScalarOpts] library. *)
+
+(** See the [llvm::createConstantPropogationPass] function. *)
+external add_constant_propagation : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_constant_propagation"
+
+(** See the [llvm::createInstructionCombiningPass] function. *)
+external add_instruction_combining : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_instruction_combining"
+
+(** See the [llvm::createReassociatePass] function. *)
+external add_reassociation : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_reassociation"
+
+(** See the [llvm::createGVNPass] function. *)
+external add_gvn : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_gvn"
+
+(** See the [llvm::createCFGSimplificationPass] function. *)
+external add_cfg_simplification : [<Llvm.PassManager.any] Llvm.PassManager.t
+ -> unit
+ = "llvm_add_cfg_simplification"
diff --git a/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c b/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c
new file mode 100644
index 0000000000..5ceb3699cc
--- /dev/null
+++ b/bindings/ocaml/transforms/scalar/scalar_opts_ocaml.c
@@ -0,0 +1,50 @@
+/*===-- scalar_opts_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/Scalar.h"
+#include "caml/mlvalues.h"
+#include "caml/misc.h"
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_constant_propagation(LLVMPassManagerRef PM) {
+ LLVMAddConstantPropagationPass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_instruction_combining(LLVMPassManagerRef PM) {
+ LLVMAddInstructionCombiningPass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_reassociation(LLVMPassManagerRef PM) {
+ LLVMAddReassociatePass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_gvn(LLVMPassManagerRef PM) {
+ LLVMAddGVNPass(PM);
+ return Val_unit;
+}
+
+/* [<Llvm.PassManager.any] Llvm.PassManager.t -> unit */
+CAMLprim value llvm_add_cfg_simplification(LLVMPassManagerRef PM) {
+ LLVMAddCFGSimplificationPass(PM);
+ return Val_unit;
+}