xref: /llvm-project/llvm/bindings/ocaml/target/llvm_target.ml (revision 30416f39be326b403e19f23da387009736483119)
1(*===-- llvm_target.ml - LLVM OCaml Interface ------------------*- OCaml -*-===*
2 *
3 * Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 * See https://llvm.org/LICENSE.txt for license information.
5 * SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 *
7 *===----------------------------------------------------------------------===*)
8
9module Endian = struct
10  type t =
11  | Big
12  | Little
13end
14
15module CodeGenOptLevel = struct
16  type t =
17  | None
18  | Less
19  | Default
20  | Aggressive
21end
22
23module RelocMode = struct
24  type t =
25  | Default
26  | Static
27  | PIC
28  | DynamicNoPIC
29end
30
31module CodeModel = struct
32  type t =
33  | Default
34  | JITDefault
35  | Small
36  | Kernel
37  | Medium
38  | Large
39end
40
41module CodeGenFileType = struct
42  type t =
43  | AssemblyFile
44  | ObjectFile
45end
46
47module GlobalISelAbortMode = struct
48  type t =
49  | Enable
50  | Disable
51  | DisableWithDiag
52end
53
54exception Error of string
55
56let () = Callback.register_exception "Llvm_target.Error" (Error "")
57
58module DataLayout = struct
59  type t
60
61  external of_string : string -> t = "llvm_datalayout_of_string"
62  external as_string : t -> string = "llvm_datalayout_as_string"
63  external byte_order : t -> Endian.t = "llvm_datalayout_byte_order"
64  external pointer_size : t -> int = "llvm_datalayout_pointer_size"
65  external intptr_type : Llvm.llcontext -> t -> Llvm.lltype
66                       = "llvm_datalayout_intptr_type"
67  external qualified_pointer_size : int -> t -> int
68                                  = "llvm_datalayout_qualified_pointer_size"
69  external qualified_intptr_type : Llvm.llcontext -> int -> t -> Llvm.lltype
70                                 = "llvm_datalayout_qualified_intptr_type"
71  external size_in_bits : Llvm.lltype -> t -> Int64.t
72                        = "llvm_datalayout_size_in_bits"
73  external store_size : Llvm.lltype -> t -> Int64.t
74                      = "llvm_datalayout_store_size"
75  external abi_size : Llvm.lltype -> t -> Int64.t
76                    = "llvm_datalayout_abi_size"
77  external abi_align : Llvm.lltype -> t -> int
78                     = "llvm_datalayout_abi_align"
79  external stack_align : Llvm.lltype -> t -> int
80                       = "llvm_datalayout_stack_align"
81  external preferred_align : Llvm.lltype -> t -> int
82                           = "llvm_datalayout_preferred_align"
83  external preferred_align_of_global : Llvm.llvalue -> t -> int
84                                   = "llvm_datalayout_preferred_align_of_global"
85  external element_at_offset : Llvm.lltype -> Int64.t -> t -> int
86                             = "llvm_datalayout_element_at_offset"
87  external offset_of_element : Llvm.lltype -> int -> t -> Int64.t
88                             = "llvm_datalayout_offset_of_element"
89end
90
91module Target = struct
92  type t
93
94  external default_triple : unit -> string = "llvm_target_default_triple"
95  external first : unit -> t option = "llvm_target_first"
96  external succ : t -> t option = "llvm_target_succ"
97  external by_name : string -> t option = "llvm_target_by_name"
98  external by_triple : string -> t = "llvm_target_by_triple"
99  external name : t -> string = "llvm_target_name"
100  external description : t -> string = "llvm_target_description"
101  external has_jit : t -> bool = "llvm_target_has_jit"
102  external has_target_machine : t -> bool = "llvm_target_has_target_machine"
103  external has_asm_backend : t -> bool = "llvm_target_has_asm_backend"
104
105  let all () =
106    let rec step elem lst =
107      match elem with
108      | Some target -> step (succ target) (target :: lst)
109      | None        -> lst
110    in
111    step (first ()) []
112end
113
114module TargetMachine = struct
115  type t
116
117  external create : triple:string -> ?cpu:string -> ?features:string ->
118                    ?level:CodeGenOptLevel.t -> ?reloc_mode:RelocMode.t ->
119                    ?code_model:CodeModel.t -> Target.t -> t
120                  = "llvm_create_targetmachine_bytecode"
121                    "llvm_create_targetmachine_native"
122  external target : t -> Target.t
123                  = "llvm_targetmachine_target"
124  external triple : t -> string
125                  = "llvm_targetmachine_triple"
126  external cpu : t -> string
127               = "llvm_targetmachine_cpu"
128  external features : t -> string
129                    = "llvm_targetmachine_features"
130  external data_layout : t -> DataLayout.t
131                       = "llvm_targetmachine_data_layout"
132  external set_verbose_asm : bool -> t -> unit
133                           = "llvm_targetmachine_set_verbose_asm"
134  external set_fast_isel : bool -> t -> unit
135                           = "llvm_targetmachine_set_fast_isel"
136  external set_global_isel : bool -> t -> unit
137                           = "llvm_targetmachine_set_global_isel"
138  external set_global_isel_abort : ?mode:GlobalISelAbortMode.t -> t -> unit
139                                 = "llvm_targetmachine_set_global_isel_abort"
140  external set_machine_outliner : bool -> t -> unit
141                                = "llvm_targetmachine_set_machine_outliner"
142  external emit_to_file : Llvm.llmodule -> CodeGenFileType.t -> string ->
143                          t -> unit
144                        = "llvm_targetmachine_emit_to_file"
145  external emit_to_memory_buffer : Llvm.llmodule -> CodeGenFileType.t ->
146                                   t -> Llvm.llmemorybuffer
147                                 = "llvm_targetmachine_emit_to_memory_buffer"
148end
149