Skip to content

Commit 9c26f9f

Browse files
committed
feature(cram): add [setup_script] to cram tests
Signed-off-by: Rudi Grinberg <[email protected]> refactor: my personal tweaks Signed-off-by: Rudi Grinberg <[email protected]>
1 parent b11b1e1 commit 9c26f9f

File tree

11 files changed

+383
-16
lines changed

11 files changed

+383
-16
lines changed

src/dune_rules/cram/cram_exec.ml

Lines changed: 58 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -325,7 +325,7 @@ let cram_commmands commands =
325325
Buffer.contents buf
326326
;;
327327

328-
let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
328+
let create_sh_script cram_stanzas ~temp_dir ~setup_scripts : sh_script Fiber.t =
329329
let script = Path.relative temp_dir "main.sh" in
330330
let oc = Io.open_out ~binary:true script in
331331
Fiber.finalize ~finally:(fun () -> Fiber.return @@ close_out oc)
@@ -374,6 +374,15 @@ let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
374374
}
375375
in
376376
fprln oc "trap 'exit 0' EXIT";
377+
let* () =
378+
Fiber.sequential_iter setup_scripts ~f:(fun (script_path : Path.t) ->
379+
let+ script_sh_path = sh_path script_path in
380+
fprln oc ". %s" script_sh_path;
381+
match script_path with
382+
| In_source_tree _ -> assert false
383+
| External _ -> ()
384+
| In_build_dir _ -> fprln oc "rm -f %s" script_sh_path)
385+
in
377386
let+ cram_to_output = Fiber.sequential_map ~f:loop cram_stanzas in
378387
let command_count = !i in
379388
let metadata_file = Option.some_if (command_count > 0) metadata_file in
@@ -413,9 +422,9 @@ let make_temp_dir ~script =
413422
temp_dir
414423
;;
415424

416-
let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
425+
let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts =
417426
let open Fiber.O in
418-
let* sh_script = create_sh_script cram_stanzas ~temp_dir in
427+
let* sh_script = create_sh_script cram_stanzas ~temp_dir ~setup_scripts in
419428
let env = make_run_env env ~temp_dir ~cwd in
420429
let open Fiber.O in
421430
let sh =
@@ -483,13 +492,21 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
483492
(timeout_msg @ [ timeout_set_message ])
484493
;;
485494

486-
let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
495+
let run_produce_correction
496+
~conflict_markers
497+
~src
498+
~env
499+
~script
500+
~timeout
501+
~setup_scripts
502+
lexbuf
503+
=
487504
let temp_dir = make_temp_dir ~script in
488505
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
489506
let cwd = Path.parent_exn script in
490507
let env = make_run_env env ~temp_dir ~cwd in
491508
let open Fiber.O in
492-
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
509+
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
493510
>>| compose_cram_output
494511
;;
495512

@@ -502,7 +519,16 @@ module Script = Persistent.Make (struct
502519
let test_example () = []
503520
end)
504521

505-
let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~timeout =
522+
let run_and_produce_output
523+
~conflict_markers
524+
~src
525+
~env
526+
~dir:cwd
527+
~script
528+
~dst
529+
~timeout
530+
~setup_scripts
531+
=
506532
let script_contents = Io.read_file ~binary:false script in
507533
let lexbuf = Lexbuf.from_string script_contents ~fname:(Path.to_string script) in
508534
let temp_dir = make_temp_dir ~script in
@@ -512,7 +538,7 @@ let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~ti
512538
let env = make_run_env env ~temp_dir ~cwd in
513539
let open Fiber.O in
514540
let+ commands =
515-
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
541+
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
516542
>>| List.filter_map ~f:(function
517543
| Cram_lexer.Command c -> Some c
518544
| Comment _ -> None)
@@ -530,28 +556,42 @@ module Run = struct
530556
; script : 'path
531557
; output : 'target
532558
; timeout : (Loc.t * float) option
559+
; setup_scripts : 'path list
533560
}
534561

535562
let name = "cram-run"
536-
let version = 2
537-
538-
let bimap ({ src = _; dir; script; output; timeout } as t) f g =
539-
{ t with dir = f dir; script = f script; output = g output; timeout }
563+
let version = 3
564+
565+
let bimap ({ src = _; dir; script; output; timeout; setup_scripts } as t) f g =
566+
{ t with
567+
dir = f dir
568+
; script = f script
569+
; output = g output
570+
; timeout
571+
; setup_scripts = List.map ~f setup_scripts
572+
}
540573
;;
541574

542575
let is_useful_to ~memoize:_ = true
543576

