Skip to content
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.

Commit 307645b

Browse files
committedJan 29, 2025·
Fix cram tests build-path-prefix-map substitutions
Signed-off-by: ArthurW <arthur@tarides.com>
1 parent e43cb9d commit 307645b

File tree

7 files changed

+128
-118
lines changed

7 files changed

+128
-118
lines changed
 

‎doc/changes/11366.md

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
- Fix cram tests build-path-prefix-map substitutions (#11366, @art-w)

‎doc/tests.rst

+2-2
Original file line numberDiff line numberDiff line change
@@ -690,9 +690,9 @@ the standard BUILD_PATH_PREFIX_MAP_ environment variable. For example:
690690

691691
.. code:: console
692692
693-
$ export BUILD_PATH_PREFIX_MAP="HOME=$HOME:$BUILD_PATH_PREFIX_MAP"
693+
$ export BUILD_PATH_PREFIX_MAP="/HOME=$HOME:$BUILD_PATH_PREFIX_MAP"
694694
$ echo $HOME
695-
$HOME
695+
/HOME
696696
697697
Note: Unlike Dune's version of Cram, the original specification for Cram
698698
supports regular expression and glob filtering for matching output. We chose

‎src/dune_engine/process.ml

+40-10
Original file line numberDiff line numberDiff line change
@@ -846,6 +846,14 @@ let report_process_finished
846846

847847
let set_temp_dir_when_running_actions = ref true
848848

849+
let set_temp_dir ~temp_dir env =
850+
match temp_dir, !set_temp_dir_when_running_actions with
851+
| Some path, _ ->
852+
Env.add env ~var:Env.Var.temp_dir ~value:(Path.to_absolute_filename path)
853+
| None, true -> Dtemp.add_to_env env
854+
| None, false -> env
855+
;;
856+
849857
let await { response_file; pid; _ } =
850858
let+ process_info, termination_reason =
851859
Scheduler.wait_for_build_process pid ~is_process_group_leader:true
@@ -856,6 +864,7 @@ let await { response_file; pid; _ } =
856864

857865
let spawn
858866
?dir
867+
?temp_dir
859868
?(env = Env.initial)
860869
~(stdout : _ Io.t)
861870
~(stderr : _ Io.t)
@@ -924,14 +933,7 @@ let spawn
924933
Unix.gettimeofday ()
925934
in
926935
let pid =
927-
let env =
928-
let env =
929-
match !set_temp_dir_when_running_actions with
930-
| true -> Dtemp.add_to_env env
931-
| false -> env
932-
in
933-
Env.to_unix env |> Spawn.Env.of_list
934-
in
936+
let env = set_temp_dir ~temp_dir env |> Env.to_unix |> Spawn.Env.of_list in
935937
let stdout = Io.fd stdout in
936938
let stderr = Io.fd stderr in
937939
let stdin = Io.fd stdin in
@@ -967,6 +969,7 @@ let spawn
967969

968970
let run_internal
969971
?dir
972+
?temp_dir
970973
~(display : Display.t)
971974
?(stdout_to = Io.stdout)
972975
?(stderr_to = Io.stderr)
@@ -1006,7 +1009,16 @@ let run_internal
10061009
| _ -> Pp.nop
10071010
in
10081011
let t =
1009-
spawn ?dir ?env ~stdout:stdout_to ~stderr:stderr_to ~stdin:stdin_from ~prog ~args ()
1012+
spawn
1013+
?dir
1014+
?temp_dir
1015+
?env
1016+
~stdout:stdout_to
1017+
~stderr:stderr_to
1018+
~stdin:stdin_from
1019+
~prog
1020+
~args
1021+
()
10101022
in
10111023
let* () =
10121024
let description =
@@ -1083,11 +1095,23 @@ let run_internal
10831095
res, times)
10841096
;;
10851097

1086-
let run ?dir ~display ?stdout_to ?stderr_to ?stdin_from ?env ?metadata fail_mode prog args
1098+
let run
1099+
?dir
1100+
?temp_dir
1101+
~display
1102+
?stdout_to
1103+
?stderr_to
1104+
?stdin_from
1105+
?env
1106+
?metadata
1107+
fail_mode
1108+
prog
1109+
args
10871110
=
10881111
let+ run =
10891112
run_internal
10901113
?dir
1114+
?temp_dir
10911115
~display
10921116
?stdout_to
10931117
?stderr_to
@@ -1104,6 +1128,7 @@ let run ?dir ~display ?stdout_to ?stderr_to ?stdin_from ?env ?metadata fail_mode
11041128

