@@ -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
495489let 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
514514let 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
0 commit comments