File: executionengine_ocaml.c

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (130 lines) | stat: -rw-r--r-- 4,880 bytes parent folder | download | duplicates (12)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
/*===-- executionengine_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
|*                                                                            *|
|* Part of the LLVM Project, under the Apache License v2.0 with LLVM          *|
|* Exceptions.                                                                *|
|* See https://llvm.org/LICENSE.txt for license information.                  *|
|* SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception                    *|
|*                                                                            *|
|*===----------------------------------------------------------------------===*|
|*                                                                            *|
|* 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 "caml/alloc.h"
#include "caml/callback.h"
#include "caml/custom.h"
#include "caml/fail.h"
#include "caml/memory.h"
#include "llvm_ocaml.h"
#include "llvm-c/Core.h"
#include "llvm-c/ExecutionEngine.h"
#include "llvm-c/Target.h"
#include <assert.h>
#include <string.h>

#define ExecutionEngine_val(v) ((LLVMExecutionEngineRef)from_val(v))

void llvm_raise(value Prototype, char *Message);

/* unit -> bool */
value llvm_ee_initialize(value Unit) {
  LLVMLinkInMCJIT();

  return Val_bool(!LLVMInitializeNativeTarget() &&
                  !LLVMInitializeNativeAsmParser() &&
                  !LLVMInitializeNativeAsmPrinter());
}

/* llcompileroption -> llmodule -> ExecutionEngine.t */
value llvm_ee_create(value OptRecordOpt, value M) {
  LLVMExecutionEngineRef MCJIT;
  char *Error;
  struct LLVMMCJITCompilerOptions Options;

  LLVMInitializeMCJITCompilerOptions(&Options, sizeof(Options));
  if (OptRecordOpt != Val_int(0)) {
    value OptRecord = Field(OptRecordOpt, 0);
    Options.OptLevel = Int_val(Field(OptRecord, 0));
    Options.CodeModel = Int_val(Field(OptRecord, 1));
    Options.NoFramePointerElim = Int_val(Field(OptRecord, 2));
    Options.EnableFastISel = Int_val(Field(OptRecord, 3));
    Options.MCJMM = NULL;
  }

  if (LLVMCreateMCJITCompilerForModule(&MCJIT, Module_val(M), &Options,
                                       sizeof(Options), &Error))
    llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
  return to_val(MCJIT);
}

/* ExecutionEngine.t -> unit */
value llvm_ee_dispose(value EE) {
  LLVMDisposeExecutionEngine(ExecutionEngine_val(EE));
  return Val_unit;
}

/* llmodule -> ExecutionEngine.t -> unit */
value llvm_ee_add_module(value M, value EE) {
  LLVMAddModule(ExecutionEngine_val(EE), Module_val(M));
  return Val_unit;
}

/* llmodule -> ExecutionEngine.t -> llmodule */
value llvm_ee_remove_module(value M, value EE) {
  LLVMModuleRef RemovedModule;
  char *Error;
  if (LLVMRemoveModule(ExecutionEngine_val(EE), Module_val(M), &RemovedModule,
                       &Error))
    llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
  return Val_unit;
}

/* ExecutionEngine.t -> unit */
value llvm_ee_run_static_ctors(value EE) {
  LLVMRunStaticConstructors(ExecutionEngine_val(EE));
  return Val_unit;
}

/* ExecutionEngine.t -> unit */
value llvm_ee_run_static_dtors(value EE) {
  LLVMRunStaticDestructors(ExecutionEngine_val(EE));
  return Val_unit;
}

extern value llvm_alloc_data_layout(LLVMTargetDataRef TargetData);

/* ExecutionEngine.t -> Llvm_target.DataLayout.t */
value llvm_ee_get_data_layout(value EE) {
  value DataLayout;
  LLVMTargetDataRef OrigDataLayout;
  char *TargetDataCStr;

  OrigDataLayout = LLVMGetExecutionEngineTargetData(ExecutionEngine_val(EE));
  TargetDataCStr = LLVMCopyStringRepOfTargetData(OrigDataLayout);
  DataLayout = llvm_alloc_data_layout(LLVMCreateTargetData(TargetDataCStr));
  LLVMDisposeMessage(TargetDataCStr);

  return DataLayout;
}

/* Llvm.llvalue -> int64 -> llexecutionengine -> unit */
value llvm_ee_add_global_mapping(value Global, value Ptr, value EE) {
  LLVMAddGlobalMapping(ExecutionEngine_val(EE), Value_val(Global),
                       (void *)(Int64_val(Ptr)));
  return Val_unit;
}

value llvm_ee_get_global_value_address(value Name, value EE) {
  return caml_copy_int64((int64_t)LLVMGetGlobalValueAddress(
      ExecutionEngine_val(EE), String_val(Name)));
}

value llvm_ee_get_function_address(value Name, value EE) {
  return caml_copy_int64((int64_t)LLVMGetFunctionAddress(
      ExecutionEngine_val(EE), String_val(Name)));
}