Home | History | Annotate | Download | only in target

Lines Matching refs:LLVM

1 (*===-- llvm_target.mli - LLVM OCaml Interface -----------------*- OCaml -*-===*
3 * The LLVM Compiler Infrastructure
12 This interface provides an OCaml API for LLVM target information,
63 See the constructor [llvm::DataLayout::DataLayout]. *)
67 See the method [llvm::DataLayout::getStringRepresentation]. *)
72 See the method [llvm::PassManagerBase::add]. *)
73 val add_to_pass_manager : [<Llvm.PassManager.any] Llvm.PassManager.t ->
78 See the method [llvm::DataLayout::isLittleEndian]. *)
82 See the method [llvm::DataLayout::getPointerSize]. *)
86 See the method [llvm::DataLayout::getIntPtrType]. *)
87 val intptr_type : Llvm.llcontext -> t -> Llvm.lltype
90 See the method [llvm::DataLayout::getPointerSize]. *)
95 See the method [llvm::DataLayout::getIntPtrType]. *)
96 val qualified_intptr_type : Llvm.llcontext -> int -> t -> Llvm.lltype
99 See the method [llvm::DataLayout::getTypeSizeInBits]. *)
100 val size_in_bits : Llvm.lltype -> t -> Int64.t
103 See the method [llvm::DataLayout::getTypeStoreSize]. *)
104 val store_size : Llvm.lltype -> t -> Int64.t
107 See the method [llvm::DataLayout::getTypeAllocSize]. *)
108 val abi_size : Llvm.lltype -> t -> Int64.t
111 See the method [llvm::DataLayout::getTypeABISize]. *)
112 val abi_align : Llvm.lltype -> t -> int
115 See the method [llvm::DataLayout::getTypeABISize]. *)
116 val stack_align : Llvm.lltype -> t -> int
119 See the method [llvm::DataLayout::getTypeABISize]. *)
120 val preferred_align : Llvm.lltype -> t -> int
123 a target. See the method [llvm::DataLayout::getPreferredAlignment]. *)
124 val preferred_align_of_global : Llvm.llvalue -> t -> int
127 See the method [llvm::StructLayout::getElementContainingOffset]. *)
128 val element_at_offset : Llvm.lltype -> Int64.t -> t -> int
131 See the method [llvm::StructLayout::getElementContainingOffset]. *)
132 val offset_of_element : Llvm.lltype -> int -> t -> Int64.t
163 (** Returns the name of a target. See [llvm::Target::getName]. *)
167 See [llvm::Target::getDescription]. *)
187 See [llvm::Target::createTargetMachine]. *)
196 [llvm::TargetMachine::getTriple]. *)
200 [llvm::TargetMachine::getCPU]. *)
204 [llvm::TargetMachine::getFeatureString]. *)
211 See [llvm::TargetMachine::addAnalysisPasses]. *)
212 val add_analysis_passes : [< Llvm.PassManager.any ] Llvm.PassManager.t -> t -> unit
215 See [llvm::TargetMachine::setAsmVerbosity]. *)
220 val emit_to_file : Llvm.llmodule -> CodeGenFileType.t -> string -> t -> unit
224 val emit_to_memory_buffer : Llvm.llmodule -> CodeGenFileType.t -> t ->
225 Llvm.llmemorybuffer