diff options
-rw-r--r-- | camlp4/Camlp4/Camlp4Ast.partial.ml | 4 | ||||
-rw-r--r-- | camlp4/Camlp4/Printers/OCaml.ml | 4 | ||||
-rw-r--r-- | camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml | 32 | ||||
-rw-r--r-- | camlp4/Camlp4Parsers/Camlp4OCamlParser.ml | 8 | ||||
-rw-r--r-- | camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml | 8 |
5 files changed, 41 insertions, 15 deletions
diff --git a/camlp4/Camlp4/Camlp4Ast.partial.ml b/camlp4/Camlp4/Camlp4Ast.partial.ml index 4ed2fb994..d821902a2 100644 --- a/camlp4/Camlp4/Camlp4Ast.partial.ml +++ b/camlp4/Camlp4/Camlp4Ast.partial.ml @@ -199,6 +199,10 @@ | WcTyp of loc and ctyp and ctyp (* module i = i *) | WcMod of loc and ident and ident + (* type t := t *) + | WcTyS of loc and ctyp and ctyp + (* module i := i *) + | WcMoS of loc and ident and ident (* wc and wc *) | WcAnd of loc and with_constr and with_constr | WcAnt of loc and string (* $s$ *) ] diff --git a/camlp4/Camlp4/Printers/OCaml.ml b/camlp4/Camlp4/Printers/OCaml.ml index b47d4555e..461b0ea99 100644 --- a/camlp4/Camlp4/Printers/OCaml.ml +++ b/camlp4/Camlp4/Printers/OCaml.ml @@ -860,6 +860,10 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct pp f "@[<2>type@ %a =@ %a@]" o#ctyp t1 o#ctyp t2 | <:with_constr< module $i1$ = $i2$ >> -> pp f "@[<2>module@ %a =@ %a@]" o#ident i1 o#ident i2 + | <:with_constr< type $t1$ := $t2$ >> -> + pp f "@[<2>type@ %a :=@ %a@]" o#ctyp t1 o#ctyp t2 + | <:with_constr< module $i1$ := $i2$ >> -> + pp f "@[<2>module@ %a :=@ %a@]" o#ident i1 o#ident i2 | <:with_constr< $wc1$ and $wc2$ >> -> do { o#with_constraint f wc1; pp f andsep; o#with_constraint f wc2 } | <:with_constr< $anti:s$ >> -> o#anti f s ]; diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml index 8354935d6..1276ad17b 100644 --- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml +++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml @@ -370,22 +370,28 @@ module Make (Ast : Sig.Camlp4Ast) = struct | <:ctyp< $id:i$ >> -> (ident i, acc) | _ -> assert False ]; + value mkwithtyp pwith_type loc id_tpl ct = + let (id, tpl) = type_parameters_and_type_name id_tpl [] in + let (params, variance) = List.split tpl in + let (kind, priv, ct) = opt_private_ctyp ct in + (id, pwith_type + {ptype_params = params; ptype_cstrs = []; + ptype_kind = kind; + ptype_private = priv; + ptype_manifest = Some ct; + ptype_loc = mkloc loc; ptype_variance = variance}); + value rec mkwithc wc acc = match wc with - [ WcNil _ -> acc - | WcTyp loc id_tpl ct -> - let (id, tpl) = type_parameters_and_type_name id_tpl [] in - let (params, variance) = List.split tpl in - let (kind, priv, ct) = opt_private_ctyp ct in - [(id, - Pwith_type - {ptype_params = params; ptype_cstrs = []; - ptype_kind = kind; - ptype_private = priv; - ptype_manifest = Some ct; - ptype_loc = mkloc loc; ptype_variance = variance}) :: acc] - | WcMod _ i1 i2 -> + [ <:with_constr<>> -> acc + | <:with_constr@loc< type $id_tpl$ = $ct$ >> -> + [mkwithtyp (fun x -> Pwith_type x) loc id_tpl ct :: acc] + | <:with_constr< module $i1$ = $i2$ >> -> [(long_uident i1, Pwith_module (long_uident i2)) :: acc] + | <:with_constr@loc< type $id_tpl$ := $ct$ >> -> + [mkwithtyp (fun x -> Pwith_typesubst x) loc id_tpl ct :: acc] + | <:with_constr< module $i1$ := $i2$ >> (*WcMoS _ i1 i2*) -> + [(long_uident i1, Pwith_modsubst (long_uident i2)) :: acc] | <:with_constr< $wc1$ and $wc2$ >> -> mkwithc wc1 (mkwithc wc2 acc) | <:with_constr@loc< $anti:_$ >> -> error loc "bad with constraint (antiquotation)" ]; diff --git a/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml b/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml index 2bedf9aa1..8a7105379 100644 --- a/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml +++ b/camlp4/Camlp4Parsers/Camlp4OCamlParser.ml @@ -446,7 +446,13 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct | "type"; t1 = type_longident_and_parameters; "="; t2 = opt_private_ctyp -> <:with_constr< type $t1$ = $t2$ >> | "module"; i1 = module_longident; "="; i2 = module_longident_with_app -> - <:with_constr< module $i1$ = $i2$ >> ] ] + <:with_constr< module $i1$ = $i2$ >> + | "type"; `ANTIQUOT (""|"typ"|"anti" as n) s; ":="; t = opt_private_ctyp -> + <:with_constr< type $anti:mk_anti ~c:"ctyp" n s$ := $t$ >> + | "type"; t1 = type_longident_and_parameters; ":="; t2 = opt_private_ctyp -> + <:with_constr< type $t1$ := $t2$ >> + | "module"; i1 = module_longident; ":="; i2 = module_longident_with_app -> + <:with_constr< module $i1$ := $i2$ >> ] ] ; opt_private_ctyp: [ [ "private"; t = ctyp -> <:ctyp< private $t$ >> diff --git a/camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml b/camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml index f31636e22..81e252cfe 100644 --- a/camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml +++ b/camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml @@ -596,7 +596,13 @@ Very old (no more supported) syntax:\n\ | "type"; t1 = type_longident_and_parameters; "="; t2 = ctyp -> <:with_constr< type $t1$ = $t2$ >> | "module"; i1 = module_longident; "="; i2 = module_longident_with_app -> - <:with_constr< module $i1$ = $i2$ >> ] ] + <:with_constr< module $i1$ = $i2$ >> + | "type"; `ANTIQUOT (""|"typ"|"anti" as n) s; ":="; t = ctyp -> + <:with_constr< type $anti:mk_anti ~c:"ctyp" n s$ := $t$ >> + | "type"; t1 = type_longident_and_parameters; ":="; t2 = ctyp -> + <:with_constr< type $t1$ := $t2$ >> + | "module"; i1 = module_longident; ":="; i2 = module_longident_with_app -> + <:with_constr< module $i1$ := $i2$ >> ] ] ; expr: [ "top" RIGHTA |