Skip to content

Commit af6e1f5

Browse files
committed
cram: locations for timeouts
Signed-off-by: Ali Caglayan <[email protected]>
1 parent b442b90 commit af6e1f5

File tree

3 files changed

+44
-35
lines changed

3 files changed

+44
-35
lines changed

src/dune_rules/cram/cram_exec.ml

Lines changed: 36 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -349,9 +349,9 @@ let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
349349
let* metadata_file_sh_path = sh_path metadata_file in
350350
let i = ref 0 in
351351
let loop block =
352-
match (block : _ Cram_lexer.block) with
352+
match (block : (Loc.t * string list) Cram_lexer.block) with
353353
| Comment _ as comment -> Fiber.return comment
354-
| Command lines ->
354+
| Command (_, lines) ->
355355
incr i;
356356
let i = !i in
357357
let file ~ext = file (sprintf "%d%s" i ext) in
@@ -455,46 +455,46 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
455455
| Ok () -> read_and_attach_exit_codes sh_script |> sanitize ~parent_script:script
456456
| Error `Timed_out ->
457457
let timeout_loc, timeout = Option.value_exn timeout in
458-
let timeout_set_message =
459-
[ Pp.textf "A time limit of %.2fs has been set in " timeout
460-
; Pp.tag User_message.Style.Loc @@ Loc.pp_file_colon_line timeout_loc
461-
]
462-
|> Pp.concat
463-
|> Pp.hovbox
464-
in
465-
let timeout_msg =
458+
let loc =
466459
match
467460
let completed_count =
468461
read_exit_codes_and_prefix_maps sh_script.metadata_file |> List.length
469462
in
470-
let command_blocks_only =
471-
List.filter_map sh_script.cram_to_output ~f:(function
463+
let original_command_locs =
464+
List.filter_map cram_stanzas ~f:(function
472465
| Cram_lexer.Comment _ -> None
473-
| Cram_lexer.Command block_result -> Some block_result)
466+
| Cram_lexer.Command (loc, _) -> Some loc)
474467
in
475-
let total_commands = List.length command_blocks_only in
468+
let total_commands = List.length original_command_locs in
476469
if completed_count < total_commands
477-
then (
470+
then
478471
(* Find the command that got stuck - it's the one at index completed_count *)
479-
match List.nth command_blocks_only completed_count with
480-
| Some { command; _ } -> Some (String.concat ~sep:" " command)
481-
| None -> None)
472+
List.nth original_command_locs completed_count
482473
else None
483474
with
484-
| None -> [ Pp.text "Cram test timed out" ]
485-
| Some cmd ->
486-
[ Pp.textf "Cram test timed out while running command:"
487-
; Pp.verbatimf " $ %s" cmd
488-
]
475+
| None -> Loc.in_file (Path.drop_optional_build_context_maybe_sandboxed src)
476+
| Some loc -> loc
489477
in
490478
User_error.raise
491-
~loc:(Loc.in_file (Path.drop_optional_build_context_maybe_sandboxed src))
492-
(timeout_msg @ [ timeout_set_message ])
479+
~loc
480+
[ Pp.text "Cram test timed out"
481+
; [ Pp.textf "A time limit of %.2fs has been set in " timeout
482+
; Pp.tag User_message.Style.Loc @@ Loc.pp_file_colon_line timeout_loc
483+
]
484+
|> Pp.concat
485+
|> Pp.hovbox
486+
]
493487
;;
494488

495489
let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
496490
let temp_dir = make_temp_dir ~script in
497-
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers |> List.map ~f:snd in
491+
let cram_stanzas =
492+
cram_stanzas lexbuf ~conflict_markers
493+
|> List.map ~f:(fun (loc, block) ->
494+
match block with
495+
| Cram_lexer.Comment lines -> Cram_lexer.Comment lines
496+
| Cram_lexer.Command lines -> Cram_lexer.Command (loc, lines))
497+
in
498498
let cwd = Path.parent_exn script in
499499
let env = make_run_env env ~temp_dir ~cwd in
500500
let open Fiber.O in
@@ -512,10 +512,17 @@ module Script = Persistent.Make (struct
512512
end)
513513

514514
let run_and_produce_output ~conflict_markers ~src ~env ~dir:cwd ~script ~dst ~timeout =
515-
let script_contents = Io.read_file ~binary:false script in
516-
let lexbuf = Lexbuf.from_string script_contents ~fname:(Path.to_string script) in
515+
let script_contents = Io.read_file ~binary:false src in
516+
let clean_src_name = Path.Source.to_string (Path.drop_build_context_exn src) in
517+
let lexbuf = Lexbuf.from_string script_contents ~fname:clean_src_name in
517518
let temp_dir = make_temp_dir ~script in
518-
let cram_stanzas = cram_stanzas lexbuf ~conflict_markers |> List.map ~f:snd in
519+
let cram_stanzas =
520+
cram_stanzas lexbuf ~conflict_markers
521+
|> List.map ~f:(fun (loc, block) ->
522+
match block with
523+
| Cram_lexer.Comment lines -> Cram_lexer.Comment lines
524+
| Cram_lexer.Command lines -> Cram_lexer.Command (loc, lines))
525+
in
519526
(* We don't want the ".cram.run.t" dir around when executing the script. *)
520527
Path.rm_rf (Path.parent_exn script);
521528
let env = make_run_env env ~temp_dir ~cwd in

test/blackbox-tests/test-cases/cram/timeout-no-command.t

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -23,9 +23,10 @@ Run the test and verify that the timeout error doesn't mention
2323
which specific command caused the timeout:
2424

2525
$ dune test test.t
26-
File "test.t", line 1, characters 0-0:
27-
Error: Cram test timed out while running command:
28-
$ echo "This is the problematic command" && sleep 2
26+
File "test.t", line 2, characters 2-53:
27+
2 | $ echo "This is the problematic command" && sleep 2
28+
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
29+
Error: Cram test timed out
2930
A time limit of 0.10s has been set in dune:2
3031
[1]
3132

test/blackbox-tests/test-cases/cram/timeout.t

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,9 @@ fails earlier by passing a timeout command in front of dune. Our expected
4040
behaviour is for dune to kill the cram test immediately.
4141

4242
$ timeout 1 dune test test.t 2>&1 | sed 's/echo hi/command/' | sed 's/sleep 2/command/'
43-
File "test.t", line 1, characters 0-0:
44-
Error: Cram test timed out while running command:
45-
$ command
43+
File "test.t", line 1, characters 2-11:
44+
1 | $ command
45+
^^^^^^^^^
46+
Error: Cram test timed out
4647
A time limit of 0.00s has been set in dune:2
4748

0 commit comments

Comments
 (0)