summaryrefslogtreecommitdiffstats
path: root/camlp4
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2006-07-25 13:53:30 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2006-07-25 13:53:30 +0000
commitd7596d10b55c0d586a7059a9f5d34e52a523b41b (patch)
tree89fab553bc8a583fdb2775be88259710e4db8fad /camlp4
parentd0d2782c2610cd3c8c7925dddfa7e7151669352b (diff)
Fix a bug with exception names (True...)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7536 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4')
-rw-r--r--camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml13
-rw-r--r--camlp4/test/fixtures/bug-camlp4o-benjamin-monate.ml8
2 files changed, 16 insertions, 5 deletions
diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
index 24c1eb706..666bfac5c 100644
--- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
+++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml
@@ -779,9 +779,11 @@ module Make (Ast : Sig.Camlp4Ast.S) = struct
(List.map class_info_class_type (list_of_class_type ctd []))) :: l]
| <:sig_item< $sg1$; $sg2$ >> -> sig_item sg1 (sig_item sg2 l)
| SgDir _ _ _ -> l
- | <:sig_item@loc< exception $uid:s$ >> -> [mksig loc (Psig_exception s []) :: l]
+ | <:sig_item@loc< exception $uid:s$ >> ->
+ [mksig loc (Psig_exception (conv_con s) []) :: l]
| <:sig_item@loc< exception $uid:s$ of $t$ >> ->
- [mksig loc (Psig_exception s (List.map ctyp (list_of_ctyp t []))) :: l]
+ [mksig loc (Psig_exception (conv_con s)
+ (List.map ctyp (list_of_ctyp t []))) :: l]
| SgExc _ _ -> assert False (*FIXME*)
| SgExt loc n t p -> [mksig loc (Psig_value n (mkvalue_desc t [p])) :: l]
| SgInc loc mt -> [mksig loc (Psig_include (module_type mt)) :: l]
@@ -838,11 +840,12 @@ module Make (Ast : Sig.Camlp4Ast.S) = struct
| <:str_item< $st1$; $st2$ >> -> str_item st1 (str_item st2 l)
| StDir _ _ _ -> l
| <:str_item@loc< exception $uid:s$ >> ->
- [mkstr loc (Pstr_exception s []) :: l ]
+ [mkstr loc (Pstr_exception (conv_con s) []) :: l ]
| <:str_item@loc< exception $uid:s$ of $t$ >> ->
- [mkstr loc (Pstr_exception s (List.map ctyp (list_of_ctyp t []))) :: l ]
+ [mkstr loc (Pstr_exception (conv_con s)
+ (List.map ctyp (list_of_ctyp t []))) :: l ]
| <:str_item@loc< exception $uid:s$ = $i$ >> ->
- [mkstr loc (Pstr_exn_rebind s (ident i)) :: l ]
+ [mkstr loc (Pstr_exn_rebind (conv_con s) (ident i)) :: l ]
| StExc _ _ _ -> assert False (*FIXME*)
| StExp loc e -> [mkstr loc (Pstr_eval (expr e)) :: l]
| StExt loc n t p -> [mkstr loc (Pstr_primitive n (mkvalue_desc t [p])) :: l]
diff --git a/camlp4/test/fixtures/bug-camlp4o-benjamin-monate.ml b/camlp4/test/fixtures/bug-camlp4o-benjamin-monate.ml
index 2de1a43fc..3cf593965 100644
--- a/camlp4/test/fixtures/bug-camlp4o-benjamin-monate.ml
+++ b/camlp4/test/fixtures/bug-camlp4o-benjamin-monate.ml
@@ -1,2 +1,10 @@
type t = A of t | B ;;
let f = function A A B -> B | B | A B | A (A _) -> B ;;
+
+
+exception True
+let qexists f q =
+ try
+ Queue.iter (fun v -> if f v then raise True) q;
+ false
+ with True -> true