-
Notifications
You must be signed in to change notification settings - Fork 413
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
# Problem The problem this PR is trying to solve is a bit specific to dune, but it's likely that it will be encountered by other projects as well. Currently, dune has a complicated script for generating test definitions that make sure tests run only in environments which support them. For example, some tests may not run on win32. A mechanism to enable tests conditionally would fix these problems. # Proposal Add an `enabled_if` field to aliases to toggle the execution of the alias. This field will be valued by a little EDSL for expressing boolean expressions. Here's an example of the kind of conditions we'd express with it: ``` (alias ((name runtest) (deps (foo.exe)) (action (run ${<})) (enabled_if (and (<> ${os} win32) (>= ${ocaml_version} 4.0.5))))) ``` # Progress This stalled a bit since I'm not sure how to do handle type safety here. Ideally, we only allow numbers and versions to be compared with `>=`, `<`, etc. I guess we really need to annotate which variables are comparable and making sure that we don't compare numbers to strings or versions.
- Loading branch information
Showing
15 changed files
with
272 additions
and
48 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,45 @@ | ||
open! Stdune | ||
|
||
module Op = struct | ||
type t = | ||
| Eq | ||
| Gt | ||
| Gte | ||
| Lte | ||
| Lt | ||
| Neq | ||
|
||
let eval t (x : Ordering.t) = | ||
match t, x with | ||
| (Eq | Gte | Lte) , Eq | ||
| (Lt | Lte) , Lt | ||
| (Gt | Gte) , Gt -> true | ||
| _, _ -> false | ||
end | ||
|
||
type 'a t = | ||
| Expr of 'a | ||
| And of 'a t list | ||
| Or of 'a t list | ||
| Compare of Op.t * 'a * 'a | ||
|
||
type 'a expander = | ||
{ f : 'value. mode:'value String_with_vars.Mode.t | ||
-> 'a | ||
-> Loc.t * 'value | ||
} | ||
|
||
let rec eval_bool t ~dir ~(f : 'a expander) = | ||
match t with | ||
| Expr a -> | ||
begin match f.f ~mode:Single a with | ||
| _, String "true" -> true | ||
| _, String "false" -> false | ||
| loc, _ -> Loc.fail loc "This value must be either true or false" | ||
end | ||
| And xs -> List.for_all ~f:(eval_bool ~f ~dir) xs | ||
| Or xs -> List.exists ~f:(eval_bool ~f ~dir) xs | ||
| Compare (op, x, y) -> | ||
let ((_, x), (_, y)) = (f.f ~mode:Many x, f.f ~mode:Many y) in | ||
Value.L.compare_vals ~dir x y | ||
|> Op.eval op |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,25 @@ | ||
open Stdune | ||
|
||
module Op : sig | ||
type t = | ||
| Eq | ||
| Gt | ||
| Gte | ||
| Lte | ||
| Lt | ||
| Neq | ||
end | ||
|
||
type 'a t = | ||
| Expr of 'a | ||
| And of 'a t list | ||
| Or of 'a t list | ||
| Compare of Op.t * 'a * 'a | ||
|
||
type 'a expander = | ||
{ f : 'value. mode:'value String_with_vars.Mode.t | ||
-> 'a | ||
-> Loc.t * 'value | ||
} | ||
|
||
val eval_bool : 'a t -> dir:Path.t -> f:'a expander -> bool |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,10 @@ | ||
type t = bool | ||
|
||
let compare x y = | ||
match x, y with | ||
| true, true | ||
| false, false -> Ordering.Eq | ||
| true, false -> Gt | ||
| false, true -> Lt | ||
|
||
let to_string = string_of_bool |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
type t = bool | ||
|
||
val compare : t -> t -> Ordering.t | ||
|
||
val to_string : t -> string |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.