Skip to content
Open
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
74 changes: 58 additions & 16 deletions src/dune_rules/cram/cram_exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -325,7 +325,7 @@ let cram_commmands commands =
Buffer.contents buf
;;

let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
let create_sh_script cram_stanzas ~temp_dir ~setup_scripts : sh_script Fiber.t =
let script = Path.relative temp_dir "main.sh" in
let oc = Io.open_out ~binary:true script in
Fiber.finalize ~finally:(fun () -> Fiber.return @@ close_out oc)
Expand Down Expand Up @@ -374,6 +374,15 @@ let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
}
in
fprln oc "trap 'exit 0' EXIT";
let* () =
Fiber.sequential_iter setup_scripts ~f:(fun (script_path : Path.t) ->
let+ script_sh_path = sh_path script_path in
fprln oc ". %s" script_sh_path;
match script_path with
| In_source_tree _ -> assert false
| External _ -> ()
| In_build_dir _ -> fprln oc "rm -f %s" script_sh_path)
in
let+ cram_to_output = Fiber.sequential_map ~f:loop cram_stanzas in
let command_count = !i in
let metadata_file = Option.some_if (command_count > 0) metadata_file in
Expand Down Expand Up @@ -413,9 +422,9 @@ let make_temp_dir ~script =
temp_dir
;;

let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts =
let open Fiber.O in
let* sh_script = create_sh_script cram_stanzas ~temp_dir in
let* sh_script = create_sh_script cram_stanzas ~temp_dir ~setup_scripts in
let env = make_run_env env ~temp_dir ~cwd in
let open Fiber.O in
let sh =
Expand Down Expand Up @@ -483,13 +492,21 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
(timeout_msg @ [ timeout_set_message ])
;;

let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
let run_produce_correction
~conflict_markers
~src
~env
~script
~timeout
~setup_scripts
lexbuf
=
let temp_dir = make_temp_dir ~script in
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
let cwd = Path.parent_exn script in
let env = make_run_env env ~temp_dir ~cwd in
let open Fiber.O in
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
>>| compose_cram_output
;;

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

let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~timeout =
let run_and_produce_output
~conflict_markers
~src
~env
~dir:cwd
~script
~dst
~timeout
~setup_scripts
=
let script_contents = Io.read_file ~binary:false script in
let lexbuf = Lexbuf.from_string script_contents ~fname:(Path.to_string script) in
let temp_dir = make_temp_dir ~script in
Expand All @@ -512,7 +538,7 @@ let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~ti
let env = make_run_env env ~temp_dir ~cwd in
let open Fiber.O in
let+ commands =
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout
run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout ~setup_scripts
>>| List.filter_map ~f:(function
| Cram_lexer.Command c -> Some c
| Comment _ -> None)
Expand All @@ -530,28 +556,42 @@ module Run = struct
; script : 'path
; output : 'target
; timeout : (Loc.t * float) option
; setup_scripts : 'path list
}

let name = "cram-run"
let version = 2

let bimap ({ src = _; dir; script; output; timeout } as t) f g =
{ t with dir = f dir; script = f script; output = g output; timeout }
let version = 3

let bimap ({ src = _; dir; script; output; timeout; setup_scripts } as t) f g =
{ t with
dir = f dir
; script = f script
; output = g output
; timeout
; setup_scripts = List.map ~f setup_scripts
}
;;

let is_useful_to ~memoize:_ = true

let encode { src = _; dir; script; output; timeout } path target : Sexp.t =
let encode { src = _; dir; script; output; timeout; setup_scripts } path target
: Sexp.t
=
List
[ path dir
; path script
; target output
; Dune_sexp.Encoder.(option float (Option.map ~f:snd timeout))
|> Dune_sexp.to_sexp
; List (List.map ~f:path setup_scripts)
]
;;

