1 (*===-- llvm_debuginfo.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 *===----------------------------------------------------------------------===*)
11 (** Source languages known by DWARF. *)
12 module DWARFSourceLanguageKind
: sig
24 (* New in DWARF v3: *)
34 (* New in DWARF v4: *)
36 (* New in DWARF v5: *)
54 (* Vendor extensions: *)
100 (** An opaque type to represent OR of multiple DIFlag.t. *)
102 val diflags_get
: DIFlag.t
-> lldiflags
103 (** [diflags_set f] Construct an lldiflags value with a single flag [f]. *)
105 val diflags_set
: lldiflags
-> DIFlag.t
-> lldiflags
106 (** [diflags_set fs f] Include flag [f] in [fs] and return the new value. *)
108 val diflags_test
: lldiflags
-> DIFlag.t
-> bool
109 (** [diflags_test fs f] Does [fs] contain flag [f]? *)
111 (** The kind of metadata nodes. *)
112 module MetadataKind
: sig
114 | MDStringMetadataKind
115 | ConstantAsMetadataMetadataKind
116 | LocalAsMetadataMetadataKind
117 | DistinctMDOperandPlaceholderMetadataKind
118 | MDTupleMetadataKind
119 | DILocationMetadataKind
120 | DIExpressionMetadataKind
121 | DIGlobalVariableExpressionMetadataKind
122 | GenericDINodeMetadataKind
123 | DISubrangeMetadataKind
124 | DIEnumeratorMetadataKind
125 | DIBasicTypeMetadataKind
126 | DIDerivedTypeMetadataKind
127 | DICompositeTypeMetadataKind
128 | DISubroutineTypeMetadataKind
130 | DICompileUnitMetadataKind
131 | DISubprogramMetadataKind
132 | DILexicalBlockMetadataKind
133 | DILexicalBlockFileMetadataKind
134 | DINamespaceMetadataKind
135 | DIModuleMetadataKind
136 | DITemplateTypeParameterMetadataKind
137 | DITemplateValueParameterMetadataKind
138 | DIGlobalVariableMetadataKind
139 | DILocalVariableMetadataKind
140 | DILabelMetadataKind
141 | DIObjCPropertyMetadataKind
142 | DIImportedEntityMetadataKind
143 | DIMacroMetadataKind
144 | DIMacroFileMetadataKind
145 | DICommonBlockMetadataKind
148 (** The amount of debug information to emit. *)
149 module DWARFEmissionKind
: sig
150 type t
= None
| Full
| LineTablesOnly
153 val debug_metadata_version
: unit -> int
154 (** [debug_metadata_version ()] The current debug metadata version number *)
156 val get_module_debug_metadata_version
: Llvm.llmodule
-> int
157 (** [get_module_debug_metadata_version m] Version of metadata present in [m]. *)
159 val dibuilder
: Llvm.llmodule
-> lldibuilder
160 (** [dibuilder m] Create a debug info builder for [m]. *)
162 val dibuild_finalize
: lldibuilder
-> unit
163 (** [dibuild_finalize dib] Construct any deferred debug info descriptors. *)
165 val dibuild_create_compile_unit
:
167 DWARFSourceLanguageKind.t
->
168 file_ref
:Llvm.llmetadata
->
174 DWARFEmissionKind.t
->
181 (** [dibuild_create_compile_unit] A CompileUnit provides an anchor for all
182 debugging information generated during this instance of compilation.
183 See LLVMDIBuilderCreateCompileUnit. *)
185 val dibuild_create_file
:
186 lldibuilder
-> filename
:string -> directory
:string -> Llvm.llmetadata
187 (** [dibuild_create_file] Create a file descriptor to hold debugging information
188 for a file. See LLVMDIBuilderCreateFile. *)
190 val dibuild_create_module
:
192 parent_ref
:Llvm.llmetadata
->
194 config_macros
:string ->
195 include_path
:string ->
198 (** [dibuild_create_module] Create a new descriptor for a module with the
199 specified parent scope. See LLVMDIBuilderCreateModule. *)
201 val dibuild_create_namespace
:
203 parent_ref
:Llvm.llmetadata
->
205 export_symbols
:bool ->
207 (** [dibuild_create_namespace] Create a new descriptor for a namespace with
208 the specified parent scope. See LLVMDIBuilderCreateNameSpace *)
210 val dibuild_create_function
:
212 scope
:Llvm.llmetadata
->
214 linkage_name
:string ->
215 file
:Llvm.llmetadata
->
217 ty
:Llvm.llmetadata
->
218 is_local_to_unit
:bool ->
219 is_definition
:bool ->
224 (** [dibuild_create_function] Create a new descriptor for the specified
225 subprogram. See LLVMDIBuilderCreateFunction. *)
227 val dibuild_create_lexical_block
:
229 scope
:Llvm.llmetadata
->
230 file
:Llvm.llmetadata
->
234 (** [dibuild_create_lexical_block] Create a descriptor for a lexical block with
235 the specified parent context. See LLVMDIBuilderCreateLexicalBlock *)
237 val llmetadata_null
: unit -> Llvm.llmetadata
238 (** [llmetadata_null ()] llmetadata is a wrapper around "llvm::Metadata *".
239 This function returns a nullptr valued llmetadata. For example, it
240 can be used to convey an llmetadata for "void" type. *)
242 val dibuild_create_debug_location
:
243 ?inlined_at
:Llvm.llmetadata
->
247 scope
:Llvm.llmetadata
->
249 (** [dibuild_create] Create a new DebugLocation that describes a source
250 location. See LLVMDIBuilderCreateDebugLocation *)
252 val di_location_get_line
: location
:Llvm.llmetadata
-> int
253 (** [di_location_get_line l] Get the line number of debug location [l]. *)
255 val di_location_get_column
: location
:Llvm.llmetadata
-> int
256 (** [di_location_get_column l] Get the column number of debug location [l]. *)
258 val di_location_get_scope
: location
:Llvm.llmetadata
-> Llvm.llmetadata
259 (** [di_location_get_scope l] Get the local scope associated with
260 debug location [l]. *)
262 val di_location_get_inlined_at
:
263 location
:Llvm.llmetadata
-> Llvm.llmetadata
option
264 (** [di_location_get_inlined_at l] Get the "inlined at" location associated with
265 debug location [l], if it exists. *)
267 val di_scope_get_file
: scope
:Llvm.llmetadata
-> Llvm.llmetadata
option
268 (** [di_scope_get_file l] Get the metadata of the file associated with scope [s]
271 val di_file_get_directory
: file
:Llvm.llmetadata
-> string
272 (** [di_file_get_directory f] Get the directory of file [f]. *)
274 val di_file_get_filename
: file
:Llvm.llmetadata
-> string
275 (** [di_file_get_filename f] Get the name of file [f]. *)
277 val di_file_get_source
: file
:Llvm.llmetadata
-> string
278 (** [di_file_get_source f] Get the source of file [f]. *)
280 val dibuild_get_or_create_type_array
:
281 lldibuilder
-> data
:Llvm.llmetadata array
-> Llvm.llmetadata
282 (** [dibuild_get_or_create_type_array] Create a type array.
283 See LLVMDIBuilderGetOrCreateTypeArray. *)
285 val dibuild_get_or_create_array
:
286 lldibuilder
-> data
:Llvm.llmetadata array
-> Llvm.llmetadata
287 (** [dibuild_get_or_create_array] Create an array of DI Nodes.
288 See LLVMDIBuilderGetOrCreateArray. *)
290 val dibuild_create_constant_value_expression
:
291 lldibuilder
-> int -> Llvm.llmetadata
292 (** [dibuild_create_constant_value_expression] Create a new descriptor for
293 the specified variable that does not have an address, but does have
294 a constant value. See LLVMDIBuilderCreateConstantValueExpression. *)
296 val dibuild_create_global_variable_expression
:
298 scope
:Llvm.llmetadata
->
301 file
:Llvm.llmetadata
->
303 ty
:Llvm.llmetadata
->
304 is_local_to_unit
:bool ->
305 expr
:Llvm.llmetadata
->
306 decl
:Llvm.llmetadata
->
309 (** [dibuild_create_global_variable_expression] Create a new descriptor for
310 the specified variable. See LLVMDIBuilderCreateGlobalVariableExpression. *)
312 val di_global_variable_expression_get_variable
:
313 Llvm.llmetadata
-> Llvm.llmetadata
option
314 (** [di_global_variable_expression_get_variable gve] returns the debug variable
315 of [gve], which must be a [DIGlobalVariableExpression].
316 See LLVMDIGlobalVariableExpressionGetVariable. *)
318 val di_variable_get_line
: Llvm.llmetadata
-> int
319 (** [di_variable_get_line v] returns the line number of the variable [v].
320 See LLVMDIVariableGetLine. *)
322 val di_variable_get_file
: Llvm.llmetadata
-> Llvm.llmetadata
option
323 (** [di_variable_get_file v] returns the file of the variable [v].
324 See LLVMDIVariableGetFile. *)
326 val dibuild_create_subroutine_type
:
328 file
:Llvm.llmetadata
->
329 param_types
:Llvm.llmetadata array
->
332 (** [dibuild_create_subroutine_type] Create subroutine type.
333 See LLVMDIBuilderCreateSubroutineType *)
335 val dibuild_create_enumerator
:
336 lldibuilder
-> name
:string -> value:int -> is_unsigned
:bool -> Llvm.llmetadata
337 (** [dibuild_create_enumerator] Create debugging information entry for an
338 enumerator. See LLVMDIBuilderCreateEnumerator *)
340 val dibuild_create_enumeration_type
:
342 scope
:Llvm.llmetadata
->
344 file
:Llvm.llmetadata
->
348 elements
:Llvm.llmetadata array
->
349 class_ty
:Llvm.llmetadata
->
351 (** [dibuild_create_enumeration_type] Create debugging information entry for
352 an enumeration. See LLVMDIBuilderCreateEnumerationType. *)
354 val dibuild_create_union_type
:
356 scope
:Llvm.llmetadata
->
358 file
:Llvm.llmetadata
->
363 elements
:Llvm.llmetadata array
->
364 run_time_language
:int ->
367 (** [dibuild_create_union_type] Create debugging information entry for a union.
368 See LLVMDIBuilderCreateUnionType. *)
370 val dibuild_create_array_type
:
374 ty
:Llvm.llmetadata
->
375 subscripts
:Llvm.llmetadata array
->
377 (** [dibuild_create_array_type] Create debugging information entry for an array.
378 See LLVMDIBuilderCreateArrayType. *)
380 val dibuild_create_vector_type
:
384 ty
:Llvm.llmetadata
->
385 subscripts
:Llvm.llmetadata array
->
387 (** [dibuild_create_vector_type] Create debugging information entry for a
388 vector type. See LLVMDIBuilderCreateVectorType. *)
390 val dibuild_create_unspecified_type
:
391 lldibuilder
-> name
:string -> Llvm.llmetadata
392 (** [dibuild_create_unspecified_type] Create a DWARF unspecified type. *)
394 val dibuild_create_basic_type
:
401 (** [dibuild_create_basic_type] Create debugging information entry for a basic
402 type. See LLVMDIBuilderCreateBasicType. *)
404 val dibuild_create_pointer_type
:
406 pointee_ty
:Llvm.llmetadata
->
412 (** [dibuild_create_pointer_type] Create debugging information entry for a
413 pointer. See LLVMDIBuilderCreatePointerType. *)
415 val dibuild_create_struct_type
:
417 scope
:Llvm.llmetadata
->
419 file
:Llvm.llmetadata
->
424 derived_from
:Llvm.llmetadata
->
425 elements
:Llvm.llmetadata array
->
426 DWARFSourceLanguageKind.t
->
427 vtable_holder
:Llvm.llmetadata
->
430 (** [dibuild_create_struct_type] Create debugging information entry for a
431 struct. See LLVMDIBuilderCreateStructType *)
433 val dibuild_create_member_type
:
435 scope
:Llvm.llmetadata
->
437 file
:Llvm.llmetadata
->
441 offset_in_bits
:int ->
443 ty
:Llvm.llmetadata
->
445 (** [dibuild_create_member_type] Create debugging information entry for a
446 member. See LLVMDIBuilderCreateMemberType. *)
448 val dibuild_create_static_member_type
:
450 scope
:Llvm.llmetadata
->
452 file
:Llvm.llmetadata
->
454 ty
:Llvm.llmetadata
->
456 const_val
:Llvm.llvalue
->
459 (** [dibuild_create_static_member_type] Create debugging information entry for
460 a C++ static data member. See LLVMDIBuilderCreateStaticMemberType *)
462 val dibuild_create_member_pointer_type
:
464 pointee_type
:Llvm.llmetadata
->
465 class_type
:Llvm.llmetadata
->
470 (** [dibuild_create_member_pointer_type] Create debugging information entry for
471 a pointer to member. See LLVMDIBuilderCreateMemberPointerType *)
473 val dibuild_create_object_pointer_type
:
474 lldibuilder
-> Llvm.llmetadata
-> Llvm.llmetadata
475 (** [dibuild_create_object_pointer_type dib ty] Create a uniqued DIType* clone
476 with FlagObjectPointer and FlagArtificial set. [dib] is the dibuilder
477 value and [ty] the underlying type to which this pointer points. *)
479 val dibuild_create_qualified_type
:
480 lldibuilder
-> tag
:int -> Llvm.llmetadata
-> Llvm.llmetadata
481 (** [dibuild_create_qualified_type dib tag ty] Create debugging information
482 entry for a qualified type, e.g. 'const int'. [dib] is the dibuilder value,
483 [tag] identifyies the type and [ty] is the base type. *)
485 val dibuild_create_reference_type
:
486 lldibuilder
-> tag
:int -> Llvm.llmetadata
-> Llvm.llmetadata
487 (** [dibuild_create_reference_type dib tag ty] Create debugging information
488 entry for a reference type. [dib] is the dibuilder value, [tag] identifyies
489 the type and [ty] is the base type. *)
491 val dibuild_create_null_ptr_type
: lldibuilder
-> Llvm.llmetadata
492 (** [dibuild_create_null_ptr_type dib] Create C++11 nullptr type. *)
494 val dibuild_create_typedef
:
496 ty
:Llvm.llmetadata
->
498 file
:Llvm.llmetadata
->
500 scope
:Llvm.llmetadata
->
503 (** [dibuild_create_typedef] Create debugging information entry for a typedef.
504 See LLVMDIBuilderCreateTypedef. *)
506 val dibuild_create_inheritance
:
508 ty
:Llvm.llmetadata
->
509 base_ty
:Llvm.llmetadata
->
514 (** [dibuild_create_inheritance] Create debugging information entry
515 to establish inheritance relationship between two types.
516 See LLVMDIBuilderCreateInheritance. *)
518 val dibuild_create_forward_decl
:
522 scope
:Llvm.llmetadata
->
523 file
:Llvm.llmetadata
->
528 unique_identifier
:string ->
530 (** [dibuild_create_forward_decl] Create a permanent forward-declared type.
531 See LLVMDIBuilderCreateForwardDecl. *)
533 val dibuild_create_replaceable_composite_type
:
537 scope
:Llvm.llmetadata
->
538 file
:Llvm.llmetadata
->
544 unique_identifier
:string ->
546 (** [dibuild_create_replaceable_composite_type] Create a temporary
547 forward-declared type. See LLVMDIBuilderCreateReplaceableCompositeType. *)
549 val dibuild_create_bit_field_member_type
:
551 scope
:Llvm.llmetadata
->
553 file
:Llvm.llmetadata
->
556 offset_in_bits
:int ->
557 storage_offset_in_bits
:int ->
559 ty
:Llvm.llmetadata
->
561 (** [dibuild_create_bit_field_member_type] Create debugging information entry
562 for a bit field member. See LLVMDIBuilderCreateBitFieldMemberType. *)
564 val dibuild_create_class_type
:
566 scope
:Llvm.llmetadata
->
568 file
:Llvm.llmetadata
->
572 offset_in_bits
:int ->
574 derived_from
:Llvm.llmetadata
->
575 elements
:Llvm.llmetadata array
->
576 vtable_holder
:Llvm.llmetadata
->
577 template_params_node
:Llvm.llmetadata
->
578 unique_identifier
:string ->
580 (** [dibuild_create_class_type] Create debugging information entry for a class.
581 See LLVMDIBuilderCreateClassType. *)
583 val dibuild_create_artificial_type
:
584 lldibuilder
-> ty
:Llvm.llmetadata
-> Llvm.llmetadata
585 (** [dibuild_create_artificial_type dib ty] Create a uniqued DIType* clone with
587 [dib] is the dibuilder value and [ty] the underlying type. *)
589 val di_type_get_name
: Llvm.llmetadata
-> string
590 (** [di_type_get_name m] Get the name of DIType [m]. *)
592 val di_type_get_size_in_bits
: Llvm.llmetadata
-> int
593 (** [di_type_get_size_in_bits m] Get size in bits of DIType [m]. *)
595 val di_type_get_offset_in_bits
: Llvm.llmetadata
-> int
596 (** [di_type_get_offset_in_bits m] Get offset in bits of DIType [m]. *)
598 val di_type_get_align_in_bits
: Llvm.llmetadata
-> int
599 (** [di_type_get_align_in_bits m] Get alignment in bits of DIType [m]. *)
601 val di_type_get_line
: Llvm.llmetadata
-> int
602 (** [di_type_get_line m] Get source line where DIType [m] is declared. *)
604 val di_type_get_flags
: Llvm.llmetadata
-> lldiflags
605 (** [di_type_get_flags m] Get the flags associated with DIType [m]. *)
607 val get_subprogram
: Llvm.llvalue
-> Llvm.llmetadata
option
608 (** [get_subprogram f] Get the metadata of the subprogram attached to
611 val set_subprogram
: Llvm.llvalue
-> Llvm.llmetadata
-> unit
612 (** [set_subprogram f m] Set the subprogram [m] attached to function [f]. *)
614 val di_subprogram_get_line
: Llvm.llmetadata
-> int
615 (** [di_subprogram_get_line m] Get the line associated with subprogram [m]. *)
617 val instr_get_debug_loc
: Llvm.llvalue
-> Llvm.llmetadata
option
618 (** [instr_get_debug_loc i] Get the debug location for instruction [i]. *)
620 val instr_set_debug_loc
: Llvm.llvalue
-> Llvm.llmetadata
option -> unit
621 (** [instr_set_debug_loc i mopt] If [mopt] is None location metadata of [i]
622 is cleared, Otherwise location of [i] is set to the value in [mopt]. *)
624 val get_metadata_kind
: Llvm.llmetadata
-> MetadataKind.t
625 (** [get_metadata_kind] Obtain the enumerated type of a Metadata instance. *)
627 val dibuild_create_auto_variable
:
629 scope
:Llvm.llmetadata
->
631 file
:Llvm.llmetadata
->
633 ty
:Llvm.llmetadata
->
634 always_preserve
:bool ->
638 (** [dibuild_create_auto_variable] Create a new descriptor for a
639 local auto variable. *)
641 val dibuild_create_parameter_variable
:
643 scope
:Llvm.llmetadata
->
646 file
:Llvm.llmetadata
->
648 ty
:Llvm.llmetadata
->
649 always_preserve
:bool ->
652 (** [dibuild_create_parameter_variable] Create a new descriptor for a
653 function parameter variable. *)
655 val dibuild_insert_declare_before
:
657 storage
:Llvm.llvalue
->
658 var_info
:Llvm.llmetadata
->
659 expr
:Llvm.llmetadata
->
660 location
:Llvm.llmetadata
->
661 instr
:Llvm.llvalue
->
663 (** [dibuild_insert_declare_before] Insert a new llvm.dbg.declare
664 intrinsic call before the given instruction [instr]. *)
666 val dibuild_insert_declare_at_end
:
668 storage
:Llvm.llvalue
->
669 var_info
:Llvm.llmetadata
->
670 expr
:Llvm.llmetadata
->
671 location
:Llvm.llmetadata
->
672 block
:Llvm.llbasicblock
->
674 (** [dibuild_insert_declare_at_end] Insert a new llvm.dbg.declare
675 intrinsic call at the end of basic block [block]. If [block]
676 has a terminator instruction, the intrinsic is inserted
677 before that terminator instruction. *)
679 val dibuild_expression
: lldibuilder
-> Int64.t array
-> Llvm.llmetadata
680 (** [dibuild_expression] Create a new descriptor for the specified variable
681 which has a complex address expression for its address.
682 See LLVMDIBuilderCreateExpression. *)