Remove malloc and free from the ocaml bindings.
[oota-llvm.git] / bindings / ocaml / llvm / llvm_ocaml.c
index 69bd0a2fbc111bb92020a210d9f4874331d9eb51..23b74dd95d596ea31eefd5bbacb96cb0384f15bc 100644 (file)
@@ -92,11 +92,29 @@ static value alloc_variant(int tag, void *Value) {
   }
 
 
+/*===-- Contexts ----------------------------------------------------------===*/
+
+/* unit -> llcontext */
+CAMLprim LLVMContextRef llvm_create_context(value Unit) {
+  return LLVMContextCreate();
+}
+
+/* llcontext -> unit */
+CAMLprim value llvm_dispose_context(LLVMContextRef C) {
+  LLVMContextDispose(C);
+  return Val_unit;
+}
+
+/* unit -> llcontext */
+CAMLprim LLVMContextRef llvm_global_context(value Unit) {
+  return LLVMGetGlobalContext();
+}
+
 /*===-- Modules -----------------------------------------------------------===*/
 
-/* string -> llmodule */
-CAMLprim LLVMModuleRef llvm_create_module(value ModuleID) {
-  return LLVMModuleCreateWithName(String_val(ModuleID));
+/* llcontext -> string -> llmodule */
+CAMLprim LLVMModuleRef llvm_create_module(LLVMContextRef C, value ModuleID) {
+  return LLVMModuleCreateWithNameInContext(String_val(ModuleID), C);
 }
 
 /* llmodule -> unit */
@@ -153,18 +171,41 @@ CAMLprim value llvm_classify_type(LLVMTypeRef Ty) {
   return Val_int(LLVMGetTypeKind(Ty));
 }
 
+/* lltype -> llcontext */
+CAMLprim LLVMContextRef llvm_type_context(LLVMTypeRef Ty) {
+  return LLVMGetTypeContext(Ty);
+}
+
 /*--... Operations on integer types ........................................--*/
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_i1_type (value Unit) { return LLVMInt1Type();  }
-CAMLprim LLVMTypeRef llvm_i8_type (value Unit) { return LLVMInt8Type();  }
-CAMLprim LLVMTypeRef llvm_i16_type(value Unit) { return LLVMInt16Type(); }
-CAMLprim LLVMTypeRef llvm_i32_type(value Unit) { return LLVMInt32Type(); }
-CAMLprim LLVMTypeRef llvm_i64_type(value Unit) { return LLVMInt64Type(); }
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_i1_type (LLVMContextRef Context) {
+  return LLVMInt1TypeInContext(Context);
+}
 
-/* int -> lltype */
-CAMLprim LLVMTypeRef llvm_integer_type(value Width) {
-  return LLVMIntType(Int_val(Width));
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_i8_type (LLVMContextRef Context) {
+  return LLVMInt8TypeInContext(Context);
+}
+
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_i16_type (LLVMContextRef Context) {
+  return LLVMInt16TypeInContext(Context);
+}
+
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_i32_type (LLVMContextRef Context) {
+  return LLVMInt32TypeInContext(Context);
+}
+
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_i64_type (LLVMContextRef Context) {
+  return LLVMInt64TypeInContext(Context);
+}
+
+/* llcontext -> int -> lltype */
+CAMLprim LLVMTypeRef llvm_integer_type(LLVMContextRef Context, value Width) {
+  return LLVMIntTypeInContext(Context, Int_val(Width));
 }
 
 /* lltype -> int */
@@ -174,29 +215,29 @@ CAMLprim value llvm_integer_bitwidth(LLVMTypeRef IntegerTy) {
 
 /*--... Operations on real types ...........................................--*/
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_float_type(value Unit) {
-  return LLVMFloatType();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_float_type(LLVMContextRef Context) {
+  return LLVMFloatTypeInContext(Context);
 }
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_double_type(value Unit) {
-  return LLVMDoubleType();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_double_type(LLVMContextRef Context) {
+  return LLVMDoubleTypeInContext(Context);
 }
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_x86fp80_type(value Unit) {
-  return LLVMX86FP80Type();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_x86fp80_type(LLVMContextRef Context) {
+  return LLVMX86FP80TypeInContext(Context);
 }
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_fp128_type(value Unit) {
-  return LLVMFP128Type();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_fp128_type(LLVMContextRef Context) {
+  return LLVMFP128TypeInContext(Context);
 }
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_ppc_fp128_type(value Unit) {
-  return LLVMPPCFP128Type();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_ppc_fp128_type(LLVMContextRef Context) {
+  return LLVMPPCFP128TypeInContext(Context);
 }
 
 /*--... Operations on function types .......................................--*/
@@ -228,16 +269,17 @@ CAMLprim value llvm_param_types(LLVMTypeRef FunTy) {
 
 /*--... Operations on struct types .........................................--*/
 
-/* lltype array -> lltype */
-CAMLprim LLVMTypeRef llvm_struct_type(value ElementTypes) {
-  return LLVMStructType((LLVMTypeRef *) ElementTypes,
-                        Wosize_val(ElementTypes), 0);
+/* llcontext -> lltype array -> lltype */
+CAMLprim LLVMTypeRef llvm_struct_type(LLVMContextRef C, value ElementTypes) {
+  return LLVMStructTypeInContext(C, (LLVMTypeRef *) ElementTypes,
+                                 Wosize_val(ElementTypes), 0);
 }
 
-/* lltype array -> lltype */
-CAMLprim LLVMTypeRef llvm_packed_struct_type(value ElementTypes) {
-  return LLVMStructType((LLVMTypeRef *) ElementTypes,
-                        Wosize_val(ElementTypes), 1);
+/* llcontext -> lltype array -> lltype */
+CAMLprim LLVMTypeRef llvm_packed_struct_type(LLVMContextRef C,
+                                             value ElementTypes) {
+  return LLVMStructTypeInContext(C, (LLVMTypeRef *) ElementTypes,
+                                 Wosize_val(ElementTypes), 1);
 }
 
 /* lltype -> lltype array */
@@ -292,13 +334,19 @@ CAMLprim value llvm_vector_size(LLVMTypeRef VectorTy) {
 
 /*--... Operations on other types ..........................................--*/
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_void_type (value Unit) { return LLVMVoidType();  }
-CAMLprim LLVMTypeRef llvm_label_type(value Unit) { return LLVMLabelType(); }
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_void_type (LLVMContextRef Context) {
+  return LLVMVoidTypeInContext(Context);
+}
+
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_label_type(LLVMContextRef Context) {
+  return LLVMLabelTypeInContext(Context);
+}
 
-/* unit -> lltype */
-CAMLprim LLVMTypeRef llvm_opaque_type(value Unit) {
-  return LLVMOpaqueType();
+/* llcontext -> lltype */
+CAMLprim LLVMTypeRef llvm_opaque_type(LLVMContextRef Context) {
+  return LLVMOpaqueTypeInContext(Context);
 }
 
 /*--... Operations on type handles .........................................--*/
@@ -408,14 +456,18 @@ CAMLprim LLVMValueRef llvm_const_float_of_string(LLVMTypeRef RealTy, value S) {
 
 /*--... Operations on composite constants ..................................--*/
 
-/* string -> llvalue */
-CAMLprim LLVMValueRef llvm_const_string(value Str, value NullTerminate) {
-  return LLVMConstString(String_val(Str), string_length(Str), 1);
+/* llcontext -> string -> llvalue */
+CAMLprim LLVMValueRef llvm_const_string(LLVMContextRef Context, value Str,
+                                        value NullTerminate) {
+  return LLVMConstStringInContext(Context, String_val(Str), string_length(Str),
+                                  1);
 }
 
-/* string -> llvalue */
-CAMLprim LLVMValueRef llvm_const_stringz(value Str, value NullTerminate) {
-  return LLVMConstString(String_val(Str), string_length(Str), 0);
+/* llcontext -> string -> llvalue */
+CAMLprim LLVMValueRef llvm_const_stringz(LLVMContextRef Context, value Str,
+                                         value NullTerminate) {
+  return LLVMConstStringInContext(Context, String_val(Str), string_length(Str),
+                                  0);
 }
 
 /* lltype -> llvalue array -> llvalue */
@@ -425,16 +477,17 @@ CAMLprim LLVMValueRef llvm_const_array(LLVMTypeRef ElementTy,
                         Wosize_val(ElementVals));
 }
 
-/* llvalue array -> llvalue */
-CAMLprim LLVMValueRef llvm_const_struct(value ElementVals) {
-  return LLVMConstStruct((LLVMValueRef *) Op_val(ElementVals),
-                         Wosize_val(ElementVals), 0);
+/* llcontext -> llvalue array -> llvalue */
+CAMLprim LLVMValueRef llvm_const_struct(LLVMContextRef C, value ElementVals) {
+  return LLVMConstStructInContext(C, (LLVMValueRef *) Op_val(ElementVals),
+                                  Wosize_val(ElementVals), 0);
 }
 
-/* llvalue array -> llvalue */
-CAMLprim LLVMValueRef llvm_const_packed_struct(value ElementVals) {
-  return LLVMConstStruct((LLVMValueRef *) Op_val(ElementVals),
-                         Wosize_val(ElementVals), 1);
+/* llcontext -> llvalue array -> llvalue */
+CAMLprim LLVMValueRef llvm_const_packed_struct(LLVMContextRef C,
+                                               value ElementVals) {
+  return LLVMConstStructInContext(C, (LLVMValueRef *) Op_val(ElementVals),
+                                  Wosize_val(ElementVals), 1);
 }
 
 /* llvalue array -> llvalue */
@@ -672,7 +725,7 @@ CAMLprim value llvm_lookup_function(value Name, LLVMModuleRef M) {
 CAMLprim LLVMValueRef llvm_define_function(value Name, LLVMTypeRef Ty,
                                            LLVMModuleRef M) {
   LLVMValueRef Fn = LLVMAddFunction(M, String_val(Name), Ty);
-  LLVMAppendBasicBlock(Fn, "entry");
+  LLVMAppendBasicBlockInContext(LLVMGetTypeContext(Ty), Fn, "entry");
   return Fn;
 }
 
@@ -785,13 +838,15 @@ CAMLprim value llvm_delete_block(LLVMBasicBlockRef BB) {
 }
 
 /* string -> llvalue -> llbasicblock */
-CAMLprim LLVMBasicBlockRef llvm_append_block(value Name, LLVMValueRef Fn) {
-  return LLVMAppendBasicBlock(Fn, String_val(Name));
+CAMLprim LLVMBasicBlockRef llvm_append_block(LLVMContextRef Context, value Name,
+                                             LLVMValueRef Fn) {
+  return LLVMAppendBasicBlockInContext(Context, Fn, String_val(Name));
 }
 
 /* string -> llbasicblock -> llbasicblock */
-CAMLprim LLVMBasicBlockRef llvm_insert_block(value Name, LLVMBasicBlockRef BB) {
-  return LLVMInsertBasicBlock(BB, String_val(Name));
+CAMLprim LLVMBasicBlockRef llvm_insert_block(LLVMContextRef Context, value Name,
+                                             LLVMBasicBlockRef BB) {
+  return LLVMInsertBasicBlockInContext(Context, BB, String_val(Name));
 }
 
 /* llvalue -> bool */
@@ -905,9 +960,9 @@ static value alloc_builder(LLVMBuilderRef B) {
   return V;
 }
 
-/* unit-> llbuilder */
-CAMLprim value llvm_builder(value Unit) {
-  return alloc_builder(LLVMCreateBuilder());
+/* llcontext -> llbuilder */
+CAMLprim value llvm_builder(LLVMContextRef C) {
+  return alloc_builder(LLVMCreateBuilderInContext(C));
 }
 
 /* (llbasicblock, llvalue) llpos -> llbuilder -> unit */
@@ -949,6 +1004,12 @@ CAMLprim LLVMValueRef llvm_build_ret(LLVMValueRef Val, value B) {
   return LLVMBuildRet(Builder_val(B), Val);
 }
 
+/* llvalue array -> llbuilder -> llvalue */
+CAMLprim LLVMValueRef llvm_build_aggregate_ret(value RetVals, value B) {
+  return LLVMBuildAggregateRet(Builder_val(B), (LLVMValueRef *) Op_val(RetVals),
+                               Wosize_val(RetVals));
+}
+
 /* llbasicblock -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_br(LLVMBasicBlockRef BB, value B) {
   return LLVMBuildBr(Builder_val(B), BB);
@@ -970,8 +1031,8 @@ CAMLprim LLVMValueRef llvm_build_switch(LLVMValueRef Of,
   return LLVMBuildSwitch(Builder_val(B), Of, Else, Int_val(EstimatedCount));
 }
 
-CAMLprim value llvm_add_case(LLVMValueRef Switch,
-                             LLVMValueRef OnVal,
+/* llvalue -> llvalue -> llbasicblock -> unit */
+CAMLprim value llvm_add_case(LLVMValueRef Switch, LLVMValueRef OnVal,
                              LLVMBasicBlockRef Dest) {
   LLVMAddCase(Switch, OnVal, Dest);
   return Val_unit;
@@ -1142,18 +1203,6 @@ CAMLprim LLVMValueRef llvm_build_not(LLVMValueRef X,
 
 /*--... Memory .............................................................--*/
 
-/* lltype -> string -> llbuilder -> llvalue */
-CAMLprim LLVMValueRef llvm_build_malloc(LLVMTypeRef Ty,
-                                        value Name, value B) {
-  return LLVMBuildMalloc(Builder_val(B), Ty, String_val(Name));
-}
-
-/* lltype -> llvalue -> string -> llbuilder -> llvalue */
-CAMLprim LLVMValueRef llvm_build_array_malloc(LLVMTypeRef Ty, LLVMValueRef Size,
-                                              value Name, value B) {
-  return LLVMBuildArrayMalloc(Builder_val(B), Ty, Size, String_val(Name));
-}
-
 /* lltype -> string -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_alloca(LLVMTypeRef Ty,
                                         value Name, value B) {
@@ -1166,11 +1215,6 @@ CAMLprim LLVMValueRef llvm_build_array_alloca(LLVMTypeRef Ty, LLVMValueRef Size,
   return LLVMBuildArrayAlloca(Builder_val(B), Ty, Size, String_val(Name));
 }
 
-/* llvalue -> llbuilder -> llvalue */
-CAMLprim LLVMValueRef llvm_build_free(LLVMValueRef Pointer, value B) {
-  return LLVMBuildFree(Builder_val(B), Pointer);
-}
-
 /* llvalue -> string -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_load(LLVMValueRef Pointer,
                                       value Name, value B) {
@@ -1202,11 +1246,10 @@ CAMLprim LLVMValueRef llvm_build_in_bounds_gep(LLVMValueRef Pointer,
 
 /* llvalue -> int -> string -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_struct_gep(LLVMValueRef Pointer,
-                                               value Indices, value Name,
+                                               value Index, value Name,
                                                value B) {
-  return LLVMBuildInBoundsGEP(Builder_val(B), Pointer,
-                              (LLVMValueRef *) Op_val(Indices),
-                              Wosize_val(Indices), String_val(Name));
+  return LLVMBuildStructGEP(Builder_val(B), Pointer,
+                              Int_val(Index), String_val(Name));
 }
 
 /* string -> string -> llbuilder -> llvalue */