ocaml / ocaml

The core OCaml system: compilers, runtime system, base libraries
https://ocaml.org
Other
5.19k stars 1.06k forks source link

A minor oversight in pretty-printing raw identifiers (for new types in Pexp_function) #13116

Closed chetmurthy closed 2 weeks ago

chetmurthy commented 3 weeks ago

Hi, I found what appears to be a really trivial-to-fix bug in Pprintast. Here's a repro (I did this with 5.2.0~beta2, but the code hasn't changed in HEAD as of this writing). I'm just reporting, instead of preparing a PR, b/c it's so tiny (literally a one-liner fix). If you'd prefer a PR, let me know and I can prepare one though it'll take a little longer b/c it'll take a little time for me to remember how it all works.

let pa s =
  let lb = Lexing.from_string s in
  Parse.implementation lb
;;
let pr st =
  Pprintast.string_of_structure st
;;
{foo|let hh = fun x (type \#let) (type \#foo) -> 1|foo} |> pa |> pr |> print_string ;;
let hh x (type let) (type foo) = 1- : unit = ()

This is a slight change from code I found in the testsuite (parsetree/source.ml), and if I use what's there, it works fine.

# {foo|let hh = fun (type \#let) (type \#foo) -> 1|foo} |> pa |> pr |> print_string ;;
let hh (type \#let) (type foo) = 1- : unit = ()

Explanation: in the first case, the parser constructs a Pexp_function with 3 params (1 val, 2 newtype). In the second case, the parser constructs two nested Pexp_newtype expressions. The pretty-printer for Pexp_newtype invokes "ident_of_name" to properly escape raw identifiers; the pretty-printer for Pexp_function->function_param does not do so, viz.

    | Pexp_newtype (lid, e) ->
        pp f "@[<2>fun@;(type@;%a)@;->@;%a@]" ident_of_name lid.txt

https://github.com/ocaml/ocaml/blob/eabbb4002a0dabdbcf708f52a1db1d7a11618119/parsing/pprintast.ml#L630

  | Pparam_newtype ty -> pp f "(type %s)@;" ty.txt

If this were a larger bug, I'd prepare a PR, but since it's literally a one-liner, and you're already at beta2, I figured I should just report it.

If you'd like me to prepare a PR, let me know and I'l do so, though it'll take a little time to do so (I'll have to remember all the steps to build/test/etc).

chetmurthy commented 3 weeks ago

I found another instance of the same problem (in printing of longidents). Here's a diff.

diff --git a/parsing/pprintast.ml b/parsing/pprintast.ml
index d7fea80a7c..c0100995a8 100644
--- a/parsing/pprintast.ml
+++ b/parsing/pprintast.ml
@@ -108,11 +108,12 @@ let ident_of_name ppf txt =
 let ident_of_name_loc ppf s = ident_of_name ppf s.txt

 let protect_longident ppf print_longident longprefix txt =
-  let format : (_, _, _) format =
-    if not (needs_parens txt) then "%a.%s"
-    else if needs_spaces txt then  "%a.(@;%s@;)"
-    else "%a.(%s)" in
-  fprintf ppf format print_longident longprefix txt
+    if not (needs_parens txt) then
+      fprintf ppf "%a.%a" print_longident longprefix ident_of_name txt
+    else if needs_spaces txt then
+      fprintf ppf "%a.(@;%s@;)" print_longident longprefix txt
+    else 
+      fprintf ppf "%a.(%s)" print_longident longprefix txt

 type space_formatter = (unit, Format.formatter, unit) format

@@ -625,7 +626,7 @@ and sugar_expr ctxt f e =
 and function_param ctxt f param =
   match param.pparam_desc with
   | Pparam_val (a, b, c) -> label_exp ctxt f (a, b, c)
-  | Pparam_newtype ty -> pp f "(type %s)@;" ty.txt
+  | Pparam_newtype ty -> pp f "(type %a)@;" ident_of_name ty.txt

 and function_body ctxt f function_body =
   match function_body with
chetmurthy commented 2 weeks ago

OK, I submitted a PR: #13127

Ekdohibs commented 2 weeks ago

I think this can be closed now that #13130 has been merged?

Octachron commented 2 weeks ago

Indeed, let's close the issue.