@@ -340,9 +340,9 @@ let create_sh_script cram_stanzas ~temp_dir : sh_script Fiber.t =
340340 let * metadata_file_sh_path = sh_path metadata_file in
341341 let i = ref 0 in
342342 let loop block =
343- match (block : _ Cram_lexer.block ) with
343+ match (block : (Loc.t * string list ) Cram_lexer. block) with
344344 | Comment _ as comment -> Fiber. return comment
345- | Command lines ->
345+ | Command ( _ , lines ) ->
346346 incr i;
347347 let i = ! i in
348348 let file ~ext = file (sprintf " %d%s" i ext) in
@@ -446,46 +446,46 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
446446 | Ok () -> read_and_attach_exit_codes sh_script |> sanitize ~parent_script: script
447447 | Error `Timed_out ->
448448 let timeout_loc, timeout = Option. value_exn timeout in
449- let timeout_set_message =
450- [ Pp. textf " A time limit of %.2fs has been set in " timeout
451- ; Pp. tag User_message.Style. Loc @@ Loc. pp_file_colon_line timeout_loc
452- ]
453- |> Pp. concat
454- |> Pp. hovbox
455- in
456- let timeout_msg =
449+ let loc =
457450 match
458451 let completed_count =
459452 read_exit_codes_and_prefix_maps sh_script.metadata_file |> List. length
460453 in
461- let command_blocks_only =
462- List. filter_map sh_script.cram_to_output ~f: (function
454+ let original_command_locs =
455+ List. filter_map cram_stanzas ~f: (function
463456 | Cram_lexer. Comment _ -> None
464- | Cram_lexer. Command block_result -> Some block_result )
457+ | Cram_lexer. Command ( loc , _ ) -> Some loc )
465458 in
466- let total_commands = List. length command_blocks_only in
459+ let total_commands = List. length original_command_locs in
467460 if completed_count < total_commands
468- then (
461+ then
469462 (* Find the command that got stuck - it's the one at index completed_count *)
470- match List. nth command_blocks_only completed_count with
471- | Some { command; _ } -> Some (String. concat ~sep: " " command)
472- | None -> None )
463+ List. nth original_command_locs completed_count
473464 else None
474465 with
475- | None -> [ Pp. text " Cram test timed out" ]
476- | Some cmd ->
477- [ Pp. textf " Cram test timed out while running command:"
478- ; Pp. verbatimf " $ %s" cmd
479- ]
466+ | None -> Loc. in_file (Path. drop_optional_build_context_maybe_sandboxed src)
467+ | Some loc -> loc
480468 in
481469 User_error. raise
482- ~loc: (Loc. in_file (Path. drop_optional_build_context_maybe_sandboxed src))
483- (timeout_msg @ [ timeout_set_message ])
470+ ~loc
471+ [ Pp. text " Cram test timed out"
472+ ; [ Pp. textf " A time limit of %.2fs has been set in " timeout
473+ ; Pp. tag User_message.Style. Loc @@ Loc. pp_file_colon_line timeout_loc
474+ ]
475+ |> Pp. concat
476+ |> Pp. hovbox
477+ ]
484478;;
485479
486480let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
487481 let temp_dir = make_temp_dir ~script in
488- let cram_stanzas = cram_stanzas lexbuf ~conflict_markers |> List. map ~f: snd in
482+ let cram_stanzas =
483+ cram_stanzas lexbuf ~conflict_markers
484+ |> List. map ~f: (fun (loc , block ) ->
485+ match block with
486+ | Cram_lexer. Comment lines -> Cram_lexer. Comment lines
487+ | Cram_lexer. Command lines -> Cram_lexer. Command (loc, lines))
488+ in
489489 let cwd = Path. parent_exn script in
490490 let env = make_run_env env ~temp_dir ~cwd in
491491 let open Fiber.O in
@@ -503,10 +503,17 @@ module Script = Persistent.Make (struct
503503 end )
504504
505505let run_and_produce_output ~conflict_markers ~src ~env ~dir :cwd ~script ~dst ~timeout =
506- let script_contents = Io. read_file ~binary: false script in
507- let lexbuf = Lexbuf. from_string script_contents ~fname: (Path. to_string script) in
506+ let script_contents = Io. read_file ~binary: false src in
507+ let clean_src_name = Path.Source. to_string (Path. drop_build_context_exn src) in
508+ let lexbuf = Lexbuf. from_string script_contents ~fname: clean_src_name in
508509 let temp_dir = make_temp_dir ~script in
509- let cram_stanzas = cram_stanzas lexbuf ~conflict_markers |> List. map ~f: snd in
510+ let cram_stanzas =
511+ cram_stanzas lexbuf ~conflict_markers
512+ |> List. map ~f: (fun (loc , block ) ->
513+ match block with
514+ | Cram_lexer. Comment lines -> Cram_lexer. Comment lines
515+ | Cram_lexer. Command lines -> Cram_lexer. Command (loc, lines))
516+ in
510517 (* We don't want the ".cram.run.t" dir around when executing the script. *)
511518 Path. rm_rf (Path. parent_exn script);
512519 let env = make_run_env env ~temp_dir ~cwd in
0 commit comments