executionengine_ocaml.c 12 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361
  1. /*===-- executionengine_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
  2. |* *|
  3. |* The LLVM Compiler Infrastructure *|
  4. |* *|
  5. |* This file is distributed under the University of Illinois Open Source *|
  6. |* License. See LICENSE.TXT for details. *|
  7. |* *|
  8. |*===----------------------------------------------------------------------===*|
  9. |* *|
  10. |* This file glues LLVM's OCaml interface to its C interface. These functions *|
  11. |* are by and large transparent wrappers to the corresponding C functions. *|
  12. |* *|
  13. |* Note that these functions intentionally take liberties with the CAMLparamX *|
  14. |* macros, since most of the parameters are not GC heap objects. *|
  15. |* *|
  16. \*===----------------------------------------------------------------------===*/
  17. #include "llvm-c/ExecutionEngine.h"
  18. #include "llvm-c/Target.h"
  19. #include "caml/alloc.h"
  20. #include "caml/custom.h"
  21. #include "caml/fail.h"
  22. #include "caml/memory.h"
  23. #include <string.h>
  24. #include <assert.h>
  25. /* Force the LLVM interpreter and JIT to be linked in. */
  26. void llvm_initialize(void) {
  27. LLVMLinkInInterpreter();
  28. LLVMLinkInMCJIT();
  29. }
  30. /* unit -> bool */
  31. CAMLprim value llvm_initialize_native_target(value Unit) {
  32. return Val_bool(!LLVMInitializeNativeTarget() &&
  33. !LLVMInitializeNativeAsmParser() &&
  34. !LLVMInitializeNativeAsmPrinter());
  35. }
  36. /* Can't use the recommended caml_named_value mechanism for backwards
  37. compatibility reasons. This is largely equivalent. */
  38. static value llvm_ee_error_exn;
  39. CAMLprim value llvm_register_ee_exns(value Error) {
  40. llvm_ee_error_exn = Field(Error, 0);
  41. register_global_root(&llvm_ee_error_exn);
  42. return Val_unit;
  43. }
  44. static void llvm_raise(value Prototype, char *Message) {
  45. CAMLparam1(Prototype);
  46. CAMLlocal1(CamlMessage);
  47. CamlMessage = copy_string(Message);
  48. LLVMDisposeMessage(Message);
  49. raise_with_arg(Prototype, CamlMessage);
  50. abort(); /* NOTREACHED */
  51. #ifdef CAMLnoreturn
  52. CAMLnoreturn; /* Silences warnings, but is missing in some versions. */
  53. #endif
  54. }
  55. /*--... Operations on generic values .......................................--*/
  56. #define Genericvalue_val(v) (*(LLVMGenericValueRef *)(Data_custom_val(v)))
  57. static void llvm_finalize_generic_value(value GenVal) {
  58. LLVMDisposeGenericValue(Genericvalue_val(GenVal));
  59. }
  60. static struct custom_operations generic_value_ops = {
  61. (char *) "LLVMGenericValue",
  62. llvm_finalize_generic_value,
  63. custom_compare_default,
  64. custom_hash_default,
  65. custom_serialize_default,
  66. custom_deserialize_default
  67. #ifdef custom_compare_ext_default
  68. , custom_compare_ext_default
  69. #endif
  70. };
  71. static value alloc_generic_value(LLVMGenericValueRef Ref) {
  72. value Val = alloc_custom(&generic_value_ops, sizeof(LLVMGenericValueRef), 0, 1);
  73. Genericvalue_val(Val) = Ref;
  74. return Val;
  75. }
  76. /* Llvm.lltype -> float -> t */
  77. CAMLprim value llvm_genericvalue_of_float(LLVMTypeRef Ty, value N) {
  78. CAMLparam1(N);
  79. CAMLreturn(alloc_generic_value(
  80. LLVMCreateGenericValueOfFloat(Ty, Double_val(N))));
  81. }
  82. /* 'a -> t */
  83. CAMLprim value llvm_genericvalue_of_pointer(value V) {
  84. CAMLparam1(V);
  85. CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V))));
  86. }
  87. /* Llvm.lltype -> int -> t */
  88. CAMLprim value llvm_genericvalue_of_int(LLVMTypeRef Ty, value Int) {
  89. return alloc_generic_value(LLVMCreateGenericValueOfInt(Ty, Int_val(Int), 1));
  90. }
  91. /* Llvm.lltype -> int32 -> t */
  92. CAMLprim value llvm_genericvalue_of_int32(LLVMTypeRef Ty, value Int32) {
  93. CAMLparam1(Int32);
  94. CAMLreturn(alloc_generic_value(
  95. LLVMCreateGenericValueOfInt(Ty, Int32_val(Int32), 1)));
  96. }
  97. /* Llvm.lltype -> nativeint -> t */
  98. CAMLprim value llvm_genericvalue_of_nativeint(LLVMTypeRef Ty, value NatInt) {
  99. CAMLparam1(NatInt);
  100. CAMLreturn(alloc_generic_value(
  101. LLVMCreateGenericValueOfInt(Ty, Nativeint_val(NatInt), 1)));
  102. }
  103. /* Llvm.lltype -> int64 -> t */
  104. CAMLprim value llvm_genericvalue_of_int64(LLVMTypeRef Ty, value Int64) {
  105. CAMLparam1(Int64);
  106. CAMLreturn(alloc_generic_value(
  107. LLVMCreateGenericValueOfInt(Ty, Int64_val(Int64), 1)));
  108. }
  109. /* Llvm.lltype -> t -> float */
  110. CAMLprim value llvm_genericvalue_as_float(LLVMTypeRef Ty, value GenVal) {
  111. CAMLparam1(GenVal);
  112. CAMLreturn(copy_double(
  113. LLVMGenericValueToFloat(Ty, Genericvalue_val(GenVal))));
  114. }
  115. /* t -> 'a */
  116. CAMLprim value llvm_genericvalue_as_pointer(value GenVal) {
  117. return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal)));
  118. }
  119. /* t -> int */
  120. CAMLprim value llvm_genericvalue_as_int(value GenVal) {
  121. assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 8 * sizeof(value)
  122. && "Generic value too wide to treat as an int!");
  123. return Val_int(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1));
  124. }
  125. /* t -> int32 */
  126. CAMLprim value llvm_genericvalue_as_int32(value GenVal) {
  127. CAMLparam1(GenVal);
  128. assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 32
  129. && "Generic value too wide to treat as an int32!");
  130. CAMLreturn(copy_int32(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1)));
  131. }
  132. /* t -> int64 */
  133. CAMLprim value llvm_genericvalue_as_int64(value GenVal) {
  134. CAMLparam1(GenVal);
  135. assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 64
  136. && "Generic value too wide to treat as an int64!");
  137. CAMLreturn(copy_int64(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1)));
  138. }
  139. /* t -> nativeint */
  140. CAMLprim value llvm_genericvalue_as_nativeint(value GenVal) {
  141. CAMLparam1(GenVal);
  142. assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 8 * sizeof(value)
  143. && "Generic value too wide to treat as a nativeint!");
  144. CAMLreturn(copy_nativeint(LLVMGenericValueToInt(Genericvalue_val(GenVal),1)));
  145. }
  146. /*--... Operations on execution engines ....................................--*/
  147. /* llmodule -> ExecutionEngine.t */
  148. CAMLprim LLVMExecutionEngineRef llvm_ee_create(LLVMModuleRef M) {
  149. LLVMExecutionEngineRef Interp;
  150. char *Error;
  151. if (LLVMCreateExecutionEngineForModule(&Interp, M, &Error))
  152. llvm_raise(llvm_ee_error_exn, Error);
  153. return Interp;
  154. }
  155. /* llmodule -> ExecutionEngine.t */
  156. CAMLprim LLVMExecutionEngineRef
  157. llvm_ee_create_interpreter(LLVMModuleRef M) {
  158. LLVMExecutionEngineRef Interp;
  159. char *Error;
  160. if (LLVMCreateInterpreterForModule(&Interp, M, &Error))
  161. llvm_raise(llvm_ee_error_exn, Error);
  162. return Interp;
  163. }
  164. /* llmodule -> int -> ExecutionEngine.t */
  165. CAMLprim LLVMExecutionEngineRef
  166. llvm_ee_create_jit(LLVMModuleRef M, value OptLevel) {
  167. LLVMExecutionEngineRef JIT;
  168. char *Error;
  169. if (LLVMCreateJITCompilerForModule(&JIT, M, Int_val(OptLevel), &Error))
  170. llvm_raise(llvm_ee_error_exn, Error);
  171. return JIT;
  172. }
  173. /* llmodule -> llcompileroption -> ExecutionEngine.t */
  174. CAMLprim LLVMExecutionEngineRef
  175. llvm_ee_create_mcjit(LLVMModuleRef M, value OptRecord) {
  176. LLVMExecutionEngineRef MCJIT;
  177. char *Error;
  178. struct LLVMMCJITCompilerOptions Options = {
  179. .OptLevel = Int_val(Field(OptRecord, 0)),
  180. .CodeModel = Int_val(Field(OptRecord, 1)),
  181. .NoFramePointerElim = Int_val(Field(OptRecord, 2)),
  182. .EnableFastISel = Int_val(Field(OptRecord, 3)),
  183. .MCJMM = NULL
  184. };
  185. if (LLVMCreateMCJITCompilerForModule(&MCJIT, M, &Options,
  186. sizeof(Options), &Error))
  187. llvm_raise(llvm_ee_error_exn, Error);
  188. return MCJIT;
  189. }
  190. /* ExecutionEngine.t -> unit */
  191. CAMLprim value llvm_ee_dispose(LLVMExecutionEngineRef EE) {
  192. LLVMDisposeExecutionEngine(EE);
  193. return Val_unit;
  194. }
  195. /* llmodule -> ExecutionEngine.t -> unit */
  196. CAMLprim value llvm_ee_add_module(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
  197. LLVMAddModule(EE, M);
  198. return Val_unit;
  199. }
  200. /* llmodule -> ExecutionEngine.t -> llmodule */
  201. CAMLprim LLVMModuleRef llvm_ee_remove_module(LLVMModuleRef M,
  202. LLVMExecutionEngineRef EE) {
  203. LLVMModuleRef RemovedModule;
  204. char *Error;
  205. if (LLVMRemoveModule(EE, M, &RemovedModule, &Error))
  206. llvm_raise(llvm_ee_error_exn, Error);
  207. return RemovedModule;
  208. }
  209. /* string -> ExecutionEngine.t -> llvalue option */
  210. CAMLprim value llvm_ee_find_function(value Name, LLVMExecutionEngineRef EE) {
  211. CAMLparam1(Name);
  212. CAMLlocal1(Option);
  213. LLVMValueRef Found;
  214. if (LLVMFindFunction(EE, String_val(Name), &Found))
  215. CAMLreturn(Val_unit);
  216. Option = alloc(1, 0);
  217. Field(Option, 0) = Val_op(Found);
  218. CAMLreturn(Option);
  219. }
  220. /* llvalue -> GenericValue.t array -> ExecutionEngine.t -> GenericValue.t */
  221. CAMLprim value llvm_ee_run_function(LLVMValueRef F, value Args,
  222. LLVMExecutionEngineRef EE) {
  223. unsigned NumArgs;
  224. LLVMGenericValueRef Result, *GVArgs;
  225. unsigned I;
  226. NumArgs = Wosize_val(Args);
  227. GVArgs = (LLVMGenericValueRef*) malloc(NumArgs * sizeof(LLVMGenericValueRef));
  228. for (I = 0; I != NumArgs; ++I)
  229. GVArgs[I] = Genericvalue_val(Field(Args, I));
  230. Result = LLVMRunFunction(EE, F, NumArgs, GVArgs);
  231. free(GVArgs);
  232. return alloc_generic_value(Result);
  233. }
  234. /* ExecutionEngine.t -> unit */
  235. CAMLprim value llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE) {
  236. LLVMRunStaticConstructors(EE);
  237. return Val_unit;
  238. }
  239. /* ExecutionEngine.t -> unit */
  240. CAMLprim value llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE) {
  241. LLVMRunStaticDestructors(EE);
  242. return Val_unit;
  243. }
  244. /* llvalue -> string array -> (string * string) array -> ExecutionEngine.t ->
  245. int */
  246. CAMLprim value llvm_ee_run_function_as_main(LLVMValueRef F,
  247. value Args, value Env,
  248. LLVMExecutionEngineRef EE) {
  249. CAMLparam2(Args, Env);
  250. int I, NumArgs, NumEnv, EnvSize, Result;
  251. const char **CArgs, **CEnv;
  252. char *CEnvBuf, *Pos;
  253. NumArgs = Wosize_val(Args);
  254. NumEnv = Wosize_val(Env);
  255. /* Build the environment. */
  256. CArgs = (const char **) malloc(NumArgs * sizeof(char*));
  257. for (I = 0; I != NumArgs; ++I)
  258. CArgs[I] = String_val(Field(Args, I));
  259. /* Compute the size of the environment string buffer. */
  260. for (I = 0, EnvSize = 0; I != NumEnv; ++I) {
  261. EnvSize += strlen(String_val(Field(Field(Env, I), 0))) + 1;
  262. EnvSize += strlen(String_val(Field(Field(Env, I), 1))) + 1;
  263. }
  264. /* Build the environment. */
  265. CEnv = (const char **) malloc((NumEnv + 1) * sizeof(char*));
  266. CEnvBuf = (char*) malloc(EnvSize);
  267. Pos = CEnvBuf;
  268. for (I = 0; I != NumEnv; ++I) {
  269. char *Name = String_val(Field(Field(Env, I), 0)),
  270. *Value = String_val(Field(Field(Env, I), 1));
  271. int NameLen = strlen(Name),
  272. ValueLen = strlen(Value);
  273. CEnv[I] = Pos;
  274. memcpy(Pos, Name, NameLen);
  275. Pos += NameLen;
  276. *Pos++ = '=';
  277. memcpy(Pos, Value, ValueLen);
  278. Pos += ValueLen;
  279. *Pos++ = '\0';
  280. }
  281. CEnv[NumEnv] = NULL;
  282. Result = LLVMRunFunctionAsMain(EE, F, NumArgs, CArgs, CEnv);
  283. free(CArgs);
  284. free(CEnv);
  285. free(CEnvBuf);
  286. CAMLreturn(Val_int(Result));
  287. }
  288. /* llvalue -> ExecutionEngine.t -> unit */
  289. CAMLprim value llvm_ee_free_machine_code(LLVMValueRef F,
  290. LLVMExecutionEngineRef EE) {
  291. LLVMFreeMachineCodeForFunction(EE, F);
  292. return Val_unit;
  293. }
  294. extern value llvm_alloc_data_layout(LLVMTargetDataRef TargetData);
  295. /* ExecutionEngine.t -> Llvm_target.DataLayout.t */
  296. CAMLprim value llvm_ee_get_data_layout(LLVMExecutionEngineRef EE) {
  297. value DataLayout;
  298. LLVMTargetDataRef OrigDataLayout;
  299. OrigDataLayout = LLVMGetExecutionEngineTargetData(EE);
  300. char* TargetDataCStr;
  301. TargetDataCStr = LLVMCopyStringRepOfTargetData(OrigDataLayout);
  302. DataLayout = llvm_alloc_data_layout(LLVMCreateTargetData(TargetDataCStr));
  303. LLVMDisposeMessage(TargetDataCStr);
  304. return DataLayout;
  305. }