let action { src; dir; script; output; timeout } ~ectx:_ ~(eenv : Action.env) =
let action
{ src; dir; script; output; timeout; setup_scripts }
~ectx:_
~(eenv : Action.env)
=
run_and_produce_output
~conflict_markers:Ignore
~src
Expand All @@ -560,14 +600,15 @@ module Run = struct
~script
~dst:output
~timeout
~setup_scripts
;;
end

include Action_ext.Make (Spec)
end

let run ~src ~dir ~script ~output ~timeout =
Run.action { src; dir; script; output; timeout }
let run ~src ~dir ~script ~output ~timeout ~setup_scripts =
Run.action { src; dir; script; output; timeout; setup_scripts }
;;

module Make_script = struct
Expand Down Expand Up @@ -688,7 +729,8 @@ module Action = struct
~src:script
~env:eenv.env
~script
~timeout:None)
~timeout:None
~setup_scripts:[])
;;
end

Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/cram/cram_exec.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ val run
-> script:Path.t
-> output:Path.Build.t
-> timeout:(Loc.t * float) option
-> setup_scripts:Path.t list
-> Action.t

(** Produces a diff if [src] needs to be updated *)
Expand Down
14 changes: 14 additions & 0 deletions src/dune_rules/cram/cram_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ module Spec = struct
; packages : Package.Name.Set.t
; timeout : (Loc.t * float) option
; conflict_markers : Cram_stanza.Conflict_markers.t
; setup_scripts : Path.t list
}

let make_empty ~test_name_alias =
Expand All @@ -26,6 +27,7 @@ module Spec = struct
; packages = Package.Name.Set.empty
; timeout = None
; conflict_markers = Ignore
; setup_scripts = []
}
;;
end
Expand Down Expand Up @@ -61,6 +63,7 @@ let test_rule
; packages = _
; timeout
; conflict_markers
; setup_scripts
} :
Spec.t)
(test : (Cram_test.t, error) result)
Expand Down Expand Up @@ -135,6 +138,7 @@ let test_rule
in
let+ (_ : Path.Set.t) = Action_builder.dyn_memo_deps deps in
()
and+ () = Action_builder.paths setup_scripts
and+ locks = locks >>| Path.Set.to_list in
Cram_exec.run
~src:(Path.build script)
Expand All @@ -146,6 +150,7 @@ let test_rule
~script:(Path.build script_sh)
~output
~timeout
~setup_scripts
|> Action.Full.make ~locks ~sandbox)
|> Action_builder.with_file_targets ~file_targets:[ output ]
|> Super_context.add_rule sctx ~dir ~loc
Expand Down Expand Up @@ -297,6 +302,14 @@ let rules ~sctx ~dir tests =
let conflict_markers =
Option.value ~default:acc.conflict_markers stanza.conflict_markers
in
let setup_scripts =
List.map stanza.setup_scripts ~f:(fun (_loc, script) ->
(* Handle both relative and absolute paths *)
if Filename.is_relative script
then Path.build (Path.Build.relative dir script)
else Path.external_ (Path.External.of_string script))
@ acc.setup_scripts
in
( runtest_alias
, { acc with
enabled_if
Expand All @@ -308,6 +321,7 @@ let rules ~sctx ~dir tests =
; sandbox
; timeout
; conflict_markers
; setup_scripts
} ))
in
let extra_aliases =
Expand Down
9 changes: 9 additions & 0 deletions src/dune_rules/cram/cram_stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ type t =
; package : Package.t option
; runtest_alias : (Loc.t * bool) option
; timeout : (Loc.t * float) option
; setup_scripts : (Loc.t * string) list
}

