Skip to content

Commit

Permalink
Introduce a versioned API for Alcotest V1
Browse files Browse the repository at this point in the history
  • Loading branch information
craigfe committed May 6, 2021
1 parent ddd288a commit b7e8120
Show file tree
Hide file tree
Showing 17 changed files with 198 additions and 164 deletions.
10 changes: 10 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,13 @@
### Unreleased

- Introduce an `Alcotest.V1` module that aliases the existing `Alcotest` API and
provides a stability guarantee over major version changes. (#306, @CraigFe)

- Renamed some less frequently used modules used by the test backends:
- `Alcotest.Unix` -> `Alcotest.Unix_platform`
- `Alcotest_engine.{Cli,Core,Test}` -> `Alcotest_engine.V1.{Cli,Core,Test}`
(#306, @CraigFe)

### 1.4.0 (2021-04-15)

- Add `?here` and `?pos` arguments to the test assertion functions. These can be
Expand Down
4 changes: 2 additions & 2 deletions src/alcotest-async/alcotest_async.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@ open Async_kernel
open Async_unix

module Tester =
Alcotest_engine.Cli.Make
(Alcotest.Unix)
Alcotest_engine.V1.Cli.Make
(Alcotest.Unix_platform)
(struct
include Deferred

Expand Down
2 changes: 1 addition & 1 deletion src/alcotest-async/alcotest_async.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
(** [Alcotest_async] enables testing functions which return an Async deferred.
{!run} returns a deferred which will run the tests when scheduled. *)

include Alcotest_engine.Cli.S with type return = unit Async_kernel.Deferred.t
include Alcotest_engine.V1.Cli.S with type return = unit Async_kernel.Deferred.t

val test_case :
?timeout:Core_kernel.Time.Span.t ->
Expand Down
9 changes: 6 additions & 3 deletions src/alcotest-engine/alcotest_engine.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
module Test = Test
module Core = Core
module Cli = Cli
module V1 = struct
module Test = Test
module Core = Core.V1
module Cli = Cli.V1
end

module Monad = Monad
module Platform = Platform

Expand Down
30 changes: 17 additions & 13 deletions src/alcotest-engine/alcotest_engine.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,24 +20,28 @@
to defined tests. The platform-specific runners for these tests are in
[alcotest], [alcotest-lwt], [alcotest-async] and [alcotest-mirage]. *)

(** {1 Assert functions} *)
module V1 : sig
(** Version 1 of the user-facing Alcotest API. *)

module Test = Test
(** {1 Assert functions} *)

(** {1 Monadic test runners} *)
module Test = Test

(** These modules provide the ability to run tests inside a concurrency monad:
that is, to sequence test cases of type ['a -> unit m] into a computation of
type ['a -> unit m] (for some concurrency monad [m]) with can then be
scheduled in a main event loop. For tests using [Lwt.t] or
[Async_kernel.Deferred.t], use the [Alcotest_lwt] and [Alcotest_async]
packages directly. *)
(** {1 Monadic test runners} *)

module Core = Core
(** Defines monadic test runners {i without} command-line interfaces. *)
(** These modules provide the ability to run tests inside a concurrency monad:
that is, to sequence test cases of type ['a -> unit m] into a computation
of type ['a -> unit m] (for some concurrency monad [m]) with can then be
scheduled in a main event loop. For tests using [Lwt.t] or
[Async_kernel.Deferred.t], use the [Alcotest_lwt] and [Alcotest_async]
packages directly. *)

module Cli = Cli
(** Wraps {!Core} to provide a command-line interface. *)
module Core = Core.V1
(** Defines monadic test runners {i without} command-line interfaces. *)

module Cli = Cli.V1
(** Wraps {!Core} to provide a command-line interface. *)
end

module Monad = Monad
(** Monad signatures for use with {!Core} and {!Cli}. *)
Expand Down
11 changes: 9 additions & 2 deletions src/alcotest-engine/cli.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module IntSet = Set.Make (struct
end)

module type S = sig
include Core.S
include Core.V1.S

val run :
(?argv:string array -> string -> unit test list -> return) with_options
Expand Down Expand Up @@ -55,7 +55,7 @@ struct
+ 4. if the flag/option is passed to [run] directly, use that;
+ 5. otherwise, use the default behaviour set by {!Alcotest.Core}. *)

module C = Core.Make (P) (M)
module C = Core.V1.Make (P) (M)
include C
module P = P (M)
open Cmdliner_syntax
Expand Down Expand Up @@ -146,3 +146,10 @@ struct
Config.User.kcreate (fun config ?argv name tl ->
run_with_args' config ~argv name (Term.pure ()) tl)
end

module V1 = struct
module type S = S
module type MAKER = MAKER

module Make = Make
end
69 changes: 36 additions & 33 deletions src/alcotest-engine/cli.mli
Original file line number Diff line number Diff line change
Expand Up @@ -25,42 +25,45 @@

open! Import

module type S = sig
include Core.S
(** @inline *)
module V1 : sig
module type S = sig
include Core.V1.S
(** @inline *)

val run :
(?argv:string array -> string -> unit test list -> return) with_options
(** [run n t] runs the test suite [t]. [n] is the name of the tested library.
val run :
(?argv:string array -> string -> unit test list -> return) with_options
(** [run n t] runs the test suite [t]. [n] is the name of the tested
library.
The optional argument [and_exit] controls what happens when the function
ends. By default, [and_exit] is set, which makes the function exit with
[0] if everything is fine or [1] if there is an issue. If [and_exit] is
[false], then the function raises [Test_error] on error.
The optional argument [and_exit] controls what happens when the function
ends. By default, [and_exit] is set, which makes the function exit with
[0] if everything is fine or [1] if there is an issue. If [and_exit] is
[false], then the function raises [Test_error] on error.
The optional argument [argv] specifies command line arguments sent to
alcotest like ["--json"], ["--verbose"], etc. Note that this array will be
treated like a regular [Sys.argv], so the array must have at least one
element, and the first element will be treated as if it was the command
name and thus ignored for the purposes of option processing. So
[~argv:\[||\]] is an error, [~argv:\[| "--verbose" |\]] will have no
effect, and [~argv:\[| "ignored"; "--verbose" |\]] will successfully pass
the verbose option. *)
The optional argument [argv] specifies command line arguments sent to
alcotest like ["--json"], ["--verbose"], etc. Note that this array will
be treated like a regular [Sys.argv], so the array must have at least
one element, and the first element will be treated as if it was the
command name and thus ignored for the purposes of option processing. So
[~argv:\[||\]] is an error, [~argv:\[| "--verbose" |\]] will have no
effect, and [~argv:\[| "ignored"; "--verbose" |\]] will successfully
pass the verbose option. *)

val run_with_args :
(?argv:string array ->
string ->
'a Cmdliner.Term.t ->
'a test list ->
return)
with_options
(** [run_with_args n a t] Similar to [run a t] but take an extra argument [a].
Every test function will receive as argument the evaluation of the
[Cmdliner] term [a]: this is useful to configure the test behaviors using
the CLI. *)
end
val run_with_args :
(?argv:string array ->
string ->
'a Cmdliner.Term.t ->
'a test list ->
return)
with_options
(** [run_with_args n a t] Similar to [run a t] but take an extra argument
[a]. Every test function will receive as argument the evaluation of the
[Cmdliner] term [a]: this is useful to configure the test behaviors
using the CLI. *)
end

module type MAKER = functor (P : Platform.MAKER) (M : Monad.S) ->
S with type return = unit M.t
module type MAKER = functor (P : Platform.MAKER) (M : Monad.S) ->
S with type return = unit M.t

module Make (P : Platform.MAKER) (M : Monad.S) : S with type return = unit M.t
module Make (P : Platform.MAKER) (M : Monad.S) : S with type return = unit M.t
end
5 changes: 5 additions & 0 deletions src/alcotest-engine/core.ml
Original file line number Diff line number Diff line change
Expand Up @@ -415,3 +415,8 @@ module Make (P : Platform.MAKER) (M : Monad.S) = struct

let run = Config.User.kcreate run'
end

module V1 = struct
include V1_types
module Make = Make
end
162 changes: 83 additions & 79 deletions src/alcotest-engine/core_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,88 +17,92 @@

open! Import

module type S = sig
type return
(** The return type of each test case run by Alcotest. For the standard
{!Alcotest} module, [return = unit]. The concurrent backends
[Alcotest_lwt] and [Alcotest_async] set [return = unit Lwt.t] and
[return = Async_kernel.Deferred.t] respectively. *)

type speed_level = [ `Quick | `Slow ]
(** Speed level of a test. Tests marked as [`Quick] are always run. Tests
marked as [`Slow] are skipped when the `-q` flag is passed. *)

type 'a test_case = string * speed_level * ('a -> return)
(** A test case is a UTF-8 encoded documentation string, a speed level and a
function to execute. Typically, the testing function calls the helper
functions provided below (such as [check] and [fail]). *)

exception Test_error
(** The exception return by {!run} in case of errors. *)

val test_case : string -> speed_level -> ('a -> return) -> 'a test_case
(** [test_case n s f] is the test case [n] running at speed [s] using the
function [f]. *)

type 'a test = string * 'a test_case list
(** A test is a UTF-8 encoded name and a list of test cases. The name can be
used for filtering which tests to run on the CLI. *)

val list_tests : 'a test list -> return
(** Print all of the test cases in a human-readable form *)

type 'a with_options =
?and_exit:bool ->
?verbose:bool ->
?compact:bool ->
?tail_errors:[ `Unlimited | `Limit of int ] ->
?quick_only:bool ->
?show_errors:bool ->
?json:bool ->
?filter:Re.re option * int list option ->
?log_dir:string ->
?bail:bool ->
'a
(** The various options taken by the tests runners {!run} and
{!run_with_args}:
- [and_exit] (default [true]). Once the tests have completed, exit with
return code [0] if all tests passed, otherwise [1].
- [verbose] (default [false]). Display the test std.out and std.err
(rather than redirecting to a log file).
- [compact] (default [false]). Compact the output of the tests.
- [tail_errors] (default unlimited). Show only the last N lines of output
of failed tests.
- [quick_only] (default [false]). Don't run tests with the
{{!Core.speed_level} [`Slow] speed level}.
- [show_errors] (default [false]). Display the test errors.
- [json] (default [false]). Print test results in a JSON-compatible
format.
- [log_dir] (default ["$PWD/_build/_tests/"]). The directory in which to
log the output of the tests (if [verbose] is not set).
- [bail] (default [false]). If true, stop running the tests after the
first failure. *)

val run : (string -> unit test list -> return) with_options
val run_with_args : (string -> 'a -> 'a test list -> return) with_options
end

module type MAKER = functor (P : Platform.MAKER) (M : Monad.S) -> sig
include S with type return = unit M.t

val run' : Config.User.t -> string -> unit test list -> return
val run_with_args' : Config.User.t -> string -> 'a -> 'a test list -> return
module V1_types = struct
module type S = sig
type return
(** The return type of each test case run by Alcotest. For the standard
{!Alcotest} module, [return = unit]. The concurrent backends
[Alcotest_lwt] and [Alcotest_async] set [return = unit Lwt.t] and
[return = Async_kernel.Deferred.t] respectively. *)

type speed_level = [ `Quick | `Slow ]
(** Speed level of a test. Tests marked as [`Quick] are always run. Tests
marked as [`Slow] are skipped when the `-q` flag is passed. *)

type 'a test_case = string * speed_level * ('a -> return)
(** A test case is a UTF-8 encoded documentation string, a speed level and a
function to execute. Typically, the testing function calls the helper
functions provided below (such as [check] and [fail]). *)

exception Test_error
(** The exception return by {!run} in case of errors. *)

val test_case : string -> speed_level -> ('a -> return) -> 'a test_case
(** [test_case n s f] is the test case [n] running at speed [s] using the
function [f]. *)

type 'a test = string * 'a test_case list
(** A test is a UTF-8 encoded name and a list of test cases. The name can be
used for filtering which tests to run on the CLI. *)

val list_tests : 'a test list -> return
(** Print all of the test cases in a human-readable form *)

type 'a with_options =
?and_exit:bool ->
?verbose:bool ->
?compact:bool ->
?tail_errors:[ `Unlimited | `Limit of int ] ->
?quick_only:bool ->
?show_errors:bool ->
?json:bool ->
?filter:Re.re option * int list option ->
?log_dir:string ->
?bail:bool ->
'a
(** The various options taken by the tests runners {!run} and
{!run_with_args}:
- [and_exit] (default [true]). Once the tests have completed, exit with
return code [0] if all tests passed, otherwise [1].
- [verbose] (default [false]). Display the test std.out and std.err
(rather than redirecting to a log file).
- [compact] (default [false]). Compact the output of the tests.
- [tail_errors] (default unlimited). Show only the last N lines of
output of failed tests.
- [quick_only] (default [false]). Don't run tests with the
{{!Core.speed_level} [`Slow] speed level}.
- [show_errors] (default [false]). Display the test errors.
- [json] (default [false]). Print test results in a JSON-compatible
format.
- [log_dir] (default ["$PWD/_build/_tests/"]). The directory in which to
log the output of the tests (if [verbose] is not set).
- [bail] (default [false]). If true, stop running the tests after the
first failure. *)

val run : (string -> unit test list -> return) with_options
val run_with_args : (string -> 'a -> 'a test list -> return) with_options
end

module type MAKER = functor (P : Platform.MAKER) (M : Monad.S) -> sig
include S with type return = unit M.t

val run' : Config.User.t -> string -> unit test list -> return
val run_with_args' : Config.User.t -> string -> 'a -> 'a test list -> return
end
end

module type Core = sig
module type S = S
module type MAKER = MAKER

exception Check_error of unit Fmt.t

module Make : MAKER
(** Functor for building a tester that sequences tests of type
[('a -> unit M.t)] within a given concurrency monad [M.t]. The [run] and
[run_with_args] functions must be scheduled in a global event loop.
Intended for use by the {!Alcotest_lwt} and {!Alcotest_async} backends. *)
module V1 : sig
module type S = V1_types.S
module type MAKER = V1_types.MAKER

module Make : MAKER
(** Functor for building a tester that sequences tests of type
[('a -> unit M.t)] within a given concurrency monad [M.t]. The [run] and
[run_with_args] functions must be scheduled in a global event loop.
Intended for use by the {!Alcotest_lwt} and {!Alcotest_async} backends. *)
end
end
2 changes: 1 addition & 1 deletion src/alcotest-lwt/alcotest_lwt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
*)

module Tester = Alcotest_engine.Cli.Make (Alcotest.Unix) (Lwt)
module Tester = Alcotest_engine.V1.Cli.Make (Alcotest.Unix_platform) (Lwt)
include Tester

let test_case_sync n s f = test_case n s (fun x -> Lwt.return (f x))
Expand Down
2 changes: 1 addition & 1 deletion src/alcotest-lwt/alcotest_lwt.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
returns a promise that runs the tests when scheduled, catching any
asynchronous exceptions thrown by the tests. *)

include Alcotest_engine.Cli.S with type return = unit Lwt.t
include Alcotest_engine.V1.Cli.S with type return = unit Lwt.t

val test_case :
string ->
Expand Down
Loading

0 comments on commit b7e8120

Please sign in to comment.