11051129
let run_with_times
11061130
?dir
1131+
?temp_dir
11071132
~display
11081133
?stdout_to
11091134
?stderr_to
@@ -1117,6 +1142,7 @@ let run_with_times
11171142
let+ code, times =
11181143
run_internal
11191144
?dir
1145+
?temp_dir
11201146
~display
11211147
?stdout_to
11221148
?stderr_to
@@ -1132,6 +1158,7 @@ let run_with_times
11321158

11331159
let run_capture_gen
11341160
?dir
1161+
?temp_dir
11351162
~display
11361163
?stderr_to
11371164
?stdin_from
@@ -1146,6 +1173,7 @@ let run_capture_gen
11461173
let+ run =
11471174
run_internal
11481175
?dir
1176+
?temp_dir
11491177
~display
11501178
~stdout_to:(Io.file fn Io.Out)
11511179
?stderr_to
@@ -1169,6 +1197,7 @@ let run_capture_zero_separated = run_capture_gen ~f:Stdune.Io.zero_strings_of_fi
11691197

11701198
let run_capture_line
11711199
?dir
1200+
?temp_dir
11721201
~display
11731202
?stderr_to
11741203
?stdin_from
@@ -1180,6 +1209,7 @@ let run_capture_line
11801209
=
11811210
run_capture_gen
11821211
?dir
1212+
?temp_dir
11831213
~display
11841214
?stderr_to
11851215
?stdin_from

‎src/dune_engine/process.mli

+6
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,7 @@ val set_temp_dir_when_running_actions : bool ref
9090
termination. [stdout_to] [stderr_to] are released *)
9191
val run
9292
: ?dir:Path.t
93+
-> ?temp_dir:Path.t
9394
-> display:Display.t
9495
-> ?stdout_to:Io.output Io.t
9596
-> ?stderr_to:Io.output Io.t
@@ -103,6 +104,7 @@ val run
103104

104105
val run_with_times
105106
: ?dir:Path.t
107+
-> ?temp_dir:Path.t
106108
-> display:Display.t
107109
-> ?stdout_to:Io.output Io.t
108110
-> ?stderr_to:Io.output Io.t
@@ -117,6 +119,7 @@ val run_with_times
117119
(** Run a command and capture its output *)
118120
val run_capture
119121
: ?dir:Path.t
122+
-> ?temp_dir:Path.t
120123
-> display:Display.t
121124
-> ?stderr_to:Io.output Io.t
122125
-> ?stdin_from:Io.input Io.t
@@ -129,6 +132,7 @@ val run_capture
129132

130133
val run_capture_line
131134
: ?dir:Path.t
135+
-> ?temp_dir:Path.t
132136
-> display:Display.t
133137
-> ?stderr_to:Io.output Io.t
134138
-> ?stdin_from:Io.input Io.t
@@ -141,6 +145,7 @@ val run_capture_line
141145

142146
val run_capture_lines
143147
: ?dir:Path.t
148+
-> ?temp_dir:Path.t
144149
-> display:Display.t
145150
-> ?stderr_to:Io.output Io.t
146151
-> ?stdin_from:Io.input Io.t
@@ -153,6 +158,7 @@ val run_capture_lines
153158

154159
val run_capture_zero_separated
155160
: ?dir:Path.t
161+
-> ?temp_dir:Path.t
156162
-> display:Display.t
157163
-> ?stderr_to:Io.output Io.t
158164
-> ?stdin_from:Io.input Io.t

‎src/dune_rules/cram/cram_exec.ml

+20-104
Original file line numberDiff line numberDiff line change
@@ -1,94 +1,5 @@
11
open Import
22

