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