Skip to content

Commit 821ae4f

Browse files
authored
Merge pull request #12651 from Alizter/push-luppyxluzruz
cram: rename conflict -> conflict_marker
2 parents 56d6850 + 887ca08 commit 821ae4f

File tree

11 files changed

+65
-50
lines changed

11 files changed

+65
-50
lines changed

doc/changes/added/12538.md

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
- Add a `(conflict error|ignore)` option to the cram stanza. When `(conflict
2-
error)` is set, the cram test will fail in the presence of conflict markers.
3-
Git, diff3 and jujutsu conflict markers are detected. (#12538, #12617, fixes
4-
#12512, @rgrinberg, @Alizter)
1+
- Add a `(conflict_markers error|ignore)` option to the cram stanza. When
2+
`(conflict_markers error)` is set, the cram test will fail in the presence of
3+
conflict markers. Git, diff3 and jujutsu conflict markers are detected.
4+
(#12538, #12617, fixes #12512, @rgrinberg, @Alizter)

doc/reference/dune/cram.rst

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,7 @@ Cram
110110
111111
This limits each selected test to at most 2.5 seconds of execution time.
112112

113-
.. describe:: (conflict <ignore|error>)
113+
.. describe:: (conflict_markers <ignore|error>)
114114

115115
.. versionadded:: 3.21
116116

src/dune_rules/cram/cram_exec.ml

Lines changed: 20 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -55,10 +55,12 @@ let cram_stanzas =
5555
(* CR-someday rgrinberg for alizter: insert a location spanning the
5656
entire once we start extracting it *)
5757
User_error.raise
58-
[ Pp.text "Conflict found. Please remove it or set (conflict allow)" ]
58+
[ Pp.text
59+
"Conflict marker found. Please remove it or set (conflict_markers allow)"
60+
]
5961
| _ -> state
6062
in
61-
fun ~(conflict : Cram_stanza.Conflict.t) lexbuf ->
63+
fun ~(conflict_markers : Cram_stanza.Conflict_markers.t) lexbuf ->
6264
let rec loop acc conflict_state =
6365
match Cram_lexer.block lexbuf with
6466
| None -> List.rev acc
@@ -67,7 +69,7 @@ let cram_stanzas =
6769
match s with
6870
| Command _ -> conflict_state
6971
| Comment lines ->
70-
(match conflict with
72+
(match conflict_markers with
7173
| Ignore -> conflict_state
7274
| Error -> List.fold_left lines ~init:conflict_state ~f:find_conflict)
7375
in
@@ -77,7 +79,7 @@ let cram_stanzas =
7779
;;
7880

7981
module For_tests = struct
80-
let cram_stanzas lexbuf = cram_stanzas lexbuf ~conflict:Ignore
82+
let cram_stanzas lexbuf = cram_stanzas lexbuf ~conflict_markers:Ignore
8183

8284
let dyn_of_block = function
8385
| Cram_lexer.Comment lines -> Dyn.variant "Comment" [ Dyn.list Dyn.string lines ]
@@ -482,9 +484,9 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
482484
(timeout_msg @ [ timeout_set_message ])
483485
;;
484486

485-
let run_produce_correction ~conflict ~src ~env ~script ~timeout lexbuf =
487+
let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
486488
let temp_dir = make_temp_dir ~script in
487-
let cram_stanzas = cram_stanzas lexbuf ~conflict in
489+
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
488490
let cwd = Path.parent_exn script in
489491
let env = make_run_env env ~temp_dir ~cwd in
490492
let open Fiber.O in
@@ -501,11 +503,11 @@ module Script = Persistent.Make (struct
501503
let test_example () = []
502504
end)
503505

504-
let run_and_produce_output ~conflict ~src ~env ~dir:cwd ~script ~dst ~timeout =
506+
let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~timeout =
505507
let script_contents = Io.read_file ~binary:false script in
506508
let lexbuf = Lexbuf.from_string script_contents ~fname:(Path.to_string script) in
507509
let temp_dir = make_temp_dir ~script in
508-
let cram_stanzas = cram_stanzas lexbuf ~conflict in
510+
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
509511
(* We don't want the ".cram.run.t" dir around when executing the script. *)
510512
Path.rm_rf (Path.parent_exn script);
511513
let env = make_run_env env ~temp_dir ~cwd in
@@ -552,7 +554,7 @@ module Run = struct
552554

553555
let action { src; dir; script; output; timeout } ~ectx:_ ~(eenv : Action.env) =
554556
run_and_produce_output
555-
~conflict:Ignore
557+
~conflict_markers:Ignore
556558
~src
557559
~env:eenv.env
558560
~dir
@@ -574,30 +576,30 @@ module Make_script = struct
574576
type ('path, 'target) t =
575577
{ script : 'path
576578
; target : 'target
577-
; conflict : Cram_stanza.Conflict.t
579+
; conflict_markers : Cram_stanza.Conflict_markers.t
578580
}
579581

580582
let name = "cram-generate"
581583
let version = 2
582584
let bimap t f g = { t with script = f t.script; target = g t.target }
583585
let is_useful_to ~memoize:_ = true
584586

585-
let encode { script = src; target = dst; conflict } path target : Sexp.t =
587+
let encode { script = src; target = dst; conflict_markers } path target : Sexp.t =
586588
List
587589
[ path src
588590
; target dst
589591
; Atom
590-
(match conflict with
592+
(match conflict_markers with
591593
| Error -> "error"
592594
| Ignore -> "ignore")
593595
]
594596
;;
595597

596-
let action { script = src; target = dst; conflict } ~ectx:_ ~eenv:_ =
598+
let action { script = src; target = dst; conflict_markers } ~ectx:_ ~eenv:_ =
597599
let commands =
598600
Io.read_file ~binary:false src
599601
|> Lexbuf.from_string ~fname:(Path.to_string src)
600-
|> cram_stanzas ~conflict
602+
|> cram_stanzas ~conflict_markers
601603
|> List.filter_map ~f:(function
602604
| Cram_lexer.Comment _ -> None
603605
| Command s -> Some s)
@@ -611,8 +613,8 @@ module Make_script = struct
611613
include Action_ext.Make (Spec)
612614
end
613615

614-
let make_script ~src ~script ~conflict =
615-
Make_script.action { script = src; target = script; conflict }
616+
let make_script ~src ~script ~conflict_markers =
617+
Make_script.action { script = src; target = script; conflict_markers }
616618
;;
617619

618620
module Diff = struct
@@ -640,7 +642,7 @@ module Diff = struct
640642
in
641643
let current_stanzas =
642644
Lexbuf.from_string ~fname:(Path.to_string script) current
643-
|> cram_stanzas ~conflict:Ignore
645+
|> cram_stanzas ~conflict_markers:Ignore
644646
in
645647
let rec loop acc current expected =
646648
match current with
@@ -683,7 +685,7 @@ module Action = struct
683685
script
684686
~f:
685687
(run_produce_correction
686-
~conflict:Ignore
688+
~conflict_markers:Ignore
687689
~src:script
688690
~env:eenv.env
689691
~script

src/dune_rules/cram/cram_exec.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ open Import
44
val make_script
55
: src:Path.t
66
-> script:Path.Build.t
7-
-> conflict:Cram_stanza.Conflict.t
7+
-> conflict_markers:Cram_stanza.Conflict_markers.t
88
-> Action.t
99

1010
(** Runs the script created in [make_script] *)

src/dune_rules/cram/cram_rules.ml

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module Spec = struct
1212
; locks : Path.Set.t Action_builder.t
1313
; packages : Package.Name.Set.t
1414
; timeout : (Loc.t * float) option
15-
; conflict : Cram_stanza.Conflict.t
15+
; conflict_markers : Cram_stanza.Conflict_markers.t
1616
}
1717

1818
let make_empty ~test_name_alias =
@@ -25,7 +25,7 @@ module Spec = struct
2525
; sandbox = Sandbox_config.needs_sandboxing
2626
; packages = Package.Name.Set.empty
2727
; timeout = None
28-
; conflict = Ignore
28+
; conflict_markers = Ignore
2929
}
3030
;;
3131
end
@@ -60,7 +60,7 @@ let test_rule
6060
; sandbox
6161
; packages = _
6262
; timeout
63-
; conflict
63+
; conflict_markers
6464
} :
6565
Spec.t)
6666
(test : (Cram_test.t, error) result)
@@ -110,7 +110,10 @@ let test_rule
110110
let* () =
111111
(let open Action_builder.O in
112112
let+ () = Action_builder.path (Path.build script) in
113-
Cram_exec.make_script ~src:(Path.build script) ~script:script_sh ~conflict
113+
Cram_exec.make_script
114+
~src:(Path.build script)
115+
~script:script_sh
116+
~conflict_markers
114117
|> Action.Full.make)
115118
|> Action_builder.with_file_targets ~file_targets:[ script_sh ]
116119
|> Super_context.add_rule sctx ~dir ~loc
@@ -291,7 +294,9 @@ let rules ~sctx ~dir tests =
291294
stanza.timeout
292295
~f:(Ordering.min (fun x y -> Float.compare (snd x) (snd y)))
293296
in
294-
let conflict = Option.value ~default:acc.conflict stanza.conflict in
297+
let conflict_markers =
298+
Option.value ~default:acc.conflict_markers stanza.conflict_markers
299+
in
295300
( runtest_alias
296301
, { acc with
297302
enabled_if
@@ -302,7 +307,7 @@ let rules ~sctx ~dir tests =
302307
; packages
303308
; sandbox
304309
; timeout
305-
; conflict
310+
; conflict_markers
306311
} ))
307312
in
308313
let extra_aliases =

src/dune_rules/cram/cram_stanza.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ let decode_applies_to =
2020
subtree <|> predicate
2121
;;
2222

23-
module Conflict = struct
23+
module Conflict_markers = struct
2424
type t =
2525
| Error
2626
| Ignore
@@ -41,7 +41,7 @@ type t =
4141
; deps : Dep_conf.t Bindings.t option
4242
; enabled_if : Blang.t
4343
; locks : Locks.t
44-
; conflict : Conflict.t option
44+
; conflict_markers : Conflict_markers.t option
4545
; package : Package.t option
4646
; runtest_alias : (Loc.t * bool) option
4747
; timeout : (Loc.t * float) option
@@ -96,10 +96,10 @@ let decode =
9696
User_error.raise
9797
~loc
9898
[ Pp.text "Timeout value must be a non-negative float." ])
99-
and+ conflict =
99+
and+ conflict_markers =
100100
field_o
101-
"conflict"
102-
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict.decode)
101+
"conflict_markers"
102+
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict_markers.decode)
103103
in
104104
{ loc
105105
; alias
@@ -110,6 +110,6 @@ let decode =
110110
; package
111111
; runtest_alias
112112
; timeout
113-
; conflict
113+
; conflict_markers
114114
})
115115
;;