3-
module Sanitizer : sig
4-
[@@@ocaml.warning "-32"]
5-
6-
module Command : sig
7-
type t =
8-
{ output : string
9-
; build_path_prefix_map : string
10-
; script : Path.t
11-
}
12-
end
13-
14-
val impl_sanitizer : (Command.t -> string) -> in_channel -> out_channel -> unit
15-
16-
val run_sanitizer
17-
: ?temp_dir:Path.t
18-
-> prog:Path.t
19-
-> argv:string list
20-
-> Command.t list
21-
-> string list Fiber.t
22-
end = struct
23-
module Command = struct
24-
type t =
25-
{ output : string
26-
; build_path_prefix_map : string
27-
; script : Path.t
28-
}
29-
30-
let of_sexp script (csexp : Sexp.t) : t =
31-
match csexp with
32-
| List [ Atom build_path_prefix_map; Atom output ] ->
33-
{ build_path_prefix_map; output; script }
34-
| _ -> Code_error.raise "Command.of_csexp: invalid csexp" []
35-
;;
36-
37-
let to_sexp { output; build_path_prefix_map; script } : Sexp.t =
38-
List
39-
[ Atom build_path_prefix_map
40-
; Atom output
41-
; Atom (Path.to_absolute_filename script)
42-
]
43-
;;
44-
end
45-
46-
let run_sanitizer ?temp_dir ~prog ~argv commands =
47-
let temp_dir =
48-
match temp_dir with
49-
| Some d -> d
50-
| None -> Temp.create Dir ~prefix:"sanitizer" ~suffix:"unspecified"
51-
in
52-
let fname = Path.relative temp_dir in
53-
let stdout_path = fname "sanitizer.stdout" in
54-
let stdout_to = Process.Io.file stdout_path Process.Io.Out in
55-
let stdin_from =
56-
let path = fname "sanitizer.stdin" in
57-
let csexp = List.map commands ~f:Command.to_sexp in
58-
Io.with_file_out ~binary:true path ~f:(fun oc ->
59-
List.iter csexp ~f:(Csexp.to_channel oc));
60-
Process.Io.file path Process.Io.In
61-
in
62-
let open Fiber.O in
63-
let+ () = Process.run ~display:Quiet ~stdin_from ~stdout_to Strict prog argv in
64-
Io.with_file_in stdout_path ~f:(fun ic ->
65-
let rec loop acc =
66-
match Csexp.input_opt ic with
67-
| Ok None -> List.rev acc
68-
| Ok (Some (Sexp.Atom s)) -> loop (s :: acc)
69-
| Error error -> Code_error.raise "invalid csexp" [ "error", String error ]
70-
| Ok _ -> Code_error.raise "unexpected output" []
71-
in
72-
loop [])
73-
;;
74-
75-
let impl_sanitizer f in_ out =
76-
set_binary_mode_in in_ true;
77-
set_binary_mode_out out true;
78-
let rec loop () =
79-
match Csexp.input_opt in_ with
80-
| Error error -> Code_error.raise "unable to parse csexp" [ "error", String error ]
81-
| Ok None -> ()
82-
| Ok (Some sexp) ->
83-
let command = Command.of_sexp (assert false) sexp in
84-
Csexp.to_channel out (Atom (f command));
85-
flush out;
86-
loop ()
87-
in
88-
loop ()
89-
;;
90-
end
91-
923
(* Translate a path for [sh]. On Windows, [sh] will come from Cygwin so if we
934
are a real windows program we need to pass the path through [cygpath] *)
945
let translate_path_for_sh =
@@ -266,9 +177,16 @@ let rewrite_paths build_path_prefix_map ~parent_script ~command_script s =
266177
"Cannot decode build prefix map"
267178
[ "build_path_prefix_map", String build_path_prefix_map; "msg", String msg ]
268179
| Ok map ->
269-
let abs_path_re =
270-
let not_dir = Printf.sprintf " \n\r\t%c" Bin.path_sep in
271-
Re.(compile (seq [ char '/'; rep1 (diff any (set not_dir)) ]))
180+
let known_paths =
181+
List.filter_map
182+
~f:(function
183+
| None | Some { Build_path_prefix_map.source = ""; _ } -> None
184+
| Some pair -> Some (Re.str pair.source))
185+
map
186+
|> List.rev
187+
(* prefer right-most paths in the list, as required by the build-path-prefix-map spec *)
188+
|> Re.alt
189+
|> Re.compile
272190
in
273191
let error_msg =
274192
let open Re in
@@ -281,7 +199,7 @@ let rewrite_paths build_path_prefix_map ~parent_script ~command_script s =
281199
let b = seq [ command_script; str ": line "; line_number; str ": " ] in
282200
[ a; b ] |> List.map ~f:(fun re -> seq [ bol; re ]) |> alt |> compile
283201
in
284-
Re.replace abs_path_re s ~f:(fun g ->
202+
Re.replace ~all:true known_paths s ~f:(fun g ->
285203
Build_path_prefix_map.rewrite map (Re.Group.get g 0))
286204
|> Re.replace_string error_msg ~by:""
287205
;;
@@ -406,19 +324,16 @@ let run ~env ~script lexbuf : string Fiber.t =
406324
let open Fiber.O in
407325
let* sh_script = create_sh_script cram_stanzas ~temp_dir in
408326
let cwd = Path.parent_exn script in
327+
let temp_dir = Path.relative temp_dir "tmp" in
328+
Path.mkdir_p temp_dir;
409329
let env =
410330
let env = Env.add env ~var:"LC_ALL" ~value:"C" in
411-
let temp_dir = Path.relative temp_dir "tmp" in
412-
let env =
413-
Dune_util.Build_path_prefix_map.extend_build_path_prefix_map
414-
env
415-
`New_rules_have_precedence
416-
[ Some { source = Path.to_absolute_filename cwd; target = "$TESTCASE_ROOT" }
417-
; Some { source = Path.to_absolute_filename temp_dir; target = "$TMPDIR" }
418-
]
419-
in
420-
Path.mkdir_p temp_dir;
421-
Env.add env ~var:Env.Var.temp_dir ~value:(Path.to_absolute_filename temp_dir)
331+
Dune_util.Build_path_prefix_map.extend_build_path_prefix_map
332+
env
333+
`New_rules_have_precedence
334+
[ Some { source = Path.to_absolute_filename cwd; target = "$TESTCASE_ROOT" }
335+
; Some { source = Path.to_absolute_filename temp_dir; target = "$TMPDIR" }
336+
]
422337
in
423338
let open Fiber.O in
424339
let+ () =
@@ -442,6 +357,7 @@ let run ~env ~script lexbuf : string Fiber.t =
442357
~display:Quiet
443358
~metadata
444359
~dir:cwd
360+
~temp_dir
445361
~env
446362
Strict
447363
sh
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
The build-path-prefix-map substitutes any dynamic path in the output of
2+
commands, to help with reproducibility:
3+
4+
$ PWD=$(pwd)
5+
$ echo $PWD
6+
$TESTCASE_ROOT
7+
$ echo /nest/$PWD/sub/dir
8+
/nest/$TESTCASE_ROOT/sub/dir
9+
$ echo "[\"$PWD\",\"$PWD\"]"
10+
["$TESTCASE_ROOT","$TESTCASE_ROOT"]
11+
12+
Besides the current `$TESTCASE_ROOT` directory, an empty `$TMPDIR` is available:
13+
14+
$ ls -a $TMPDIR
15+
.
16+
..
17+
$ echo $TMPDIR
18+
$TMPDIR
19+
$ echo $TMPDIR/sub/dir
20+
$TMPDIR/sub/dir
21+
$ echo The tempdir is at:$TMPDIR:
22+
The tempdir is at:$TMPDIR:
23+
24+
And the dune workspace root is replaced by `/workspace_root`:
25+
26+
$ dirname $(pwd)
27+
/workspace_root/default/test/blackbox-tests/test-cases
28+
29+
The environment variable `$BUILD_PATH_PREFIX_MAP` can be extended with new
30+
entries, e.g. the user `$HOME` directory:
31+
32+
$ export BUILD_PATH_PREFIX_MAP="HOME=$HOME:$BUILD_PATH_PREFIX_MAP"
33+
$ echo $HOME
34+
HOME
35+
36+
Spaces in paths are supported:
37+
38+
$ SPACED="path/contains spaces/.but/it's not an"
39+
$ echo /this/$SPACED/issue
40+
/this/path/contains spaces/.but/it's not an/issue
41+
$ export BUILD_PATH_PREFIX_MAP="\$SPACED=$SPACED:$BUILD_PATH_PREFIX_MAP"
42+
$ echo /this/$SPACED/issue
43+
/this/$SPACED/issue
44+
45+
Right-most entries are preferred:
46+
47+
$ SUBDIR="$(pwd)/sub"
48+
$ export BUILD_PATH_PREFIX_MAP="\$LEFT=$SUBDIR:$BUILD_PATH_PREFIX_MAP"
49+
$ echo $SUBDIR
50+
$TESTCASE_ROOT/sub
51+
$ export BUILD_PATH_PREFIX_MAP="$BUILD_PATH_PREFIX_MAP:\$RIGHT=$SUBDIR"
52+
$ echo $SUBDIR
53+
$RIGHT
54+
55+
Inspecting the `$BUILD_PATH_PREFIX_MAP` should show no dynamic path as they are
56+
all replaced by their binding:
57+
58+
$ echo $BUILD_PATH_PREFIX_MAP
59+
$LEFT=$RIGHT:$SPACED=$SPACED:HOME=HOME:/workspace_root=/workspace_root:$TESTCASE_ROOT=$TESTCASE_ROOT:$TMPDIR=$TMPDIR:$RIGHT=$RIGHT

‎test/blackbox-tests/test-cases/pkg/install-action.t

-2
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,6 @@ Testing install actions
1111
$ build_pkg test
1212
foobar
1313

14-
$ export BUILD_PATH_PREFIX_MAP="/PKG_ROOT=test/target:$BUILD_PATH_PREFIX_MAP"
15-
1614
$ show_pkg_targets test
1715

1816
/bin

0 commit comments

Comments
 (0)
Please sign in to comment.