diff --git a/Changes b/Changes index 49d8deb27..ba83d858f 100644 --- a/Changes +++ b/Changes @@ -62,6 +62,7 @@ Runtime system: point within the major heap. Bug fixes: +- PR#6062: Fix a regression bug caused by commit 13047 - PR#3679: Warning display problems - PR#3963: Graphics.wait_next_event in Win32 hangs if window closed - PR#4079: Queue.copy is now tail-recursive diff --git a/build/camlp4-bootstrap.sh b/build/camlp4-bootstrap.sh index 612e060e9..c466ecdda 100755 --- a/build/camlp4-bootstrap.sh +++ b/build/camlp4-bootstrap.sh @@ -34,7 +34,7 @@ for target in $TARGETS camlp4/boot/Camlp4Ast.ml; do done if [ -x ./boot/myocamlbuild.native ]; then - OCAMLBUILD=./boot/myocamlbuild.native + OCAMLBUILD=./boot/myocamlbuild.native else OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild" fi diff --git a/camlp4/Camlp4Parsers/Camlp4MacroParser.ml b/camlp4/Camlp4Parsers/Camlp4MacroParser.ml index 840bc5ec1..bf7f69c52 100644 --- a/camlp4/Camlp4Parsers/Camlp4MacroParser.ml +++ b/camlp4/Camlp4Parsers/Camlp4MacroParser.ml @@ -248,7 +248,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct defined.val := list_remove x defined.val; } with - [ Not_found -> () ]; + [ Struct.Grammar.Delete.Rule_not_found _ -> () ]; value parse_def s = match Gram.parse_string expr (Loc.mk "") s with diff --git a/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml b/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml index 8231cb817..940e2a101 100644 --- a/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml +++ b/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml @@ -277,11 +277,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct <:expr< let module $m$ = $mb$ in $e$ >> | "let"; "open"; "!"; i = module_longident; "in"; e = expr LEVEL ";" -> <:expr< let open! $id:i$ in $e$ >> - (* Ast.ExOpI _loc i Ast.OvOverride e *) | "let"; "open"; i = module_longident; "in"; e = expr LEVEL ";" -> <:expr< let open $id:i$ in $e$ >> - (* Ast.ExOpI _loc i Ast.OvNil e *) - (* <:expr< let open $id:i$ in $e$ >> *) | "function"; a = match_case -> <:expr< fun [ $a$ ] >> | "if"; e1 = SELF; "then"; e2 = expr LEVEL "top"; diff --git a/camlp4/boot/camlp4boot.ml b/camlp4/boot/camlp4boot.ml index 0fc928b62..9569fc450 100644 --- a/camlp4/boot/camlp4boot.ml +++ b/camlp4/boot/camlp4boot.ml @@ -932,13 +932,10 @@ New syntax:\ and _ = (a_FLOAT : 'a_FLOAT Gram.Entry.t) in let grammar_entry_create = Gram.Entry.mk in let (* <:str_item< open $i$ >> *) - (* <:expr< let open $id:i$ in $e$ >> *) (* Here it's LABEL and not tilde_label since ~a:b is different than ~a : b *) - (* Same remark for ?a:b *) (* <:expr< let open $i$ in $e$ >> *) - infixop5 : 'infixop5 Gram.Entry.t = + (* Same remark for ?a:b *) infixop5 : 'infixop5 Gram.Entry.t = grammar_entry_create "infixop5" - and (* <:expr< let open $id:i$ in $e$ >> *) - (* | i = opt_label; "("; p = patt_tcon; ")" -> *) + and (* | i = opt_label; "("; p = patt_tcon; ")" -> *) (* <:patt< ? $i$ : ($p$) >> *) (* | i = opt_label; "("; p = ipatt_tcon; ")" -> <:patt< ? $i$ : ($p$) >> @@ -14304,7 +14301,7 @@ Added statements: Gram.Sself ]) | None -> ()); defined := list_remove x !defined) - with | Not_found -> () + with | Struct.Grammar.Delete.Rule_not_found _ -> () let parse_def s = match Gram.parse_string expr (Loc.mk "") s with