Merge pull request #773 from Octachron/fix_dsource_local_open_in_pattern

PR#7329, fix "-dsource" for local open in patterns
master
Gabriel Scherer 2016-08-20 10:25:25 +02:00
parent 7bc893a564
commit 98472dfdf6
2 changed files with 17 additions and 0 deletions

View File

@ -409,6 +409,14 @@ and simple_pattern ctxt (f:Format.formatter) (x:pattern) : unit =
| Ppat_exception p ->
pp f "@[<2>exception@;%a@]" (pattern1 ctxt) p
| Ppat_extension e -> extension ctxt f e
| Ppat_open (lid, p) ->
let with_paren =
match p.ppat_desc with
| Ppat_array _ | Ppat_record _
| Ppat_construct (({txt=Lident ("()"|"[]");_}), _) -> false
| _ -> true in
pp f "@[<2>%a.%a @]" longident_loc lid
(paren with_paren @@ pattern1 ctxt) p
| _ -> paren true (pattern ctxt) f x
and label_exp ctxt f (l,opt,p) =

View File

@ -7245,3 +7245,12 @@ end and ['a] d () = object
inherit ['a] c ()
end;;
*)
(* PR#7329 Pattern open *)
let _ =
let module M = struct type t = { x : int } end in
let f M.(x) = () in
let g M.{x} = () in
let h = function M.[] | M.[a] | M.(a::q) -> () in
let i = function M.[||] | M.[|x|] -> true | _ -> false in
()