Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions doc/changes/8887.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- Introduce the `runtest_alias` field to the `cram` stanza. This allows
removing default `runtest` alias from tests. (@rgrinberg, #8887)
3 changes: 3 additions & 0 deletions doc/tests.rst
Original file line number Diff line number Diff line change
Expand Up @@ -674,6 +674,9 @@ The ``cram`` stanza accepts the following fields:
- ``deps`` - dependencies of the test
- ``(package <package-name>)`` - attach the tests selected by this stanza to the
specified package
- ``(runtest_alias <true|false>)`` - when set to ``false``, do not add the
tests to the ``runtest`` alias. The default is to add every cram test to
``runtest``, but this is not always desired.

A single test may be configured by more than one ``cram`` stanza. In such cases,
the values from all applicable ``cram`` stanzas are merged together to get the
Expand Down
136 changes: 91 additions & 45 deletions src/dune_rules/cram/cram_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Spec = struct

let empty =
{ loc = Loc.none
; alias = Alias.Name.Set.singleton Alias0.runtest
; alias = Alias.Name.Set.empty
; enabled_if = [ Blang.true_ ]
; locks = Path.Set.empty
; deps = []
Expand Down Expand Up @@ -149,51 +149,97 @@ let rules ~sctx ~expander ~dir tests =
| Error (Source_tree.Dir.Missing_run_t test) -> Cram_test.name test
in
let init =
let alias = Alias.Name.of_string name |> Alias.Name.Set.add Spec.empty.alias in
{ Spec.empty with alias }
( None
, let alias = Alias.Name.of_string name |> Alias.Name.Set.add Spec.empty.alias in
{ Spec.empty with alias } )
in
Memo.List.fold_left
stanzas
~init
~f:(fun (acc : Spec.t) (dir, (stanza : Cram_stanza.t)) ->
match
match stanza.applies_to with
| Whole_subtree -> true
| Files_matching_in_this_dir pred ->
Predicate_lang.Glob.test pred ~standard:Predicate_lang.true_ name
with
| false -> Memo.return acc
| true ->
let+ deps, sandbox =
match stanza.deps with
| None -> Memo.return (acc.deps, acc.sandbox)
| Some deps ->
let+ (deps : unit Action_builder.t), _, sandbox =
let+ expander = Super_context.expander sctx ~dir in
Dep_conf_eval.named ~expander deps
in
deps :: acc.deps, Sandbox_config.inter acc.sandbox sandbox
and+ locks =
(* Locks must be relative to the cram stanza directory and not
the individual tests directories *)
let base = `This (Path.build dir) in
Expander.expand_locks ~base expander stanza.locks
>>| Path.Set.of_list
>>| Path.Set.union acc.locks
in
let enabled_if = stanza.enabled_if :: acc.enabled_if in
let alias =
match stanza.alias with
| None -> acc.alias
| Some a -> Alias.Name.Set.add acc.alias a
in
let packages =
match stanza.package with
| None -> acc.packages
| Some (p : Package.t) ->
Package.Name.Set.add acc.packages (Package.Id.name p.id)
in
{ acc with enabled_if; locks; deps; alias; packages; sandbox })
let+ runtest_alias, acc =
Memo.List.fold_left
stanzas
~init
~f:(fun (runtest_alias, (acc : Spec.t)) (dir, (stanza : Cram_stanza.t)) ->
match
match stanza.applies_to with
| Whole_subtree -> true
| Files_matching_in_this_dir pred ->
Predicate_lang.Glob.test pred ~standard:Predicate_lang.true_ name
with
| false -> Memo.return (runtest_alias, acc)
| true ->
let+ deps, sandbox =
match stanza.deps with
| None -> Memo.return (acc.deps, acc.sandbox)
| Some deps ->
let+ (deps : unit Action_builder.t), _, sandbox =
let+ expander = Super_context.expander sctx ~dir in
Dep_conf_eval.named ~expander deps
in
deps :: acc.deps, Sandbox_config.inter acc.sandbox sandbox
and+ locks =
(* Locks must be relative to the cram stanza directory and not
the individual tests directories *)
let base = `This (Path.build dir) in
Expander.expand_locks ~base expander stanza.locks
>>| Path.Set.of_list
>>| Path.Set.union acc.locks
in
let runtest_alias =
match stanza.runtest_alias with
| None -> None
| Some (loc, set) ->
(match runtest_alias with
| None -> Some (loc, set)
| Some (loc', _) ->
let main_message =
Pp.concat
~sep:Pp.newline
[ Pp.text
"enabling or disabling the runtest alias for a cram test \
may only be set once."
; Pp.textf "It's already set for the test %S" name
]
in
let annots =
let main = User_message.make ~loc:loc' [ main_message ] in
let related =
[ User_message.make ~loc [ Pp.text "Already set here" ] ]
in
User_message.Annots.singleton
Compound_user_error.annot
[ Compound_user_error.make ~main ~related ]
in
User_error.raise
~annots
~loc
[ main_message
; Pp.text "The first definition is at:"
; Pp.text (Loc.to_file_colon_line loc')
])
in
let enabled_if = stanza.enabled_if :: acc.enabled_if in
let alias =
match stanza.alias with
| None -> acc.alias
| Some a -> Alias.Name.Set.add acc.alias a
in
let packages =
match stanza.package with
| None -> acc.packages
| Some (p : Package.t) ->
Package.Name.Set.add acc.packages (Package.Id.name p.id)
in
( runtest_alias
, { acc with enabled_if; locks; deps; alias; packages; sandbox } ))
in
let alias =
let to_add =
match runtest_alias with
| None | Some (_, true) -> Alias.Name.Set.singleton Alias0.runtest
| Some (_, false) -> Alias.Name.Set.empty
in
Alias.Name.Set.union to_add acc.alias
in
{ acc with alias }
in
with_package_mask spec.packages (fun () -> test_rule ~sctx ~expander ~dir spec test))
;;
Expand Down
7 changes: 6 additions & 1 deletion src/dune_rules/cram/cram_stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ type t =
; enabled_if : Blang.t
; locks : Locks.t
; package : Package.t option
; runtest_alias : (Loc.t * bool) option
}

type Stanza.t += T of t
Expand All @@ -42,6 +43,10 @@ let decode =
and+ locks = Locks.field ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 9)) ()
and+ package =
Stanza_common.Pkg.field_opt ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8)) ()
and+ runtest_alias =
field_o
"runtest_alias"
(Dune_lang.Syntax.since Stanza.syntax (3, 11) >>> located bool)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