src/dune_rules/cram/cram_stanza.mli

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ type applies_to =
44
| Whole_subtree
55
| Files_matching_in_this_dir of Predicate_lang.Glob.t
66

7-
module Conflict : sig
7+
module Conflict_markers : sig
88
type t =
99
| Error
1010
| Ignore
@@ -19,7 +19,7 @@ type t =
1919
; deps : Dep_conf.t Bindings.t option
2020
; enabled_if : Blang.t
2121
; locks : Locks.t
22-
; conflict : Conflict.t option
22+
; conflict_markers : Conflict_markers.t option
2323
; package : Package.t option
2424
; runtest_alias : (Loc.t * bool) option
2525
; timeout : (Loc.t * float) option

test/blackbox-tests/test-cases/cram/conflict-markers-diff3.t

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ Cram tests can forbid git diff3 conflicts:
55
> EOF
66

77
$ cat >dune <<EOF
8-
> (cram (conflict error))
8+
> (cram (conflict_markers error))
99
> EOF
1010

1111
Full diff3 conflict without command and output interleaving:
@@ -22,7 +22,8 @@ Full diff3 conflict without command and output interleaving:
2222
> EOF
2323

2424
$ dune runtest test.t
25-
Error: Conflict found. Please remove it or set (conflict allow)
25+
Error: Conflict marker found. Please remove it or set (conflict_markers
26+
allow)
2627
-> required by _build/default/.cram.test.t/cram.sh
2728
-> required by _build/default/.cram.test.t/cram.out
2829
-> required by alias test
@@ -42,7 +43,8 @@ Full diff3 conflict with command and output interleaving:
4243
> EOF
4344