544-
let encode { src = _; dir; script; output; timeout } path target : Sexp.t =
577+
let encode { src = _; dir; script; output; timeout; setup_scripts } path target
578+
: Sexp.t
579+
=
545580
List
546581
[ path dir
547582
; path script
548583
; target output
549584
; Dune_sexp.Encoder.(option float (Option.map ~f:snd timeout))
550585
|> Dune_sexp.to_sexp
586+
; List (List.map ~f:path setup_scripts)
551587
]
552588
;;
553589

554-
let action { src; dir; script; output; timeout } ~ectx:_ ~(eenv : Action.env) =
590+
let action
591+
{ src; dir; script; output; timeout; setup_scripts }
592+
~ectx:_
593+
~(eenv : Action.env)
594+
=
555595
run_and_produce_output
556596
~conflict_markers:Ignore
557597
~src
@@ -560,14 +600,15 @@ module Run = struct
560600
~script
561601
~dst:output
562602
~timeout
603+
~setup_scripts
563604
;;
564605
end
565606

566607
include Action_ext.Make (Spec)
567608
end
568609

569-
let run ~src ~dir ~script ~output ~timeout =
570-
Run.action { src; dir; script; output; timeout }
610+
let run ~src ~dir ~script ~output ~timeout ~setup_scripts =
611+
Run.action { src; dir; script; output; timeout; setup_scripts }
571612
;;
572613

573614
module Make_script = struct
@@ -688,7 +729,8 @@ module Action = struct
688729
~src:script
689730
~env:eenv.env
690731
~script
691-
~timeout:None)
732+
~timeout:None
733+
~setup_scripts:[])
692734
;;
693735
end
694736

src/dune_rules/cram/cram_exec.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ val run
1414
-> script:Path.t
1515
-> output:Path.Build.t
1616
-> timeout:(Loc.t * float) option
17+
-> setup_scripts:Path.t list
1718
-> Action.t
1819

1920
(** Produces a diff if [src] needs to be updated *)

src/dune_rules/cram/cram_rules.ml

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Spec = struct
1313
; packages : Package.Name.Set.t
1414
; timeout : (Loc.t * float) option
1515
; conflict_markers : Cram_stanza.Conflict_markers.t
16+
; setup_scripts : Path.t list
1617
}
1718

1819
let make_empty ~test_name_alias =
@@ -26,6 +27,7 @@ module Spec = struct
2627
; packages = Package.Name.Set.empty
2728
; timeout = None
2829
; conflict_markers = Ignore
30+
; setup_scripts = []
2931
}
3032
;;
3133
end
@@ -61,6 +63,7 @@ let test_rule
6163
; packages = _
6264
; timeout
6365
; conflict_markers
66+
; setup_scripts
6467
} :
6568
Spec.t)
6669
(test : (Cram_test.t, error) result)
@@ -135,6 +138,7 @@ let test_rule
135138
in
136139
let+ (_ : Path.Set.t) = Action_builder.dyn_memo_deps deps in
137140
()
141+
and+ () = Action_builder.paths setup_scripts
138142
and+ locks = locks >>| Path.Set.to_list in
139143
Cram_exec.run
140144
~src:(Path.build script)
@@ -146,6 +150,7 @@ let test_rule
146150
~script:(Path.build script_sh)
147151
~output
148152
~timeout
153+
~setup_scripts
149154
|> Action.Full.make ~locks ~sandbox)
150155
|> Action_builder.with_file_targets ~file_targets:[ output ]
151156
|> Super_context.add_rule sctx ~dir ~loc
@@ -297,6 +302,14 @@ let rules ~sctx ~dir tests =
297302
let conflict_markers =
298303
Option.value ~default:acc.conflict_markers stanza.conflict_markers
299304
in
305+
let setup_scripts =
306+
List.map stanza.setup_scripts ~f:(fun (_loc, script) ->
307+
(* Handle both relative and absolute paths *)
308+
if Filename.is_relative script
309+
then Path.build (Path.Build.relative dir script)
310+
else Path.external_ (Path.External.of_string script))
311+
@ acc.setup_scripts
312+
in
300313
( runtest_alias
301314
, { acc with
302315
enabled_if
@@ -308,6 +321,7 @@ let rules ~sctx ~dir tests =
308321
; sandbox
309322
; timeout
310323
; conflict_markers
324+
; setup_scripts
311325
} ))
312326
in
313327
let extra_aliases =

src/dune_rules/cram/cram_stanza.ml

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ type t =
4545
; package : Package.t option
4646
; runtest_alias : (Loc.t * bool) option
4747
; timeout : (Loc.t * float) option
48+
; setup_scripts : (Loc.t * string) list
4849
}
4950

