diff --git a/parsing/pprintast.ml b/parsing/pprintast.ml index bf1fd14dd2aa..c6f48d16bffb 100644 --- a/parsing/pprintast.ml +++ b/parsing/pprintast.ml @@ -547,8 +547,8 @@ and expression ctxt f x = then String.sub s 1 (String.length s -1) else s in begin match l with - | [(Nolabel, _) as v] -> - pp f "@[<2>%s@;%a@]" s (label_x_expression_param ctxt) v + | [(Nolabel, x)] -> + pp f "@[<2>%s@;%a@]" s (simple_expr ctxt) x | _ -> pp f "@[<2>%a %a@]" (simple_expr ctxt) e (list (label_x_expression_param ctxt)) l @@ -572,7 +572,7 @@ and expression ctxt f x = | _ -> assert false) | Pexp_setfield (e1, li, e2) -> pp f "@[<2>%a.%a@ <-@ %a@]" - (simple_expr ctxt) e1 longident_loc li (expression ctxt) e2 + (simple_expr ctxt) e1 longident_loc li (simple_expr ctxt) e2 | Pexp_ifthenelse (e1, e2, eo) -> (* @;@[<2>else@ %a@]@] *) let fmt:(_,_,_)format ="@[@[<2>if@ %a@]@;@[<2>then@ %a@]%a@]" in diff --git a/testsuite/tests/parsetree/source.ml b/testsuite/tests/parsetree/source.ml index cbb96405456d..7742c5995e25 100644 --- a/testsuite/tests/parsetree/source.ml +++ b/testsuite/tests/parsetree/source.ml @@ -7263,3 +7263,14 @@ let foo : type a' b'. a' -> b' = fun a -> assert false let foo : type t' . t' = fun (type t') -> (assert false : t') let foo : 't . 't = fun (type t) -> (assert false : t) let foo : type a' b' c' t. a' -> b' -> c' -> t = fun a b c -> assert false + +let f x = + x.contents <- (print_string "coucou" ; x.contents) + +let ( ~$ ) x = Some x +let g x = + ~$ (x.contents) + +let ( ~$ ) x y = (x, y) +let g x y = + ~$ (x.contents) (y.contents) diff --git a/testsuite/tests/parsetree/test.ml b/testsuite/tests/parsetree/test.ml index ba8819dbba59..86ed3c8cc613 100644 --- a/testsuite/tests/parsetree/test.ml +++ b/testsuite/tests/parsetree/test.ml @@ -1,5 +1,11 @@ (* (c) Alain Frisch / Lexifi *) (* cf. PR#7200 *) + +let diff = + match Array.to_list Sys.argv with + | [_; diff] -> diff + | _ -> "diff -u" + let report_err exn = match exn with | Sys_error msg -> @@ -69,7 +75,7 @@ let test parse_fun pprint print map filename = Printf.printf "%s: FAIL, REPARSED AST IS DIFFERENT\n%!" filename; let f1 = to_tmp_file print ast in let f2 = to_tmp_file print ast2 in - let cmd = Printf.sprintf "diff -u %s %s" + let cmd = Printf.sprintf "%s %s %s" diff (Filename.quote f1) (Filename.quote f2) in let _ret = Sys.command cmd in print_endline"====================================================="