this should be 3.12 since it got added in 3.12.0

in
{ loc; alias; deps; enabled_if; locks; applies_to; package })
{ loc; alias; deps; enabled_if; locks; applies_to; package; runtest_alias })
;;
1 change: 1 addition & 0 deletions src/dune_rules/cram/cram_stanza.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ type t =
; enabled_if : Blang.t
; locks : Locks.t
; package : Package.t option
; runtest_alias : (Loc.t * bool) option
}

type Stanza.t += T of t
Expand Down
44 changes: 44 additions & 0 deletions test/blackbox-tests/test-cases/cram/runtest_alias.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
Control the default runtest alias for cram tests

$ cat >dune-project <<EOF
> (lang dune 3.11)
> EOF

$ cat >dune <<EOF
> (cram
> (runtest_alias false)
> (alias this))
> EOF

$ cat >foo.t <<EOF
> $ echo foo
> EOF

This shouldn't run the test

$ dune runtest

This should run the test

$ dune build @this
File "foo.t", line 1, characters 0-0:
Error: Files _build/default/foo.t and _build/default/foo.t.corrected differ.
[1]

Now we try setting runtest alias default twice. This should be impossible:

$ cat >dune <<EOF
> (cram (runtest_alias false))
> (cram (runtest_alias true))
> EOF

$ dune build @a
File "dune", line 2, characters 21-25:
2 | (cram (runtest_alias true))
^^^^
Error: enabling or disabling the runtest alias for a cram test may only be
set once.
It's already set for the test "foo"
The first definition is at:
dune:1
[1]