summaryrefslogtreecommitdiff
path: root/bindings/ocaml/llvm/llvm.mli
diff options
context:
space:
mode:
Diffstat (limited to 'bindings/ocaml/llvm/llvm.mli')
-rw-r--r--bindings/ocaml/llvm/llvm.mli28
1 files changed, 27 insertions, 1 deletions
diff --git a/bindings/ocaml/llvm/llvm.mli b/bindings/ocaml/llvm/llvm.mli
index 541c35a2a22..5d3ce958264 100644
--- a/bindings/ocaml/llvm/llvm.mli
+++ b/bindings/ocaml/llvm/llvm.mli
@@ -15,7 +15,7 @@
(** {6 Abstract types}
- These abstract types correlate directly to the LLVM VMCore classes. *)
+ These abstract types correlate directly to the LLVMCore classes. *)
(** The top-level container for all LLVM global data. See the
[llvm::LLVMContext] class. *)
@@ -352,6 +352,16 @@ module ValueKind : sig
| Instruction of Opcode.t
end
+(** The kind of [Diagnostic], the result of [Diagnostic.severity d].
+ See [llvm::DiagnosticSeverity]. *)
+module DiagnosticSeverity : sig
+ type t =
+ | Error
+ | Warning
+ | Remark
+ | Note
+end
+
(** {6 Iteration} *)
@@ -398,6 +408,22 @@ val reset_fatal_error_handler : unit -> unit
See the function [llvm::cl::ParseCommandLineOptions()]. *)
val parse_command_line_options : ?overview:string -> string array -> unit
+(** {6 Context error handling} *)
+
+module Diagnostic : sig
+ type t
+
+ (** [description d] returns a textual description of [d]. *)
+ val description : t -> string
+
+ (** [severity d] returns the severity of [d]. *)
+ val severity : t -> DiagnosticSeverity.t
+end
+
+(** [set_diagnostic_handler c h] set the diagnostic handler of [c] to [h].
+ See the method [llvm::LLVMContext::setDiagnosticHandler]. *)
+val set_diagnostic_handler : llcontext -> (Diagnostic.t -> unit) option -> unit
+
(** {6 Contexts} *)
(** [create_context ()] creates a context for storing the "global" state in