• en

Module OUnitTest

exception Skip of string
exception Todo of string
exception OUnit_failure of string
type node =
| ListItem of int
| Label of string
See OUnit.mli.
type path = node list
See OUnit.mli.
type backtrace = string option
See OUnit2.mli.
type test_length =
| Immediate
| Short
| Long
| Huge
| Custom_length of float
type result =
| RSuccess
| RFailure of string * OUnitLogger.position option * backtrace
| RError of string * backtrace
| RSkip of string
| RTodo of string
| RTimeout of test_length
See OUnit.mli.
type result_full = (path * result * OUnitLogger.position option)
type result_list = result_full list
type ctxt = {
conf : OUnitConf.conf;
logger : (path, result) OUnitLogger.logger;
path : path;
test_logger : result OUnitLogger.Test.t;
tear_down : ctxt -> unit list;
tear_down_mutex : OUnitShared.Mutex.t;
non_fatal : result_full list Pervasives.ref;
non_fatal_mutex : OUnitShared.Mutex.t;
}
type log_event_t = (path, result) OUnitLogger.log_event_t
type logger = (path, result) OUnitLogger.logger
type test_fun = ctxt -> unit
type test =
| TestCase of test_length * test_fun
| TestList of test list
| TestLabel of string * test
val delay_of_length : test_length -> float
val get_shard_id : ctxt -> string
val section_ctxt : ctxt -> ctxt -> 'a -> 'a
val with_ctxt : OUnitConf.conf -> (path, result) OUnitLogger.logger -> OUnitShared.shared -> result_full list Pervasives.ref -> path -> ctxt -> 'a -> 'a
val standard_modules : string list
val result_full_of_exception : ctxt -> exn -> (path * result * OUnitLogger.position option)
val report_result_full : ctxt -> (path * result * 'a) -> (path * result * 'a)
val non_fatal : ctxt -> ctxt -> unit -> unit
val (>:) : string -> test -> test
val (>::) : string -> test_fun -> test
val (>:::) : string -> test list -> test
val test_decorate : test_fun -> test_fun -> test -> test
val test_case_count : test -> int
val string_of_node : node -> string
module Path : sig
type t = path
val compare : 'a -> 'a -> int
val to_string : node list -> string
end
module MapPath : sig
type key = Path.t
type 'a t = 'a Map.Make(Path).t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge : key -> 'a option -> 'b option -> 'c option -> 'a t -> 'b t -> 'c t
val compare : 'a -> 'a -> int -> 'a t -> 'a t -> int
val equal : 'a -> 'a -> bool -> 'a t -> 'a t -> bool
val iter : key -> 'a -> unit -> 'a t -> unit
val fold : key -> 'a -> 'b -> 'b -> 'a t -> 'b -> 'b
val for_all : key -> 'a -> bool -> 'a t -> bool
val exists : key -> 'a -> bool -> 'a t -> bool
val filter : key -> 'a -> bool -> 'a t -> 'a t
val partition : key -> 'a -> bool -> 'a t -> ('a t * 'a t)
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> (key * 'a)
val max_binding : 'a t -> (key * 'a)
val choose : 'a t -> (key * 'a)
val split : key -> 'a t -> ('a t * 'a option * 'a t)
val find : key -> 'a t -> 'a
val map : 'a -> 'b -> 'a t -> 'b t
val mapi : key -> 'a -> 'b -> 'a t -> 'b t
end
val string_of_path : node list -> string
val test_case_paths : test -> node list list
module SetTestPath : sig
type elt = String.t
type t = Set.Make(String).t
val empty : t
val is_empty : t -> bool
val mem : elt -> t -> bool
val add : elt -> t -> t
val singleton : elt -> t
val remove : elt -> t -> t
val union : t -> t -> t
val inter : t -> t -> t
val diff : t -> t -> t
val compare : t -> t -> int
val equal : t -> t -> bool
val subset : t -> t -> bool
val iter : elt -> unit -> t -> unit
val fold : elt -> 'a -> 'a -> t -> 'a -> 'a
val for_all : elt -> bool -> t -> bool
val exists : elt -> bool -> t -> bool
val filter : elt -> bool -> t -> t
val partition : elt -> bool -> t -> (t * t)
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val max_elt : t -> elt
val choose : t -> elt
val split : elt -> t -> (t * bool * t)
val find : elt -> t -> elt
val of_list : elt list -> t
end
val test_filter : ?skip:bool -> SetTestPath.elt list -> test -> test option