Skip to content

Commit f3fdf4f

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 024ace6 commit f3fdf4f

File tree

11 files changed

+386
-16
lines changed

11 files changed

+386
-16
lines changed

src/dune_rules/cram/cram_exec.ml

Lines changed: 50 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,13 @@ 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 ~conflict_markers ~src ~env ~script ~timeout ~setup_scripts lexbuf =
487496
let temp_dir = make_temp_dir ~script in
488497
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
489498
let cwd = Path.parent_exn script in
490499
let env = make_run_env env ~temp_dir ~cwd in
491500
let open Fiber.O in
492-
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
501+
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
493502
>>| compose_cram_output
494503
;;
495504

@@ -502,7 +511,16 @@ module Script = Persistent.Make (struct
502511
let test_example () = []
503512
end)
504513

505-
let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~timeout =
514+
let run_and_produce_output
515+
~conflict_markers
516+
~src
517+
~env
518+
~dir:cwd
519+
~script
520+
~dst
521+
~timeout
522+
~setup_scripts
523+
=
506524
let script_contents = Io.read_file ~binary:false script in
507525
let lexbuf = Lexbuf.from_string script_contents ~fname:(Path.to_string script) in
508526
let temp_dir = make_temp_dir ~script in
@@ -512,7 +530,7 @@ let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~ti
512530
let env = make_run_env env ~temp_dir ~cwd in
513531
let open Fiber.O in
514532
let+ commands =
515-
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
533+
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
516534
>>| List.filter_map ~f:(function
517535
| Cram_lexer.Command c -> Some c
518536
| Comment _ -> None)
@@ -530,28 +548,42 @@ module Run = struct
530548
; script : 'path
531549
; output : 'target
532550
; timeout : (Loc.t * float) option
551+
; setup_scripts : 'path list
533552
}
534553

535554
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 }
555+
let version = 3
556+
557+
let bimap ({ src = _; dir; script; output; timeout; setup_scripts } as t) f g =
558+
{ t with
559+
dir = f dir
560+
; script = f script
561+
; output = g output
562+
; timeout
563+
; setup_scripts = List.map ~f setup_scripts
564+
}
540565
;;
541566

542567
let is_useful_to ~memoize:_ = true
543568

544-
let encode { src = _; dir; script; output; timeout } path target : Sexp.t =
569+
let encode { src = _; dir; script; output; timeout; setup_scripts } path target
570+
: Sexp.t
571+
=
545572
List
546573
[ path dir
547574
; path script
548575
; target output
549576
; Dune_sexp.Encoder.(option float (Option.map ~f:snd timeout))
550577
|> Dune_sexp.to_sexp
578+
; List (List.map ~f:path setup_scripts)
551579
]
552580
;;
553581

554-
let action { src; dir; script; output; timeout } ~ectx:_ ~(eenv : Action.env) =
582+
let action
583+
{ src; dir; script; output; timeout; setup_scripts }
584+
~ectx:_
585+
~(eenv : Action.env)
586+
=
555587
run_and_produce_output
556588
~conflict_markers:Ignore
557589
~src
@@ -560,14 +592,15 @@ module Run = struct
560592
~script
561593
~dst:output
562594
~timeout
595+
~setup_scripts
563596
;;
564597
end
565598

566599
include Action_ext.Make (Spec)
567600
end
568601

569-
let run ~src ~dir ~script ~output ~timeout =
570-
Run.action { src; dir; script; output; timeout }
602+
let run ~src ~dir ~script ~output ~timeout ~setup_scripts =
603+
Run.action { src; dir; script; output; timeout; setup_scripts }
571604
;;
572605

573606
module Make_script = struct
@@ -688,7 +721,8 @@ module Action = struct
688721
~src:script
689722
~env:eenv.env
690723
~script
691-
~timeout:None)
724+
~timeout:None
725+
~setup_scripts:[])
692726
;;
693727
end
694728

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: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@ module Spec = struct
1313
; packages : Package.Name.Set.t
1414
; timeout : (Loc.t * float) option
1515
; conflict_markers : Cram_stanza.Conflict_markers.t
16+
; conflict : Cram_stanza.Conflict.t
17+
; setup_scripts : Path.t list
1618
}
1719

1820
let make_empty ~test_name_alias =
@@ -26,6 +28,8 @@ module Spec = struct
2628
; packages = Package.Name.Set.empty
2729
; timeout = None
2830
; conflict_markers = Ignore
31+
; conflict = Ignore
32+
; setup_scripts = []
2933
}
3034
;;
3135
end
@@ -61,6 +65,8 @@ let test_rule
6165
; packages = _
6266
; timeout
6367
; conflict_markers
68+
; conflict
69+
; setup_scripts
6470
} :
6571
Spec.t)
6672
(test : (Cram_test.t, error) result)
@@ -135,6 +141,7 @@ let test_rule
135141
in
136142
let+ (_ : Path.Set.t) = Action_builder.dyn_memo_deps deps in
137143
()
144+
and+ () = Action_builder.paths setup_scripts
138145
and+ locks = locks >>| Path.Set.to_list in
139146
Cram_exec.run
140147
~src:(Path.build script)
@@ -146,6 +153,7 @@ let test_rule
146153
~script:(Path.build script_sh)
147154
~output
148155
~timeout
156+
~setup_scripts
149157
|> Action.Full.make ~locks ~sandbox)
150158
|> Action_builder.with_file_targets ~file_targets:[ output ]
151159
|> Super_context.add_rule sctx ~dir ~loc
@@ -297,6 +305,15 @@ let rules ~sctx ~dir tests =
297305
let conflict_markers =
298306
Option.value ~default:acc.conflict_markers stanza.conflict_markers
299307
in
308+
let conflict = Option.value ~default:acc.conflict stanza.conflict in
309+
let setup_scripts =
310+
List.map stanza.setup_scripts ~f:(fun (_loc, script) ->
311+
(* Handle both relative and absolute paths *)
312+
if Filename.is_relative script
313+
then Path.build (Path.Build.relative dir script)
314+
else Path.external_ (Path.External.of_string script))
315+
@ acc.setup_scripts
316+
in
300317
( runtest_alias
301318
, { acc with
302319
enabled_if
@@ -308,6 +325,8 @@ let rules ~sctx ~dir tests =
308325
; sandbox
309326
; timeout
310327
; conflict_markers
328+
; conflict
329+
; setup_scripts
311330
} ))
312331
in
313332
let extra_aliases =

src/dune_rules/cram/cram_stanza.ml

Lines changed: 12 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,15 @@ let decode =
100101
field_o
101102
"conflict_markers"
102103
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict_markers.decode)
104+
"conflict"
105+
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict.decode)
106+
and+ setup_scripts =
107+
let+ scripts =
108+
field_o
109+
"setup_scripts"
110+
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> repeat (located string))
111+
in
112+
Option.value scripts ~default:[]
103113
in
104114
{ loc
105115
; alias
@@ -111,5 +121,7 @@ let decode =
111121
; runtest_alias
112122
; timeout
113123
; conflict_markers
124+
; conflict
125+
; setup_scripts
114126
})
115127
;;

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: 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)