4445
$ dune runtest test.t
45-
Error: Conflict found. Please remove it or set (conflict allow)
46+
Error: Conflict marker found. Please remove it or set (conflict_markers
47+
allow)
4648
-> required by _build/default/.cram.test.t/cram.sh
4749
-> required by _build/default/.cram.test.t/cram.out
4850
-> required by alias test

test/blackbox-tests/test-cases/cram/conflict-markers-jj.t

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ Cram tests can forbid jujutsu conflicts:
55
> EOF
66

77
$ cat >dune <<EOF
8-
> (cram (conflict error))
8+
> (cram (conflict_markers error))
99
> EOF
1010

1111
Full jujutsu conflict without command and output interleaving:
@@ -20,7 +20,8 @@ Full jujutsu conflict without command and output interleaving:
2020
> EOF
2121

2222
$ dune runtest test.t
23-
Error: Conflict found. Please remove it or set (conflict allow)
23+
Error: Conflict marker found. Please remove it or set (conflict_markers
24+
allow)
2425
-> required by _build/default/.cram.test.t/cram.sh
2526
-> required by _build/default/.cram.test.t/cram.out
2627
-> required by alias test
@@ -38,7 +39,8 @@ Full jujutsu conflict with command and output interleaving:
3839
> EOF
3940

