IR: Give 'DI' prefix to debug info metadata
[oota-llvm.git] / bindings / ocaml / bitwriter / bitwriter_ocaml.c
index 05682c7c864bf148036ec9b47bc4ca84dc705080..04fd61917dc6205979d36b64c8c314bcb5effc94 100644 (file)
@@ -1,13 +1,13 @@
-/*===-- bitwriter_ocaml.c - LLVM Ocaml Glue ---------------------*- C++ -*-===*\
+/*===-- bitwriter_ocaml.c - LLVM OCaml Glue ---------------------*- C++ -*-===*\
 |*                                                                            *|
 |*                     The LLVM Compiler Infrastructure                       *|
 |*                                                                            *|
-|* This file was developed by Gordon Henriksen and is distributed under the   *|
-|* University of Illinois Open Source License. See LICENSE.TXT for details.   *|
+|* 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 *|
+|* 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 *|
 #include "caml/mlvalues.h"
 #include "caml/memory.h"
 
-/*===-- Modules -----------------------------------------------------------===*/
-
 /* Llvm.llmodule -> string -> bool */
-CAMLprim value llvm_write_bitcode_file(value M, value Path) {
-  int res = LLVMWriteBitcodeToFile((LLVMModuleRef) M, String_val(Path));
-  return Val_bool(res == 0);
+CAMLprim value llvm_write_bitcode_file(LLVMModuleRef M, value Path) {
+  int Result = LLVMWriteBitcodeToFile(M, String_val(Path));
+  return Val_bool(Result == 0);
+}
+
+/* ?unbuffered:bool -> Llvm.llmodule -> Unix.file_descr -> bool */
+CAMLprim value llvm_write_bitcode_to_fd(value U, LLVMModuleRef M, value FD) {
+  int Unbuffered;
+  int Result;
+
+  if (U == Val_int(0)) {
+    Unbuffered = 0;
+  } else {
+    Unbuffered = Bool_val(Field(U, 0));
+  }
+
+  Result = LLVMWriteBitcodeToFD(M, Int_val(FD), 0, Unbuffered);
+  return Val_bool(Result == 0);
+}
+
+/* Llvm.llmodule -> Llvm.llmemorybuffer */
+CAMLprim LLVMMemoryBufferRef llvm_write_bitcode_to_memory_buffer(LLVMModuleRef M) {
+  return LLVMWriteBitcodeToMemoryBuffer(M);
 }