Continue to add support for attributes to Camlp4, a little bit.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@13599 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
365bcdeadc
commit
cf273fb995
|
@ -104,6 +104,7 @@
|
|||
| TyAmp of loc and ctyp and ctyp (* t & t *)
|
||||
| TyOfAmp of loc and ctyp and ctyp (* t of & t *)
|
||||
| TyPkg of loc and module_type (* (module S) *)
|
||||
| TyAtt of loc and string and str_item and ctyp (* .. [@attr] *)
|
||||
| TyAnt of loc and string (* $s$ *)
|
||||
]
|
||||
and patt =
|
||||
|
@ -137,6 +138,7 @@
|
|||
| PaTyp of loc and ident (* #i *)
|
||||
| PaVrn of loc and string (* `s *)
|
||||
| PaLaz of loc and patt (* lazy p *)
|
||||
| PaAtt of loc and string and str_item and patt (* .. [@attr] *)
|
||||
| PaMod of loc and string (* (module M) *) ]
|
||||
and expr =
|
||||
[ ExNil of loc
|
||||
|
@ -223,6 +225,7 @@
|
|||
| MtWit of loc and module_type and with_constr
|
||||
(* module type of m *)
|
||||
| MtOf of loc and module_expr
|
||||
| MtAtt of loc and string and str_item and module_type (* .. [@attr] *)
|
||||
| MtAnt of loc and string (* $s$ *) ]
|
||||
and sig_item =
|
||||
[ SgNil of loc
|
||||
|
@ -311,6 +314,7 @@
|
|||
(* (value e) *)
|
||||
(* (value e : S) which is represented as (value (e : S)) *)
|
||||
| MePkg of loc and expr
|
||||
| MeAtt of loc and string and str_item and module_expr (* .. [@attr] *)
|
||||
| MeAnt of loc and string (* $s$ *) ]
|
||||
and str_item =
|
||||
[ StNil of loc
|
||||
|
@ -358,6 +362,7 @@
|
|||
(* ct = ct *)
|
||||
| CtEq of loc and class_type and class_type
|
||||
(* $s$ *)
|
||||
| CtAtt of loc and string and str_item and class_type (* .. [@attr] *)
|
||||
| CtAnt of loc and string ]
|
||||
and class_sig_item =
|
||||
[ CgNil of loc
|
||||
|
@ -393,6 +398,7 @@
|
|||
(* ce = ce *)
|
||||
| CeEq of loc and class_expr and class_expr
|
||||
(* $s$ *)
|
||||
| CeAtt of loc and string and str_item and class_expr (* .. [@attr] *)
|
||||
| CeAnt of loc and string ]
|
||||
and class_str_item =
|
||||
[ CrNil of loc
|
||||
|
|
|
@ -691,6 +691,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
<:patt< $_$ .. $_$ >> | <:patt< $_$, $_$ >> |
|
||||
<:patt< $_$; $_$ >> | <:patt< $_$ = $_$ >> | <:patt< lazy $_$ >> as p ->
|
||||
pp f "@[<1>(%a)@]" o#patt p
|
||||
| Ast.PaAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#patt e s o#str_item str
|
||||
];
|
||||
|
||||
method patt_tycon f =
|
||||
|
@ -727,6 +729,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
| <:ctyp< # $i$ >> -> pp f "@[<2>#%a@]" o#ident i
|
||||
| <:ctyp< `$s$ >> -> pp f "`%a" o#var s
|
||||
| <:ctyp< $t1$ * $t2$ >> -> pp f "%a *@ %a" o#simple_ctyp t1 o#simple_ctyp t2
|
||||
| Ast.TyAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#ctyp e s o#str_item str
|
||||
| <:ctyp<>> -> assert False
|
||||
| t -> pp f "@[<1>(%a)@]" o#ctyp t ];
|
||||
|
||||
|
@ -902,6 +906,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
| <:module_type< '$s$ >> -> pp f "'%a" o#var s
|
||||
| <:module_type< sig $sg$ end >> ->
|
||||
pp f "@[<hv0>@[<hv2>sig@ %a@]@ end@]" o#sig_item sg
|
||||
| Ast.MtAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#module_type e s o#str_item str
|
||||
| <:module_type< $mt$ with $wc$ >> ->
|
||||
pp f "@[<2>%a@ with@ %a@]" o#module_type mt o#with_constraint wc ];
|
||||
|
||||
|
@ -948,6 +954,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
pp f "@[<1>(%s %a :@ %a)@]" o#value_val o#expr e o#module_type mt
|
||||
| <:module_expr< (value $e$ ) >> ->
|
||||
pp f "@[<1>(%s %a)@]" o#value_val o#expr e
|
||||
| Ast.MeAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#module_expr e s o#str_item str
|
||||
];
|
||||
|
||||
method class_expr f ce =
|
||||
|
@ -983,6 +991,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
o#patt_class_expr_fun_args (p, ce2)
|
||||
| <:class_expr< $ce1$ = $ce2$ >> ->
|
||||
pp f "@[<2>%a =@]@ %a" o#class_expr ce1 o#class_expr ce2
|
||||
| Ast.CeAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#class_expr e s o#str_item str
|
||||
| _ -> assert False ];
|
||||
|
||||
method class_type f ct =
|
||||
|
@ -1010,6 +1020,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
pp f "%a :@ %a" o#class_type ct1 o#class_type ct2
|
||||
| <:class_type< $ct1$ = $ct2$ >> ->
|
||||
pp f "%a =@ %a" o#class_type ct1 o#class_type ct2
|
||||
| Ast.CtAtt _loc s str e ->
|
||||
pp f "((%a)[@@%s %a])" o#class_type e s o#str_item str
|
||||
| _ -> assert False ];
|
||||
|
||||
method class_sig_item f csg =
|
||||
|
|
|
@ -122,6 +122,7 @@ module Make (Loc : Sig.Loc)
|
|||
| <:patt< ~ $_$ >> -> True
|
||||
| <:patt< ~ $_$ : $p$ >> -> is_irrefut_patt p
|
||||
| <:patt< lazy $p$ >> -> is_irrefut_patt p
|
||||
| Ast.PaAtt _loc _s _str p -> is_irrefut_patt p
|
||||
| <:patt< $id:_$ >> -> False (* here one need to know the arity of constructors *)
|
||||
| <:patt< (module $_$) >> -> True
|
||||
| <:patt< `$_$ >> | <:patt< $str:_$ >> | <:patt< $_$ .. $_$ >> |
|
||||
|
|
|
@ -217,6 +217,11 @@ module Make (Ast : Sig.Camlp4Ast) = struct
|
|||
value predef_option loc =
|
||||
TyId (loc, IdAcc (loc, IdLid (loc, "*predef*"), IdLid (loc, "option")));
|
||||
|
||||
value attribute_fwd = ref (fun _ _ _ -> assert False);
|
||||
|
||||
value attribute loc s str =
|
||||
!attribute_fwd loc s str;
|
||||
|
||||
value rec ctyp =
|
||||
fun
|
||||
[ TyId loc i ->
|
||||
|
@ -250,6 +255,9 @@ module Make (Ast : Sig.Camlp4Ast) = struct
|
|||
| <:ctyp@loc< (module $pt$) >> ->
|
||||
let (i, cs) = package_type pt in
|
||||
mktyp loc (Ptyp_package i cs)
|
||||
| TyAtt loc s str e ->
|
||||
let e = ctyp e in
|
||||
{(e) with ptyp_attributes = e.ptyp_attributes @ [attribute loc s str]}
|
||||
| TyLab loc _ _ -> error loc "labelled type not allowed here"
|
||||
| TyMan loc _ _ -> error loc "manifest type not allowed here"
|
||||
| TyOlb loc _ _ -> error loc "labelled type not allowed here"
|
||||
|
@ -582,6 +590,9 @@ module Make (Ast : Sig.Camlp4Ast) = struct
|
|||
| PaVrn loc s -> mkpat loc (Ppat_variant (conv_con s) None)
|
||||
| PaLaz loc p -> mkpat loc (Ppat_lazy (patt p))
|
||||
| PaMod loc m -> mkpat loc (Ppat_unpack (with_loc m loc))
|
||||
| PaAtt loc s str e ->
|
||||
let e = patt e in
|
||||
{(e) with ppat_attributes = e.ppat_attributes @ [attribute loc s str]}
|
||||
| PaEq _ _ _ | PaSem _ _ _ | PaCom _ _ _ | PaNil _ as p ->
|
||||
error (loc_of_patt p) "invalid pattern" ]
|
||||
and mklabpat =
|
||||
|
@ -862,7 +873,7 @@ value varify_constructors var_names =
|
|||
error loc "expr; expr: not allowed here, use do {...} or [|...|] to surround them"
|
||||
| ExAtt loc s str e ->
|
||||
let e = expr e in
|
||||
{(e) with pexp_attributes = [(with_loc s loc, str_item str []) :: e.pexp_attributes]}
|
||||
{(e) with pexp_attributes = e.pexp_attributes @ [attribute loc s str]}
|
||||
| ExId _ _ | ExNil _ as e -> error (loc_of_expr e) "invalid expr" ]
|
||||
and patt_of_lab _loc lab =
|
||||
fun
|
||||
|
@ -973,6 +984,9 @@ value varify_constructors var_names =
|
|||
mkmty loc (Pmty_with (module_type mt) (mkwithc wc []))
|
||||
| <:module_type@loc< module type of $me$ >> ->
|
||||
mkmty loc (Pmty_typeof (module_expr me))
|
||||
| MtAtt loc s str e ->
|
||||
let e = module_type e in
|
||||
{(e) with pmty_attributes = e.pmty_attributes @ [attribute loc s str]}
|
||||
| <:module_type< $anti:_$ >> -> assert False ]
|
||||
and sig_item s l =
|
||||
match s with
|
||||
|
@ -1045,6 +1059,9 @@ value varify_constructors var_names =
|
|||
mktyp loc (Ptyp_package (package_type pt))))))
|
||||
| <:module_expr@loc< (value $e$) >> ->
|
||||
mkmod loc (Pmod_unpack (expr e))
|
||||
| MeAtt loc s str e ->
|
||||
let e = module_expr e in
|
||||
{(e) with pmod_attributes = e.pmod_attributes @ [attribute loc s str]}
|
||||
| <:module_expr@loc< $anti:_$ >> -> error loc "antiquotation in module_expr" ]
|
||||
and str_item s l =
|
||||
match s with
|
||||
|
@ -1107,6 +1124,9 @@ value varify_constructors var_names =
|
|||
pcsig_self = ctyp t;
|
||||
pcsig_fields = cil;
|
||||
})
|
||||
| CtAtt loc s str e ->
|
||||
let e = class_type e in
|
||||
{(e) with pcty_attributes = e.pcty_attributes @ [attribute loc s str]}
|
||||
| CtCon loc _ _ _ ->
|
||||
error loc "invalid virtual class inside a class type"
|
||||
| CtAnt _ _ | CtEq _ _ _ | CtCol _ _ _ | CtAnd _ _ _ | CtNil _ ->
|
||||
|
@ -1195,6 +1215,9 @@ value varify_constructors var_names =
|
|||
})
|
||||
| CeTyc loc ce ct ->
|
||||
mkcl loc (Pcl_constraint (class_expr ce) (class_type ct))
|
||||
| CeAtt loc s str e ->
|
||||
let e = class_expr e in
|
||||
{(e) with pcl_attributes = e.pcl_attributes @ [attribute loc s str]}
|
||||
| CeCon loc _ _ _ ->
|
||||
error loc "invalid virtual class inside a class expression"
|
||||
| CeAnt _ _ | CeEq _ _ _ | CeAnd _ _ _ | CeNil _ -> assert False ]
|
||||
|
@ -1241,4 +1264,10 @@ value varify_constructors var_names =
|
|||
[ StDir _ d dp -> Ptop_dir d (directive dp)
|
||||
| si -> Ptop_def (str_item si) ]
|
||||
;
|
||||
|
||||
value attribute loc s str =
|
||||
(with_loc s loc, str_item str);
|
||||
|
||||
value () =
|
||||
attribute_fwd.val := attribute;
|
||||
end;
|
||||
|
|
|
@ -334,7 +334,10 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
;
|
||||
(* Patterns *)
|
||||
patt:
|
||||
[ "as" LEFTA
|
||||
[ "attribute"
|
||||
[ e = SELF; "[@"; s = a_LIDENT; str = str_items; "]" ->
|
||||
Ast.PaAtt _loc s str e ]
|
||||
| "as" LEFTA
|
||||
[ p1 = SELF; "as"; i = a_LIDENT -> <:patt< ($p1$ as $lid:i$) >> ]
|
||||
| "|" LEFTA
|
||||
[ p1 = SELF; "|"; p2 = SELF -> <:patt< $p1$ | $p2$ >> ]
|
||||
|
@ -495,6 +498,9 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
|
|||
let t = <:ctyp< $t1$ $t2$ >> in
|
||||
try <:ctyp< $id:Ast.ident_of_ctyp t$ >>
|
||||
with [ Invalid_argument s -> raise (Stream.Error s) ] ]
|
||||
| "attribute"
|
||||
[ e = SELF; "[@"; s = a_LIDENT; str = str_items; "]" ->
|
||||
Ast.TyAtt _loc s str e ]
|
||||
| "simple"
|
||||
[ "'"; i = a_ident -> <:ctyp< '$i$ >>
|
||||
| "_" -> <:ctyp< _ >>
|
||||
|
|
|
@ -870,7 +870,10 @@ New syntax:\
|
|||
| "->"; e = expr -> e ] ]
|
||||
;
|
||||
patt:
|
||||
[ "|" LEFTA
|
||||
[ "attribute"
|
||||
[ e = SELF; "[@"; s = a_LIDENT; str = str_items; "]" ->
|
||||
Ast.PaAtt _loc s str e ]
|
||||
| "|" LEFTA
|
||||
[ p1 = SELF; "|"; p2 = SELF -> <:patt< $p1$ | $p2$ >> ]
|
||||
| ".." NONA
|
||||
[ p1 = SELF; ".."; p2 = SELF -> <:patt< $p1$ .. $p2$ >> ]
|
||||
|
@ -1091,6 +1094,9 @@ New syntax:\
|
|||
[ t1 = SELF; "."; t2 = SELF ->
|
||||
try <:ctyp< $id:Ast.ident_of_ctyp t1$.$id:Ast.ident_of_ctyp t2$ >>
|
||||
with [ Invalid_argument s -> raise (Stream.Error s) ] ]
|
||||
| "attribute"
|
||||
[ e = SELF; "[@"; s = a_LIDENT; str = str_items; "]" ->
|
||||
Ast.TyAtt _loc s str e ]
|
||||
| "simple"
|
||||
[ "'"; i = a_ident -> <:ctyp< '$i$ >>
|
||||
| "_" -> <:ctyp< _ >>
|
||||
|
|
|
@ -107,6 +107,7 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| Ast.PaLab _ _ (Ast.PaNil _) -> True
|
||||
| Ast.PaLab _ _ p -> is_irrefut_patt p
|
||||
| Ast.PaLaz _ p -> is_irrefut_patt p
|
||||
| Ast.PaAtt _loc _s _str p -> is_irrefut_patt p
|
||||
| Ast.PaId _ _ -> False
|
||||
| (* here one need to know the arity of constructors *) Ast.PaMod _ _
|
||||
-> True
|
||||
|
@ -520,6 +521,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_class_expr _loc =
|
||||
fun
|
||||
[ Ast.CeAnt x0 x1 -> Ast.ExAnt x0 x1
|
||||
| Ast.CeAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "CeAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_class_expr _loc x3)
|
||||
| Ast.CeEq x0 x1 x2 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -792,6 +805,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_class_type _loc =
|
||||
fun
|
||||
[ Ast.CtAnt x0 x1 -> Ast.ExAnt x0 x1
|
||||
| Ast.CtAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "CtAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_class_type _loc x3)
|
||||
| Ast.CtEq x0 x1 x2 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -863,6 +888,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_ctyp _loc =
|
||||
fun
|
||||
[ Ast.TyAnt x0 x1 -> Ast.ExAnt x0 x1
|
||||
| Ast.TyAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "TyAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_ctyp _loc x3)
|
||||
| Ast.TyPkg x0 x1 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -1796,6 +1833,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_module_expr _loc =
|
||||
fun
|
||||
[ Ast.MeAnt x0 x1 -> Ast.ExAnt x0 x1
|
||||
| Ast.MeAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "MeAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_module_expr _loc x3)
|
||||
| Ast.MePkg x0 x1 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -1861,6 +1910,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_module_type _loc =
|
||||
fun
|
||||
[ Ast.MtAnt x0 x1 -> Ast.ExAnt x0 x1
|
||||
| Ast.MtAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "MtAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_module_type _loc x3)
|
||||
| Ast.MtOf x0 x1 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -1953,6 +2014,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
(Ast.IdUid _loc "PaMod")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1)
|
||||
| Ast.PaAtt x0 x1 x2 x3 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
(Ast.ExId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "PaAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_patt _loc x3)
|
||||
| Ast.PaLaz x0 x1 ->
|
||||
Ast.ExApp _loc
|
||||
(Ast.ExApp _loc
|
||||
|
@ -2639,6 +2712,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_class_expr _loc =
|
||||
fun
|
||||
[ Ast.CeAnt x0 x1 -> Ast.PaAnt x0 x1
|
||||
| Ast.CeAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "CeAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_class_expr _loc x3)
|
||||
| Ast.CeEq x0 x1 x2 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -2911,6 +2996,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_class_type _loc =
|
||||
fun
|
||||
[ Ast.CtAnt x0 x1 -> Ast.PaAnt x0 x1
|
||||
| Ast.CtAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "CtAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_class_type _loc x3)
|
||||
| Ast.CtEq x0 x1 x2 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -2982,6 +3079,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_ctyp _loc =
|
||||
fun
|
||||
[ Ast.TyAnt x0 x1 -> Ast.PaAnt x0 x1
|
||||
| Ast.TyAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "TyAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_ctyp _loc x3)
|
||||
| Ast.TyPkg x0 x1 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -3915,6 +4024,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_module_expr _loc =
|
||||
fun
|
||||
[ Ast.MeAnt x0 x1 -> Ast.PaAnt x0 x1
|
||||
| Ast.MeAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "MeAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_module_expr _loc x3)
|
||||
| Ast.MePkg x0 x1 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -3980,6 +4101,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
and meta_module_type _loc =
|
||||
fun
|
||||
[ Ast.MtAnt x0 x1 -> Ast.PaAnt x0 x1
|
||||
| Ast.MtAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "MtAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_module_type _loc x3)
|
||||
| Ast.MtOf x0 x1 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -4072,6 +4205,18 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
(Ast.IdUid _loc "PaMod")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1)
|
||||
| Ast.PaAtt x0 x1 x2 x3 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
(Ast.PaId _loc
|
||||
(Ast.IdAcc _loc (Ast.IdUid _loc "Ast")
|
||||
(Ast.IdUid _loc "PaAtt")))
|
||||
(meta_loc _loc x0))
|
||||
(meta_string _loc x1))
|
||||
(meta_str_item _loc x2))
|
||||
(meta_patt _loc x3)
|
||||
| Ast.PaLaz x0 x1 ->
|
||||
Ast.PaApp _loc
|
||||
(Ast.PaApp _loc
|
||||
|
@ -4975,6 +5120,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let _x_i1 = o#string _x_i1 in PaVrn _x _x_i1
|
||||
| PaLaz _x _x_i1 ->
|
||||
let _x = o#loc _x in let _x_i1 = o#patt _x_i1 in PaLaz _x _x_i1
|
||||
| PaAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#patt _x_i3 in PaAtt _x _x_i1 _x_i2 _x_i3
|
||||
| PaMod _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in PaMod _x _x_i1 ];
|
||||
|
@ -5011,6 +5161,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| MtOf _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#module_expr _x_i1 in MtOf _x _x_i1
|
||||
| MtAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#module_type _x_i3 in MtAtt _x _x_i1 _x_i2 _x_i3
|
||||
| MtAnt _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in MtAnt _x _x_i1 ];
|
||||
|
@ -5037,6 +5192,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let _x_i2 = o#module_type _x_i2 in MeTyc _x _x_i1 _x_i2
|
||||
| MePkg _x _x_i1 ->
|
||||
let _x = o#loc _x in let _x_i1 = o#expr _x_i1 in MePkg _x _x_i1
|
||||
| MeAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#module_expr _x_i3 in MeAtt _x _x_i1 _x_i2 _x_i3
|
||||
| MeAnt _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in MeAnt _x _x_i1 ];
|
||||
|
@ -5431,6 +5591,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| TyPkg _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#module_type _x_i1 in TyPkg _x _x_i1
|
||||
| TyAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#ctyp _x_i3 in TyAtt _x _x_i1 _x_i2 _x_i3
|
||||
| TyAnt _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in TyAnt _x _x_i1 ];
|
||||
|
@ -5462,6 +5627,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let _x = o#loc _x in
|
||||
let _x_i1 = o#class_type _x_i1 in
|
||||
let _x_i2 = o#class_type _x_i2 in CtEq _x _x_i1 _x_i2
|
||||
| CtAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#class_type _x_i3 in CtAtt _x _x_i1 _x_i2 _x_i3
|
||||
| CtAnt _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in CtAnt _x _x_i1 ];
|
||||
|
@ -5580,6 +5750,11 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let _x = o#loc _x in
|
||||
let _x_i1 = o#class_expr _x_i1 in
|
||||
let _x_i2 = o#class_expr _x_i2 in CeEq _x _x_i1 _x_i2
|
||||
| CeAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in
|
||||
let _x_i2 = o#str_item _x_i2 in
|
||||
let _x_i3 = o#class_expr _x_i3 in CeAtt _x _x_i1 _x_i2 _x_i3
|
||||
| CeAnt _x _x_i1 ->
|
||||
let _x = o#loc _x in
|
||||
let _x_i1 = o#string _x_i1 in CeAnt _x _x_i1 ];
|
||||
|
@ -5788,6 +5963,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| PaTyp _x _x_i1 -> let o = o#loc _x in let o = o#ident _x_i1 in o
|
||||
| PaVrn _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o
|
||||
| PaLaz _x _x_i1 -> let o = o#loc _x in let o = o#patt _x_i1 in o
|
||||
| PaAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#patt _x_i3 in o
|
||||
| PaMod _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method override_flag : override_flag -> 'self_type =
|
||||
fun
|
||||
|
@ -5815,6 +5994,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let o = o#module_type _x_i1 in let o = o#with_constr _x_i2 in o
|
||||
| MtOf _x _x_i1 ->
|
||||
let o = o#loc _x in let o = o#module_expr _x_i1 in o
|
||||
| MtAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#module_type _x_i3 in o
|
||||
| MtAnt _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method module_expr : module_expr -> 'self_type =
|
||||
fun
|
||||
|
@ -5833,6 +6016,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let o = o#loc _x in
|
||||
let o = o#module_expr _x_i1 in let o = o#module_type _x_i2 in o
|
||||
| MePkg _x _x_i1 -> let o = o#loc _x in let o = o#expr _x_i1 in o
|
||||
| MeAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#module_expr _x_i3 in o
|
||||
| MeAnt _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method module_binding : module_binding -> 'self_type =
|
||||
fun
|
||||
|
@ -6100,6 +6287,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
let o = o#ctyp _x_i1 in let o = o#ctyp _x_i2 in o
|
||||
| TyPkg _x _x_i1 ->
|
||||
let o = o#loc _x in let o = o#module_type _x_i1 in o
|
||||
| TyAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#ctyp _x_i3 in o
|
||||
| TyAnt _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method class_type : class_type -> 'self_type =
|
||||
fun
|
||||
|
@ -6123,6 +6314,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| CtEq _x _x_i1 _x_i2 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#class_type _x_i1 in let o = o#class_type _x_i2 in o
|
||||
| CtAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#class_type _x_i3 in o
|
||||
| CtAnt _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method class_str_item : class_str_item -> 'self_type =
|
||||
fun
|
||||
|
@ -6214,6 +6409,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
|
|||
| CeEq _x _x_i1 _x_i2 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#class_expr _x_i1 in let o = o#class_expr _x_i2 in o
|
||||
| CeAtt _x _x_i1 _x_i2 _x_i3 ->
|
||||
let o = o#loc _x in
|
||||
let o = o#string _x_i1 in
|
||||
let o = o#str_item _x_i2 in let o = o#class_expr _x_i3 in o
|
||||
| CeAnt _x _x_i1 -> let o = o#loc _x in let o = o#string _x_i1 in o ];
|
||||
method binding : binding -> 'self_type =
|
||||
fun
|
||||
|
|
Loading…
Reference in New Issue