5051
include Stanza.Make (struct
@@ -100,6 +101,13 @@ let decode =
100101
field_o
101102
"conflict_markers"
102103
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict_markers.decode)
104+
and+ setup_scripts =
105+
let+ scripts =
106+
field_o
107+
"setup_scripts"
108+
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> repeat (located string))
109+
in
110+
Option.value scripts ~default:[]
103111
in
104112
{ loc
105113
; alias
@@ -111,5 +119,6 @@ let decode =
111119
; runtest_alias
112120
; timeout
113121
; conflict_markers
122+
; setup_scripts
114123
})
115124
;;

src/dune_rules/cram/cram_stanza.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ type t =
2323
; package : Package.t option
2424
; runtest_alias : (Loc.t * bool) option
2525
; timeout : (Loc.t * float) option
26+
; setup_scripts : (Loc.t * string) list
2627
}
2728

2829
val decode : t Dune_lang.Decoder.t
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
Test setup_scripts feature for cram tests
2+
3+
Create a project with a helper script:
4+
5+
$ cat > dune-project << EOF
6+
> (lang dune 3.21)
7+
> (cram enable)
8+
> EOF
9+
10+
$ cat > helpers.sh << 'EOF'
11+
> #!/bin/sh
12+
> test_helper() {
13+
> echo "Helper called: $1"
14+
> }
15+
> export MY_VAR="test_value_from_helper"
16+
> EOF
17+
18+
$ cat > dune << EOF
19+
> (cram
20+
> (setup_scripts helpers.sh))
21+
> EOF
22+
23+
$ cat > basic.t << 'EOF'
24+
> Test that setup scripts are sourced and functions are available
25+
>
26+
> $ test_helper "foo"
27+
> Helper called: foo
28+
>
29+
> Test that variables from setup scripts are available
30+
>
31+
> $ echo $MY_VAR
32+
> test_value_from_helper
33+
>
34+
> Check if setup script is visible in test directory
35+
>
36+
> $ ls *.sh 2>&1 || echo "No sh files"
37+
> No sh files
38+
> EOF
39+
40+
Run the test:
41+
42+
$ dune runtest
43+
File "basic.t", line 1, characters 0-0:
44+
Error: Files _build/default/basic.t and _build/default/basic.t.corrected
45+
differ.
46+
[1]
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
Test if setup scripts are visible in test directory
2+
3+
$ cat > dune-project << EOF
4+
> (lang dune 3.21)
5+
> (cram enable)
6+
> EOF
7+
8+
$ cat > secret.sh << 'EOF'
9+
> MY_SECRET="should_not_be_visible"
10+
> EOF
11+
12+
$ cat > dune << EOF
13+
> (cram
14+
> (setup_scripts secret.sh))
15+
> EOF
16+
17+
$ cat > check.t << 'EOF'
18+
> $ ls *.sh 2>&1 || echo "No .sh files found"
19+
> No .sh files found
20+
> EOF
21+
22+
$ dune runtest
23+
File "check.t", line 1, characters 0-0:
24+
Error: Files _build/default/check.t and _build/default/check.t.corrected
25+
differ.
26+
[1]
Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
Test that external (absolute path) setup scripts work and are NOT deleted
2+
3+
First, create an external script in /tmp:
4+
5+
$ EXTERNAL_SCRIPT="/tmp/dune_test_external_helper_$$.sh"
6+
$ cat > "$EXTERNAL_SCRIPT" << 'EOF'
7+
> #!/bin/sh
8+
> external_helper() {
9+
> echo "External helper called"
10+
> }
11+
> export EXTERNAL_VAR="from_external_script"
12+
> EOF
13+
$ chmod +x "$EXTERNAL_SCRIPT"
14+
15+
Create a project that uses the external script:
16+
17+
$ cat > dune-project << EOF
18+
> (lang dune 3.21)
19+
> (cram enable)
20+
> EOF
21+
22+
$ cat > dune << EOF
23+
> (cram
24+
> (setup_scripts $EXTERNAL_SCRIPT))
25+
> EOF
26+
27+
Create a test that uses the external helper:
28+
29+
$ cat > external.t << 'EOF'
30+
> Test that external helper is available
31+
>
32+
> $ external_helper
33+
> External helper called
34+
>
35+
> $ echo $EXTERNAL_VAR
36+
> from_external_script
37+
> EOF
38+
39+
Run the test:
40+
41+
$ dune runtest
42+
43+
Verify the external script still exists (was NOT deleted):
44+
45+
$ if [ -f "$EXTERNAL_SCRIPT" ]; then
46+
> echo "External script still exists"
47+
> else
48+
> echo "External script was deleted"
49+
> fi
50+
External script still exists

0 commit comments

Comments
 (0)