1
1
open Import
2
2
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
-
92
3
(* Translate a path for [sh]. On Windows, [sh] will come from Cygwin so if we
93
4
are a real windows program we need to pass the path through [cygpath] *)
94
5
let translate_path_for_sh =
@@ -266,9 +177,16 @@ let rewrite_paths build_path_prefix_map ~parent_script ~command_script s =
266
177
" Cannot decode build prefix map"
267
178
[ " build_path_prefix_map" , String build_path_prefix_map; " msg" , String msg ]
268
179
| 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
272
190
in
273
191
let error_msg =
274
192
let open Re in
@@ -281,7 +199,7 @@ let rewrite_paths build_path_prefix_map ~parent_script ~command_script s =
281
199
let b = seq [ command_script; str " : line " ; line_number; str " : " ] in
282
200
[ a; b ] |> List. map ~f: (fun re -> seq [ bol; re ]) |> alt |> compile
283
201
in
284
- Re. replace abs_path_re s ~f: (fun g ->
202
+ Re. replace ~all: true known_paths s ~f: (fun g ->
285
203
Build_path_prefix_map. rewrite map (Re.Group. get g 0 ))
286
204
|> Re. replace_string error_msg ~by: " "
287
205
;;
@@ -406,19 +324,16 @@ let run ~env ~script lexbuf : string Fiber.t =
406
324
let open Fiber.O in
407
325
let * sh_script = create_sh_script cram_stanzas ~temp_dir in
408
326
let cwd = Path. parent_exn script in
327
+ let temp_dir = Path. relative temp_dir " tmp" in
328
+ Path. mkdir_p temp_dir;
409
329
let env =
410
330
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
+ ]
422
337
in
423
338
let open Fiber.O in
424
339
let + () =
@@ -442,6 +357,7 @@ let run ~env ~script lexbuf : string Fiber.t =
442
357
~display: Quiet
443
358
~metadata
444
359
~dir: cwd
360
+ ~temp_dir
445
361
~env
446
362
Strict
447
363
sh
0 commit comments