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