@@ -55,10 +55,12 @@ let cram_stanzas =
5555 (* CR-someday rgrinberg for alizter: insert a location spanning the
5656 entire once we start extracting it *)
5757 User_error. raise
58- [ Pp. text " Conflict found. Please remove it or set (conflict allow)" ]
58+ [ Pp. text
59+ " Conflict marker found. Please remove it or set (conflict_markers allow)"
60+ ]
5961 | _ -> state
6062 in
61- fun ~(conflict : Cram_stanza.Conflict .t ) lexbuf ->
63+ fun ~(conflict_markers : Cram_stanza.Conflict_markers .t ) lexbuf ->
6264 let rec loop acc conflict_state =
6365 match Cram_lexer. block lexbuf with
6466 | None -> List. rev acc
@@ -67,7 +69,7 @@ let cram_stanzas =
6769 match s with
6870 | Command _ -> conflict_state
6971 | Comment lines ->
70- (match conflict with
72+ (match conflict_markers with
7173 | Ignore -> conflict_state
7274 | Error -> List. fold_left lines ~init: conflict_state ~f: find_conflict)
7375 in
@@ -77,7 +79,7 @@ let cram_stanzas =
7779;;
7880
7981module For_tests = struct
80- let cram_stanzas lexbuf = cram_stanzas lexbuf ~conflict : Ignore
82+ let cram_stanzas lexbuf = cram_stanzas lexbuf ~conflict_markers : Ignore
8183
8284 let dyn_of_block = function
8385 | Cram_lexer. Comment lines -> Dyn. variant " Comment" [ Dyn. list Dyn. string lines ]
@@ -482,9 +484,9 @@ let run_cram_test env ~src ~script ~cram_stanzas ~temp_dir ~cwd ~timeout =
482484 (timeout_msg @ [ timeout_set_message ])
483485;;
484486
485- let run_produce_correction ~conflict ~src ~env ~script ~timeout lexbuf =
487+ let run_produce_correction ~conflict_markers ~src ~env ~script ~timeout lexbuf =
486488 let temp_dir = make_temp_dir ~script in
487- let cram_stanzas = cram_stanzas lexbuf ~conflict in
489+ let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
488490 let cwd = Path. parent_exn script in
489491 let env = make_run_env env ~temp_dir ~cwd in
490492 let open Fiber.O in
@@ -501,11 +503,11 @@ module Script = Persistent.Make (struct
501503 let test_example () = []
502504 end )
503505
504- let run_and_produce_output ~conflict ~src ~env ~dir :cwd ~script ~dst ~timeout =
506+ let run_and_produce_output ~conflict_markers ~src ~env ~dir :cwd ~script ~dst ~timeout =
505507 let script_contents = Io. read_file ~binary: false script in
506508 let lexbuf = Lexbuf. from_string script_contents ~fname: (Path. to_string script) in
507509 let temp_dir = make_temp_dir ~script in
508- let cram_stanzas = cram_stanzas lexbuf ~conflict in
510+ let cram_stanzas = cram_stanzas lexbuf ~conflict_markers in
509511 (* We don't want the ".cram.run.t" dir around when executing the script. *)
510512 Path. rm_rf (Path. parent_exn script);
511513 let env = make_run_env env ~temp_dir ~cwd in
@@ -552,7 +554,7 @@ module Run = struct
552554
553555 let action { src; dir; script; output; timeout } ~ectx :_ ~(eenv : Action.env ) =
554556 run_and_produce_output
555- ~conflict : Ignore
557+ ~conflict_markers : Ignore
556558 ~src
557559 ~env: eenv.env
558560 ~dir
@@ -574,30 +576,30 @@ module Make_script = struct
574576 type ('path, 'target) t =
575577 { script : 'path
576578 ; target : 'target
577- ; conflict : Cram_stanza.Conflict .t
579+ ; conflict_markers : Cram_stanza.Conflict_markers .t
578580 }
579581
580582 let name = " cram-generate"
581583 let version = 2
582584 let bimap t f g = { t with script = f t.script; target = g t.target }
583585 let is_useful_to ~memoize :_ = true
584586
585- let encode { script = src ; target = dst ; conflict } path target : Sexp.t =
587+ let encode { script = src ; target = dst ; conflict_markers } path target : Sexp.t =
586588 List
587589 [ path src
588590 ; target dst
589591 ; Atom
590- (match conflict with
592+ (match conflict_markers with
591593 | Error -> " error"
592594 | Ignore -> " ignore" )
593595 ]
594596 ;;
595597
596- let action { script = src ; target = dst ; conflict } ~ectx :_ ~eenv :_ =
598+ let action { script = src ; target = dst ; conflict_markers } ~ectx :_ ~eenv :_ =
597599 let commands =
598600 Io. read_file ~binary: false src
599601 |> Lexbuf. from_string ~fname: (Path. to_string src)
600- |> cram_stanzas ~conflict
602+ |> cram_stanzas ~conflict_markers
601603 |> List. filter_map ~f: (function
602604 | Cram_lexer. Comment _ -> None
603605 | Command s -> Some s)
@@ -611,8 +613,8 @@ module Make_script = struct
611613 include Action_ext. Make (Spec )
612614end
613615
614- let make_script ~src ~script ~conflict =
615- Make_script. action { script = src; target = script; conflict }
616+ let make_script ~src ~script ~conflict_markers =
617+ Make_script. action { script = src; target = script; conflict_markers }
616618;;
617619
618620module Diff = struct
@@ -640,7 +642,7 @@ module Diff = struct
640642 in
641643 let current_stanzas =
642644 Lexbuf. from_string ~fname: (Path. to_string script) current
643- |> cram_stanzas ~conflict : Ignore
645+ |> cram_stanzas ~conflict_markers : Ignore
644646 in
645647 let rec loop acc current expected =
646648 match current with
@@ -683,7 +685,7 @@ module Action = struct
683685 script
684686 ~f:
685687 (run_produce_correction
686- ~conflict : Ignore
688+ ~conflict_markers : Ignore
687689 ~src: script
688690 ~env: eenv.env
689691 ~script
0 commit comments