diff --git a/testsuite/tests/tool-caml-tex/ellipses.ml b/testsuite/tests/tool-caml-tex/ellipses.ml new file mode 100644 index 000000000..966355be6 --- /dev/null +++ b/testsuite/tests/tool-caml-tex/ellipses.ml @@ -0,0 +1,58 @@ +(* TEST + reference="${test_source_directory}/ellipses.reference" + output="ellipses.output" + script = "${ocamlrun} ${ocamlsrcdir}/tools/caml-tex \ + -repo-root ${ocamlsrcdir} ${test_source_directory}/${test_file} -o ${output}" + * native-compiler + ** script with unix,str + *** check-program-output +*) + +\begin{caml_example*}{verbatim} +let start = 0 +[@@@ellipsis.start] +let hidden = succ start +[@@@ellipsis.stop] +let mid = succ hidden +let[@ellipsis] statement = succ mid + +module E = struct end +include E[@@ellipsis] + +let expr = succ statement[@ellipsis] + +let pat = match start with + | 0[@ellipsis] | 1 -> succ expr + | _ -> succ expr + +let case = match start with + | 0 -> succ pat + | _[@ellipsis.start] -> succ pat[@ellipsis.stop] + + +let annot: int[@ellipsis] = succ case + +let subexpr = succ annot + (2[@ellipsis.stop] - 1[@ellipsis.start] * 2) - 2 + +class[@ellipsis] c = object val x = succ subexpr end + +class c2 = object + val[@ellipsis] x = 0 + val y = 1 + method[@ellipsis] m = 2 + method n = 3 + [@@@ellipsis.start] + method l = 4 + [@@@ellipsis.stop] +end + +type t = A[@ellipsis] | B |C[@ellipsis.start] | D | E [@ellipsis.stop] | F +type arrow = int -> (int -> int[@ellipsis]) +type record = { a:int; b:int[@ellipsis]; c:int; + d:int[@ellipsis.start]; e:int; f:int[@ellipsis.stop]; + g:int } +type polyvar = [`A|`B[@ellipsis] |`C + |`D[@ellipsis.start] | `E | `F [@ellipsis.stop] + | `G ] +type exn += A[@ellipsis] | B |C[@ellipsis.start] | D | E [@ellipsis.stop] | F +\end{caml_example*} diff --git a/testsuite/tests/tool-caml-tex/ellipses.reference b/testsuite/tests/tool-caml-tex/ellipses.reference new file mode 100644 index 000000000..d1498bb52 --- /dev/null +++ b/testsuite/tests/tool-caml-tex/ellipses.reference @@ -0,0 +1,56 @@ +(* TEST + reference="${test_source_directory}/ellipses.reference" + output="ellipses.output" + script = "${ocamlrun} ${ocamlsrcdir}/tools/caml-tex \ + -repo-root ${ocamlsrcdir} ${test_source_directory}/${test_file} -o ${output}" + * native-compiler + ** script with unix,str + *** check-program-output +*) + +\camlexample{verbatim} +\caml\camlinput\?let start = 0 +\?\ldots +\?let mid = succ hidden +\?\ldots + +\?module E = struct end +\?\ldots + +\?let expr = \ldots + +\?let pat = match start with +\? | \ldots | 1 -> succ expr +\? | _ -> succ expr + +\?let case = match start with +\? | 0 -> succ pat +\? | \ldots + + +\?let annot: \ldots = succ case + +\?let subexpr = succ annot + (\ldots * 2) - 2 + +\?\ldots + +\?class c2 = object +\? \ldots +\? val y = 1 +\? \ldots +\? method n = 3 +\? \ldots +\?end + +\?type t = \ldots | B \ldots | F +\?type arrow = int -> (\ldots) +\?type record = { a:int; \ldots c:int; +\? \ldots +\? g:int } +\?type polyvar = [\textasciigrave\-A|\ldots |\textasciigrave\-C +\? |\ldots +\? | \textasciigrave\-G ] +\?type exn += \ldots | B \ldots | F +\endcamlinput +\endcaml +\endcamlexample diff --git a/testsuite/tests/tool-caml-tex/ocamltests b/testsuite/tests/tool-caml-tex/ocamltests index 2b0ea2bc5..e543110f6 100644 --- a/testsuite/tests/tool-caml-tex/ocamltests +++ b/testsuite/tests/tool-caml-tex/ocamltests @@ -1 +1,2 @@ +ellipses.ml redirections.ml diff --git a/tools/caml_tex.ml b/tools/caml_tex.ml index 4c283eabf..108a0f666 100644 --- a/tools/caml_tex.ml +++ b/tools/caml_tex.ml @@ -518,7 +518,7 @@ module Ellipsis = struct let start = loc.L.loc_start.Lexing.pos_cnum in let attr_start = attr.P.attr_loc.L.loc_start.Lexing.pos_cnum in let attr_stop = attr.P.attr_loc.L.loc_end.Lexing.pos_cnum in - let stop = loc.L.loc_end.Lexing.pos_cnum in + let stop = max loc.L.loc_end.Lexing.pos_cnum attr_stop in let check_nested () = match !left_mark with | Some (first,_) -> raise (Nested_ellipses {first; second=attr_start}) | None -> () in @@ -526,7 +526,7 @@ module Ellipsis = struct | "ellipsis" -> check_nested (); transforms := - {Text_transform.kind=Ellipsis; start; stop=max attr_stop stop } + {Text_transform.kind=Ellipsis; start; stop } :: !transforms | "ellipsis.start" -> check_nested (); @@ -534,7 +534,8 @@ module Ellipsis = struct | "ellipsis.stop" -> begin match !left_mark with | None -> raise (Unmatched_ellipsis {kind="right"; start; stop}) - | Some (start, _ ) -> + | Some (start', stop' ) -> + let start, stop = min start start', max stop stop' in transforms := {kind=Ellipsis; start ; stop } :: !transforms; left_mark := None end