X-Git-Url: http://plrg.eecs.uci.edu/git/?p=oota-llvm.git;a=blobdiff_plain;f=bindings%2Focaml%2Fllvm%2Fllvm.ml;h=567fa2fc9d906669ec0ecff277d07b8a9fc0834d;hp=0c434afb34a25d6dd7216f43429341ae2e5ffd53;hb=e0129b55d24b9aa4539683378a60a4d51535ebce;hpb=0947d0e38ba18b32e8eb2b76009d558bc4b2346e diff --git a/bindings/ocaml/llvm/llvm.ml b/bindings/ocaml/llvm/llvm.ml index 0c434afb34a..567fa2fc9d9 100644 --- a/bindings/ocaml/llvm/llvm.ml +++ b/bindings/ocaml/llvm/llvm.ml @@ -1,4 +1,4 @@ -(*===-- llvm/llvm.ml - LLVM Ocaml Interface --------------------------------===* +(*===-- llvm/llvm.ml - LLVM OCaml Interface -------------------------------===* * * The LLVM Compiler Infrastructure * @@ -278,8 +278,7 @@ end exception IoError of string -external register_exns : exn -> unit = "llvm_register_core_exns" -let _ = register_exns (IoError "") +let () = Callback.register_exception "Llvm.IoError" (IoError "") external install_fatal_error_handler : (string -> unit) -> unit = "llvm_install_fatal_error_handler" @@ -287,6 +286,8 @@ external reset_fatal_error_handler : unit -> unit = "llvm_reset_fatal_error_handler" external enable_pretty_stacktrace : unit -> unit = "llvm_enable_pretty_stacktrace" +external parse_command_line_options : ?overview:string -> string array -> unit + = "llvm_parse_command_line_options" type ('a, 'b) llpos = | At_end of 'a @@ -1026,6 +1027,63 @@ external set_tail_call : bool -> llvalue -> unit = "llvm_set_tail_call" external is_volatile : llvalue -> bool = "llvm_is_volatile" external set_volatile : bool -> llvalue -> unit = "llvm_set_volatile" +(*--... Operations on terminators ..........................................--*) + +let is_terminator llv = + let open ValueKind in + let open Opcode in + match classify_value llv with + | Instruction (Br | IndirectBr | Invoke | Resume | Ret | Switch | Unreachable) + -> true + | _ -> false + +external successor : llvalue -> int -> llbasicblock = "llvm_successor" +external set_successor : llvalue -> int -> llbasicblock -> unit + = "llvm_set_successor" +external num_successors : llvalue -> int = "llvm_num_successors" + +let successors llv = + if not (is_terminator llv) then + raise (Invalid_argument "Llvm.successors can only be used on terminators") + else + Array.init (num_successors llv) (successor llv) + +let iter_successors f llv = + if not (is_terminator llv) then + raise (Invalid_argument "Llvm.iter_successors can only be used on terminators") + else + for i = 0 to num_successors llv - 1 do + f (successor llv i) + done + +let fold_successors f llv z = + if not (is_terminator llv) then + raise (Invalid_argument "Llvm.fold_successors can only be used on terminators") + else + let n = num_successors llv in + let rec aux i acc = + if i >= n then acc + else begin + let llb = successor llv i in + aux (i+1) (f llb acc) + end + in aux 0 z + + +(*--... Operations on branches .............................................--*) +external condition : llvalue -> llvalue = "llvm_condition" +external set_condition : llvalue -> llvalue -> unit + = "llvm_set_condition" +external is_conditional : llvalue -> bool = "llvm_is_conditional" + +let get_branch llv = + if classify_value llv <> ValueKind.Instruction Opcode.Br then + None + else if is_conditional llv then + Some (`Conditional (condition llv, successor llv 0, successor llv 1)) + else + Some (`Unconditional (successor llv 0)) + (*--... Operations on phi nodes ............................................--*) external add_incoming : (llvalue * llbasicblock) -> llvalue -> unit = "llvm_add_incoming"