include Stanza.Make (struct
Expand Down Expand Up @@ -100,6 +101,13 @@ let decode =
field_o
"conflict_markers"
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> Conflict_markers.decode)
and+ setup_scripts =
let+ scripts =
field_o
"setup_scripts"
(Dune_lang.Syntax.since Stanza.syntax (3, 21) >>> repeat (located string))
in
Option.value scripts ~default:[]
in
{ loc
; alias
Expand All @@ -111,5 +119,6 @@ let decode =
; runtest_alias
; timeout
; conflict_markers
; setup_scripts
})
;;
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 @@ -23,6 +23,7 @@ type t =
; package : Package.t option
; runtest_alias : (Loc.t * bool) option
; timeout : (Loc.t * float) option
; setup_scripts : (Loc.t * string) list
}

val decode : t Dune_lang.Decoder.t
Expand Down
46 changes: 46 additions & 0 deletions test/blackbox-tests/test-cases/cram-setup-scripts/basic.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
Test setup_scripts feature for cram tests

Create a project with a helper script:

$ cat > dune-project << EOF
> (lang dune 3.21)
> (cram enable)
Copy link
Collaborator

Choose a reason for hiding this comment

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

Suggested change
> (cram enable)

> EOF

$ cat > helpers.sh << 'EOF'
> #!/bin/sh
> test_helper() {
> echo "Helper called: $1"
> }
> export MY_VAR="test_value_from_helper"
> EOF

$ cat > dune << EOF
> (cram
> (setup_scripts helpers.sh))
> EOF

$ cat > basic.t << 'EOF'
> Test that setup scripts are sourced and functions are available
>
> $ test_helper "foo"
> Helper called: foo
>
> Test that variables from setup scripts are available
>
> $ echo $MY_VAR
> test_value_from_helper
>
> Check if setup script is visible in test directory
>
> $ ls *.sh 2>&1 || echo "No sh files"
> No sh files
> EOF

Run the test:

$ dune runtest
File "basic.t", line 1, characters 0-0:
Error: Files _build/default/basic.t and _build/default/basic.t.corrected
differ.
[1]
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
Test if setup scripts are visible in test directory

$ cat > dune-project << EOF
> (lang dune 3.21)
> (cram enable)
Copy link
Collaborator

Choose a reason for hiding this comment

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

Suggested change
> (cram enable)

> EOF

$ cat > secret.sh << 'EOF'
> MY_SECRET="should_not_be_visible"
> EOF

$ cat > dune << EOF
> (cram
> (setup_scripts secret.sh))
> EOF

$ cat > check.t << 'EOF'
> $ ls *.sh 2>&1 || echo "No .sh files found"
> No .sh files found
> EOF

$ dune runtest
File "check.t", line 1, characters 0-0:
Error: Files _build/default/check.t and _build/default/check.t.corrected
differ.
[1]
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
Test that external (absolute path) setup scripts work and are NOT deleted

First, create an external script in /tmp:

$ EXTERNAL_SCRIPT="/tmp/dune_test_external_helper_$$.sh"
$ cat > "$EXTERNAL_SCRIPT" << 'EOF'
> #!/bin/sh
> external_helper() {
> echo "External helper called"
> }
> export EXTERNAL_VAR="from_external_script"
> EOF
$ chmod +x "$EXTERNAL_SCRIPT"

Create a project that uses the external script:

$ cat > dune-project << EOF
> (lang dune 3.21)
> (cram enable)
Copy link
Collaborator

Choose a reason for hiding this comment

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

Suggested change
> (cram enable)

> EOF

$ cat > dune << EOF
> (cram
> (setup_scripts $EXTERNAL_SCRIPT))
> EOF

Create a test that uses the external helper:

$ cat > external.t << 'EOF'
> Test that external helper is available
>
> $ external_helper
> External helper called
>
> $ echo $EXTERNAL_VAR
> from_external_script
> EOF

Run the test:

$ dune runtest
Copy link
Collaborator

Choose a reason for hiding this comment

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

Can we make this test fail so that we can see it has run.


Verify the external script still exists (was NOT deleted):

$ if [ -f "$EXTERNAL_SCRIPT" ]; then
> echo "External script still exists"
> else
> echo "External script was deleted"
> fi
External script still exists
Loading
Loading