[NFC][Py Reformat] Added more commits to .git-blame-ignore-revs
[llvm-project.git] / llvm / bindings / ocaml / target / llvm_target.mli
blob56ecb2d908dd37473c8f86678a0c8b0d08dc7e8c
1 (*===-- llvm_target.mli - LLVM OCaml Interface -----------------*- OCaml -*-===*
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
7 *===----------------------------------------------------------------------===*)
9 (** Target Information.
11 This interface provides an OCaml API for LLVM target information,
12 the classes in the Target library. *)
14 module Endian : sig
15 type t =
16 | Big
17 | Little
18 end
20 module CodeGenOptLevel : sig
21 type t =
22 | None
23 | Less
24 | Default
25 | Aggressive
26 end
28 module RelocMode : sig
29 type t =
30 | Default
31 | Static
32 | PIC
33 | DynamicNoPIC
34 end
36 module CodeModel : sig
37 type t =
38 | Default
39 | JITDefault
40 | Small
41 | Kernel
42 | Medium
43 | Large
44 end
46 module CodeGenFileType : sig
47 type t =
48 | AssemblyFile
49 | ObjectFile
50 end
52 (** {6 Exceptions} *)
54 exception Error of string
56 (** {6 Data Layout} *)
58 module DataLayout : sig
59 type t
61 (** [of_string rep] parses the data layout string representation [rep].
62 See the constructor [llvm::DataLayout::DataLayout]. *)
63 val of_string : string -> t
65 (** [as_string dl] is the string representation of the data layout [dl].
66 See the method [llvm::DataLayout::getStringRepresentation]. *)
67 val as_string : t -> string
69 (** Returns the byte order of a target, either [Endian.Big] or
70 [Endian.Little].
71 See the method [llvm::DataLayout::isLittleEndian]. *)
72 val byte_order : t -> Endian.t
74 (** Returns the pointer size in bytes for a target.
75 See the method [llvm::DataLayout::getPointerSize]. *)
76 val pointer_size : t -> int
78 (** Returns the integer type that is the same size as a pointer on a target.
79 See the method [llvm::DataLayout::getIntPtrType]. *)
80 val intptr_type : Llvm.llcontext -> t -> Llvm.lltype
82 (** Returns the pointer size in bytes for a target in a given address space.
83 See the method [llvm::DataLayout::getPointerSize]. *)
84 val qualified_pointer_size : int -> t -> int
86 (** Returns the integer type that is the same size as a pointer on a target
87 in a given address space.
88 See the method [llvm::DataLayout::getIntPtrType]. *)
89 val qualified_intptr_type : Llvm.llcontext -> int -> t -> Llvm.lltype
91 (** Computes the size of a type in bits for a target.
92 See the method [llvm::DataLayout::getTypeSizeInBits]. *)
93 val size_in_bits : Llvm.lltype -> t -> Int64.t
95 (** Computes the storage size of a type in bytes for a target.
96 See the method [llvm::DataLayout::getTypeStoreSize]. *)
97 val store_size : Llvm.lltype -> t -> Int64.t
99 (** Computes the ABI size of a type in bytes for a target.
100 See the method [llvm::DataLayout::getTypeAllocSize]. *)
101 val abi_size : Llvm.lltype -> t -> Int64.t
103 (** Computes the ABI alignment of a type in bytes for a target.
104 See the method [llvm::DataLayout::getTypeABISize]. *)
105 val abi_align : Llvm.lltype -> t -> int
107 (** Computes the call frame alignment of a type in bytes for a target.
108 See the method [llvm::DataLayout::getTypeABISize]. *)
109 val stack_align : Llvm.lltype -> t -> int
111 (** Computes the preferred alignment of a type in bytes for a target.
112 See the method [llvm::DataLayout::getTypeABISize]. *)
113 val preferred_align : Llvm.lltype -> t -> int
115 (** Computes the preferred alignment of a global variable in bytes for
116 a target. See the method [llvm::DataLayout::getPreferredAlignment]. *)
117 val preferred_align_of_global : Llvm.llvalue -> t -> int
119 (** Computes the structure element that contains the byte offset for a target.
120 See the method [llvm::StructLayout::getElementContainingOffset]. *)
121 val element_at_offset : Llvm.lltype -> Int64.t -> t -> int
123 (** Computes the byte offset of the indexed struct element for a target.
124 See the method [llvm::StructLayout::getElementContainingOffset]. *)
125 val offset_of_element : Llvm.lltype -> int -> t -> Int64.t
128 (** {6 Target} *)
130 module Target : sig
131 type t
133 (** [default_triple ()] returns the default target triple for current
134 platform. *)
135 val default_triple : unit -> string
137 (** [first ()] returns the first target in the registered targets
138 list, or [None]. *)
139 val first : unit -> t option
141 (** [succ t] returns the next target after [t], or [None]
142 if [t] was the last target. *)
143 val succ : t -> t option
145 (** [all ()] returns a list of known targets. *)
146 val all : unit -> t list
148 (** [by_name name] returns [Some t] if a target [t] named [name] is
149 registered, or [None] otherwise. *)
150 val by_name : string -> t option
152 (** [by_triple triple] returns a target for a triple [triple], or raises
153 [Error] if [triple] does not correspond to a registered target. *)
154 val by_triple : string -> t
156 (** Returns the name of a target. See [llvm::Target::getName]. *)
157 val name : t -> string
159 (** Returns the description of a target.
160 See [llvm::Target::getDescription]. *)
161 val description : t -> string
163 (** Returns [true] if the target has a JIT. *)
164 val has_jit : t -> bool
166 (** Returns [true] if the target has a target machine associated. *)
167 val has_target_machine : t -> bool
169 (** Returns [true] if the target has an ASM backend (required for
170 emitting output). *)
171 val has_asm_backend : t -> bool
174 (** {6 Target Machine} *)
176 module TargetMachine : sig
177 type t
179 (** Creates a new target machine.
180 See [llvm::Target::createTargetMachine]. *)
181 val create : triple:string -> ?cpu:string -> ?features:string ->
182 ?level:CodeGenOptLevel.t -> ?reloc_mode:RelocMode.t ->
183 ?code_model:CodeModel.t -> Target.t -> t
185 (** Returns the Target used in a TargetMachine *)
186 val target : t -> Target.t
188 (** Returns the triple used while creating this target machine. See
189 [llvm::TargetMachine::getTriple]. *)
190 val triple : t -> string
192 (** Returns the CPU used while creating this target machine. See
193 [llvm::TargetMachine::getCPU]. *)
194 val cpu : t -> string
196 (** Returns the data layout of this target machine. *)
197 val data_layout : t -> DataLayout.t
199 (** Returns the feature string used while creating this target machine. See
200 [llvm::TargetMachine::getFeatureString]. *)
201 val features : t -> string
203 (** Sets the assembly verbosity of this target machine.
204 See [llvm::TargetMachine::setAsmVerbosity]. *)
205 val set_verbose_asm : bool -> t -> unit
207 (** Emits assembly or object data for the given module to the given
208 file or raise [Error]. *)
209 val emit_to_file : Llvm.llmodule -> CodeGenFileType.t -> string -> t -> unit
211 (** Emits assembly or object data for the given module to a fresh memory
212 buffer or raise [Error]. *)
213 val emit_to_memory_buffer : Llvm.llmodule -> CodeGenFileType.t -> t ->
214 Llvm.llmemorybuffer