4041
$ dune runtest test.t
41-
Error: Conflict found. Please remove it or set (conflict allow)
42+
Error: Conflict marker found. Please remove it or set (conflict_markers
43+
allow)
4244
-> required by _build/default/.cram.test.t/cram.sh
4345
-> required by _build/default/.cram.test.t/cram.out
4446
-> required by alias test
@@ -59,7 +61,8 @@ Jujutsu default style conflict (diff + snapshot):
5961
> EOF
6062

6163
$ dune runtest test.t
62-
Error: Conflict found. Please remove it or set (conflict allow)
64+
Error: Conflict marker found. Please remove it or set (conflict_markers
65+
allow)
6366
-> required by _build/default/.cram.test.t/cram.sh
6467
-> required by _build/default/.cram.test.t/cram.out
6568
-> required by alias test
@@ -80,7 +83,8 @@ Jujutsu snapshot style conflict:
8083
> EOF
8184

8285
$ dune runtest test.t
83-
Error: Conflict found. Please remove it or set (conflict allow)
86+
Error: Conflict marker found. Please remove it or set (conflict_markers
87+
allow)
8488
-> required by _build/default/.cram.test.t/cram.sh
8589
-> required by _build/default/.cram.test.t/cram.out
8690
-> required by alias test

test/blackbox-tests/test-cases/cram/conflict-markers.t

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ Cram tests can forbid conflicts:
55
> EOF
66

77
$ cat >dune <<EOF
8-
> (cram (conflict error))
8+
> (cram (conflict_markers error))
99
> EOF
1010

1111
Full conflict without command and output interleaving:
@@ -20,7 +20,8 @@ Full conflict without command and output interleaving:
2020
> EOF
2121

2222
$ dune runtest test.t
23-
Error: Conflict found. Please remove it or set (conflict allow)
23+
Error: Conflict marker found. Please remove it or set (conflict_markers
24+
allow)
2425
-> required by _build/default/.cram.test.t/cram.sh
2526
-> required by _build/default/.cram.test.t/cram.out
2627
-> required by alias test
@@ -38,7 +39,8 @@ Full conflict with command and output interleaving:
3839
> EOF
3940

4041
$ dune runtest test.t
41-
Error: Conflict found. Please remove it or set (conflict allow)
42+
Error: Conflict marker found. Please remove it or set (conflict_markers
43+
allow)
4244
-> required by _build/default/.cram.test.t/cram.sh
4345
-> required by _build/default/.cram.test.t/cram.out
4446
-> required by alias test

0 commit comments

Comments
 (0)