]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/camlp4/Camlp4Parsers/Camlp4OCamlRevisedParser.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / camlp4 / Camlp4Parsers / Camlp4OCamlRevisedParser.ml
1 open Camlp4;                                        (* -*- camlp4r -*- *)
2 (****************************************************************************)
3 (*                                                                          *)
4 (*                              Objective Caml                              *)
5 (*                                                                          *)
6 (*                            INRIA Rocquencourt                            *)
7 (*                                                                          *)
8 (*  Copyright 2002-2006 Institut National de Recherche en Informatique et   *)
9 (*  en Automatique.  All rights reserved.  This file is distributed under   *)
10 (*  the terms of the GNU Library General Public License, with the special   *)
11 (*  exception on linking described in LICENSE at the top of the Objective   *)
12 (*  Caml source tree.                                                       *)
13 (*                                                                          *)
14 (****************************************************************************)
15
16 (* Authors:
17  * - Daniel de Rauglaudre: initial version
18  * - Nicolas Pouillard: refactoring
19  *)
20
21 module Id = struct
22   value name = "Camlp4OCamlRevisedParser";
23   value version = Sys.ocaml_version;
24 end;
25
26 module Make (Syntax : Sig.Camlp4Syntax) = struct
27   open Sig;
28   include Syntax;
29
30   (* Camlp4_config.constructors_arity.val := True; *)
31   Camlp4_config.constructors_arity.val := False;
32
33   value help_sequences () =
34     do {
35       Printf.eprintf "\
36 New syntax:
37     (e1; e2; ... ; en) OR begin e1; e2; ... ; en end
38     while e do e1; e2; ... ; en done
39     for v = v1 to/downto v2 do e1; e2; ... ; en done
40 Old syntax (still supported):
41     do {e1; e2; ... ; en}
42     while e do {e1; e2; ... ; en}
43     for v = v1 to/downto v2 do {e1; e2; ... ; en}
44 Very old (no more supported) syntax:
45     do e1; e2; ... ; en-1; return en
46     while e do e1; e2; ... ; en; done
47     for v = v1 to/downto v2 do e1; e2; ... ; en; done
48   ";
49       flush stderr;
50       exit 1
51     }
52   ;
53   Options.add "-help_seq" (Arg.Unit help_sequences)
54     "Print explanations about new sequences and exit.";
55
56   Gram.Entry.clear a_CHAR;
57   Gram.Entry.clear a_FLOAT;
58   Gram.Entry.clear a_INT;
59   Gram.Entry.clear a_INT32;
60   Gram.Entry.clear a_INT64;
61   Gram.Entry.clear a_LABEL;
62   Gram.Entry.clear a_LIDENT;
63   Gram.Entry.clear a_NATIVEINT;
64   Gram.Entry.clear a_OPTLABEL;
65   Gram.Entry.clear a_STRING;
66   Gram.Entry.clear a_UIDENT;
67   Gram.Entry.clear a_ident;
68   Gram.Entry.clear amp_ctyp;
69   Gram.Entry.clear and_ctyp;
70   Gram.Entry.clear match_case;
71   Gram.Entry.clear match_case0;
72   Gram.Entry.clear match_case_quot;
73   Gram.Entry.clear binding;
74   Gram.Entry.clear binding_quot;
75   Gram.Entry.clear rec_binding_quot;
76   Gram.Entry.clear class_declaration;
77   Gram.Entry.clear class_description;
78   Gram.Entry.clear class_expr;
79   Gram.Entry.clear class_expr_quot;
80   Gram.Entry.clear class_fun_binding;
81   Gram.Entry.clear class_fun_def;
82   Gram.Entry.clear class_info_for_class_expr;
83   Gram.Entry.clear class_info_for_class_type;
84   Gram.Entry.clear class_longident;
85   Gram.Entry.clear class_longident_and_param;
86   Gram.Entry.clear class_name_and_param;
87   Gram.Entry.clear class_sig_item;
88   Gram.Entry.clear class_sig_item_quot;
89   Gram.Entry.clear class_signature;
90   Gram.Entry.clear class_str_item;
91   Gram.Entry.clear class_str_item_quot;
92   Gram.Entry.clear class_structure;
93   Gram.Entry.clear class_type;
94   Gram.Entry.clear class_type_declaration;
95   Gram.Entry.clear class_type_longident;
96   Gram.Entry.clear class_type_longident_and_param;
97   Gram.Entry.clear class_type_plus;
98   Gram.Entry.clear class_type_quot;
99   Gram.Entry.clear comma_ctyp;
100   Gram.Entry.clear comma_expr;
101   Gram.Entry.clear comma_ipatt;
102   Gram.Entry.clear comma_patt;
103   Gram.Entry.clear comma_type_parameter;
104   Gram.Entry.clear constrain;
105   Gram.Entry.clear constructor_arg_list;
106   Gram.Entry.clear constructor_declaration;
107   Gram.Entry.clear constructor_declarations;
108   Gram.Entry.clear ctyp;
109   Gram.Entry.clear ctyp_quot;
110   Gram.Entry.clear cvalue_binding;
111   Gram.Entry.clear direction_flag;
112   Gram.Entry.clear dummy;
113   Gram.Entry.clear eq_expr;
114   Gram.Entry.clear expr;
115   Gram.Entry.clear expr_eoi;
116   Gram.Entry.clear expr_quot;
117   Gram.Entry.clear field_expr;
118   Gram.Entry.clear field_expr_list;
119   Gram.Entry.clear fun_binding;
120   Gram.Entry.clear fun_def;
121   Gram.Entry.clear ident;
122   Gram.Entry.clear ident_quot;
123   Gram.Entry.clear implem;
124   Gram.Entry.clear interf;
125   Gram.Entry.clear ipatt;
126   Gram.Entry.clear ipatt_tcon;
127   Gram.Entry.clear label;
128   Gram.Entry.clear label_declaration;
129   Gram.Entry.clear label_declaration_list;
130   Gram.Entry.clear label_expr_list;
131   Gram.Entry.clear label_expr;
132   Gram.Entry.clear label_ipatt;
133   Gram.Entry.clear label_ipatt_list;
134   Gram.Entry.clear label_longident;
135   Gram.Entry.clear label_patt;
136   Gram.Entry.clear label_patt_list;
137   Gram.Entry.clear labeled_ipatt;
138   Gram.Entry.clear let_binding;
139   Gram.Entry.clear meth_list;
140   Gram.Entry.clear meth_decl;
141   Gram.Entry.clear module_binding;
142   Gram.Entry.clear module_binding0;
143   Gram.Entry.clear module_binding_quot;
144   Gram.Entry.clear module_declaration;
145   Gram.Entry.clear module_expr;
146   Gram.Entry.clear module_expr_quot;
147   Gram.Entry.clear module_longident;
148   Gram.Entry.clear module_longident_with_app;
149   Gram.Entry.clear module_rec_declaration;
150   Gram.Entry.clear module_type;
151   Gram.Entry.clear module_type_quot;
152   Gram.Entry.clear more_ctyp;
153   Gram.Entry.clear name_tags;
154   Gram.Entry.clear opt_as_lident;
155   Gram.Entry.clear opt_class_self_patt;
156   Gram.Entry.clear opt_class_self_type;
157   Gram.Entry.clear opt_comma_ctyp;
158   Gram.Entry.clear opt_dot_dot;
159   Gram.Entry.clear opt_eq_ctyp;
160   Gram.Entry.clear opt_expr;
161   Gram.Entry.clear opt_meth_list;
162   Gram.Entry.clear opt_mutable;
163   Gram.Entry.clear opt_polyt;
164   Gram.Entry.clear opt_private;
165   Gram.Entry.clear opt_rec;
166   Gram.Entry.clear opt_virtual;
167   Gram.Entry.clear opt_when_expr;
168   Gram.Entry.clear patt;
169   Gram.Entry.clear patt_as_patt_opt;
170   Gram.Entry.clear patt_eoi;
171   Gram.Entry.clear patt_quot;
172   Gram.Entry.clear patt_tcon;
173   Gram.Entry.clear phrase;
174   Gram.Entry.clear poly_type;
175   Gram.Entry.clear row_field;
176   Gram.Entry.clear sem_expr;
177   Gram.Entry.clear sem_expr_for_list;
178   Gram.Entry.clear sem_patt;
179   Gram.Entry.clear sem_patt_for_list;
180   Gram.Entry.clear semi;
181   Gram.Entry.clear sequence;
182   Gram.Entry.clear sig_item;
183   Gram.Entry.clear sig_item_quot;
184   Gram.Entry.clear sig_items;
185   Gram.Entry.clear star_ctyp;
186   Gram.Entry.clear str_item;
187   Gram.Entry.clear str_item_quot;
188   Gram.Entry.clear str_items;
189   Gram.Entry.clear top_phrase;
190   Gram.Entry.clear type_constraint;
191   Gram.Entry.clear type_declaration;
192   Gram.Entry.clear type_ident_and_parameters;
193   Gram.Entry.clear type_kind;
194   Gram.Entry.clear type_longident;
195   Gram.Entry.clear type_longident_and_parameters;
196   Gram.Entry.clear type_parameter;
197   Gram.Entry.clear type_parameters;
198   Gram.Entry.clear typevars;
199   Gram.Entry.clear use_file;
200   Gram.Entry.clear val_longident;
201   Gram.Entry.clear value_let;
202   Gram.Entry.clear value_val;
203   Gram.Entry.clear with_constr;
204   Gram.Entry.clear with_constr_quot;
205
206   value neg_string n =
207     let len = String.length n in
208     if len > 0 && n.[0] = '-' then String.sub n 1 (len - 1)
209     else "-" ^ n
210   ;
211
212   value mkumin _loc f arg =
213     match arg with
214     [ <:expr< $int:n$ >> -> <:expr< $int:neg_string n$ >>
215     | <:expr< $int32:n$ >> -> <:expr< $int32:neg_string n$ >>
216     | <:expr< $int64:n$ >> -> <:expr< $int64:neg_string n$ >>
217     | <:expr< $nativeint:n$ >> -> <:expr< $nativeint:neg_string n$ >>
218     | <:expr< $flo:n$ >> -> <:expr< $flo:neg_string n$ >>
219     | _ -> <:expr< $lid:"~" ^ f$ $arg$ >> ];
220
221   value mklistexp _loc last =
222     loop True where rec loop top =
223       fun
224       [ [] ->
225           match last with
226           [ Some e -> e
227           | None -> <:expr< [] >> ]
228       | [e1 :: el] ->
229           let _loc =
230             if top then _loc else Loc.merge (Ast.loc_of_expr e1) _loc
231           in
232           <:expr< [$e1$ :: $loop False el$] >> ]
233   ;
234
235   value mkassert _loc =
236     fun
237     [ <:expr< False >> ->
238         <:expr< assert False >> (* this case takes care about
239                                    the special assert false node *)
240     | e -> <:expr< assert $e$ >> ]
241   ;
242
243   value append_eLem el e = el @ [e];
244   value mk_anti ?(c = "") n s = "\\$"^n^c^":"^s;
245
246   value mksequence _loc =
247     fun
248     [ <:expr< $_$; $_$ >> | <:expr< $anti:_$ >> as e -> <:expr< do { $e$ } >>
249     | e -> e ]
250   ;
251
252   value mksequence' _loc =
253     fun
254     [ <:expr< $_$; $_$ >> as e -> <:expr< do { $e$ } >>
255     | e -> e ]
256   ;
257
258   value module_type_app mt1 mt2 =
259     match (mt1, mt2) with
260     [ (<:module_type@_loc< $id:i1$ >>, <:module_type< $id:i2$ >>) ->
261         <:module_type< $id:<:ident< $i1$ $i2$ >>$ >>
262     | _ -> raise Stream.Failure ];
263
264   value module_type_acc mt1 mt2 =
265     match (mt1, mt2) with
266     [ (<:module_type@_loc< $id:i1$ >>, <:module_type< $id:i2$ >>) ->
267         <:module_type< $id:<:ident< $i1$.$i2$ >>$ >>
268     | _ -> raise Stream.Failure ];
269
270   value bigarray_get _loc arr arg =
271     let coords =
272       match arg with
273       [ <:expr< ($e1$, $e2$) >> | <:expr< $e1$, $e2$ >> ->
274           Ast.list_of_expr e1 (Ast.list_of_expr e2 [])
275       | _ -> [arg] ]
276     in
277     match coords with
278     [ [c1] -> <:expr< Bigarray.Array1.get $arr$ $c1$ >>
279     | [c1; c2] -> <:expr< Bigarray.Array2.get $arr$ $c1$ $c2$ >>
280     | [c1; c2; c3] -> <:expr< Bigarray.Array3.get $arr$ $c1$ $c2$ $c3$ >>
281     (* | coords -> <:expr< Bigarray.Genarray.get $arr$ [| $list:coords$ |] >> ] *)
282     | coords ->
283        <:expr< Bigarray.Genarray.get $arr$ [| $Ast.exSem_of_list coords$ |] >> ];
284
285   value bigarray_set _loc var newval =
286     match var with
287     [ <:expr< Bigarray.Array1.get $arr$ $c1$ >> ->
288         Some <:expr< Bigarray.Array1.set $arr$ $c1$ $newval$ >>
289     | <:expr< Bigarray.Array2.get $arr$ $c1$ $c2$ >> ->
290         Some <:expr< Bigarray.Array2.set $arr$ $c1$ $c2$ $newval$ >>
291     | <:expr< Bigarray.Array3.get $arr$ $c1$ $c2$ $c3$ >> ->
292         Some <:expr< Bigarray.Array3.set $arr$ $c1$ $c2$ $c3$ $newval$ >>
293     | <:expr< Bigarray.Genarray.get $arr$ [| $coords$ |] >> ->
294         Some <:expr< Bigarray.Genarray.set $arr$ [| $coords$ |] $newval$ >>
295     | _ -> None ];
296
297   value test_not_left_brace_nor_do =
298     Gram.Entry.of_parser "test_not_left_brace_nor_do"
299       (fun strm ->
300         match Stream.peek strm with
301         [ Some(KEYWORD "{" | KEYWORD "do", _) -> raise Stream.Failure
302         | _ -> () ]);
303
304   value stopped_at _loc =
305     Some (Loc.move_line 1 _loc) (* FIXME be more precise *);
306
307   value symbolchar =
308     let list =
309       ['$'; '!'; '%'; '&'; '*'; '+'; '-'; '.'; '/'; ':'; '<'; '='; '>'; '?';
310        '@'; '^'; '|'; '~'; '\\']
311     in
312     let rec loop s i =
313       if i == String.length s then True
314       else if List.mem s.[i] list then loop s (i + 1)
315       else False
316     in
317     loop
318   ;
319
320   let list = ['!'; '?'; '~'] in
321   let excl = ["!="; "??"] in
322   Gram.Entry.setup_parser prefixop
323     (parser
324       [: `(KEYWORD x | SYMBOL x, _loc)
325           when
326             not (List.mem x excl) && String.length x >= 2 &&
327             List.mem x.[0] list && symbolchar x 1 :] ->
328         <:expr< $lid:x$ >>)
329   ;
330
331   let list_ok = ["<"; ">"; "<="; ">="; "="; "<>"; "=="; "!="; "$"] in 
332   let list_first_char_ok = ['='; '<'; '>'; '|'; '&'; '$'; '!'] in
333   let excl = ["<-"; "||"; "&&"] in
334   Gram.Entry.setup_parser infixop0
335     (parser
336       [: `(KEYWORD x | SYMBOL x, _loc)
337           when
338             (List.mem x list_ok) ||
339             (not (List.mem x excl) && String.length x >= 2 &&
340               List.mem x.[0] list_first_char_ok && symbolchar x 1) :] ->
341         <:expr< $lid:x$ >>)
342   ;
343
344   let list = ['@'; '^'] in
345   Gram.Entry.setup_parser infixop1
346     (parser
347       [: `(KEYWORD x | SYMBOL x, _loc)
348           when
349             String.length x >= 1 && List.mem x.[0] list &&
350             symbolchar x 1 :] ->
351         <:expr< $lid:x$ >>)
352   ;
353
354   let list = ['+'; '-'] in
355   Gram.Entry.setup_parser infixop2
356     (parser
357       [: `(KEYWORD x | SYMBOL x, _loc)
358           when
359             x <> "->" && String.length x >= 1 && List.mem x.[0] list &&
360             symbolchar x 1 :] ->
361         <:expr< $lid:x$ >>)
362   ;
363
364   let list = ['*'; '/'; '%'; '\\'] in
365   Gram.Entry.setup_parser infixop3
366     (parser
367       [: `(KEYWORD x | SYMBOL x, _loc)
368           when
369             String.length x >= 1 && List.mem x.[0] list &&
370             (x.[0] <> '*' || String.length x < 2 || x.[1] <> '*') &&
371             symbolchar x 1 :] ->
372         <:expr< $lid:x$ >>)
373   ;
374
375   Gram.Entry.setup_parser infixop4
376     (parser
377       [: `(KEYWORD x | SYMBOL x, _loc)
378           when
379             String.length x >= 2 && x.[0] == '*' && x.[1] == '*' &&
380             symbolchar x 2 :] ->
381         <:expr< $lid:x$ >>)
382   ;
383
384   value rec infix_kwds_filter =
385     parser
386     [ [: `((KEYWORD "(", _) as tok); xs :] ->
387         match xs with parser
388         [ [: `(KEYWORD ("mod"|"land"|"lor"|"lxor"|"lsl"|"lsr"|"asr" as i), _loc);
389              `(KEYWORD ")", _); xs :] ->
390                 [: `(LIDENT i, _loc); infix_kwds_filter xs :]
391         | [: xs :] ->
392                 [: `tok; infix_kwds_filter xs :] ]
393     | [: `x; xs :] -> [: `x; infix_kwds_filter xs :] ];
394
395   Token.Filter.define_filter (Gram.get_filter ())
396     (fun f strm -> infix_kwds_filter (f strm));
397
398   (* transmit the context *)
399   Gram.Entry.setup_parser sem_expr begin
400     let symb1 = Gram.parse_tokens_after_filter expr in
401     let symb =
402       parser
403       [ [: `(ANTIQUOT ("list" as n) s, _loc) :] -> <:expr< $anti:mk_anti ~c:"expr;" n s$ >>
404       | [: a = symb1 :] -> a ]
405     in
406     let rec kont al =
407       parser
408       [ [: `(KEYWORD ";", _loc); a = symb; s :] -> kont <:expr< $al$; $a$ >> s
409       | [: :] -> al ]
410     in
411     parser [: a = symb; s :] -> kont a s
412   end;
413
414   EXTEND Gram
415     GLOBAL:
416       a_CHAR a_FLOAT a_INT a_INT32 a_INT64 a_LABEL a_LIDENT rec_binding_quot
417       a_NATIVEINT a_OPTLABEL a_STRING a_UIDENT a_ident
418       amp_ctyp and_ctyp match_case match_case0 match_case_quot binding binding_quot
419       class_declaration class_description class_expr class_expr_quot
420       class_fun_binding class_fun_def class_info_for_class_expr
421       class_info_for_class_type class_longident class_longident_and_param
422       class_name_and_param class_sig_item class_sig_item_quot class_signature
423       class_str_item class_str_item_quot class_structure class_type
424       class_type_declaration class_type_longident
425       class_type_longident_and_param class_type_plus class_type_quot
426       comma_ctyp comma_expr comma_ipatt comma_patt comma_type_parameter
427       constrain constructor_arg_list constructor_declaration
428       constructor_declarations ctyp ctyp_quot cvalue_binding direction_flag
429       dummy eq_expr expr expr_eoi expr_quot field_expr field_expr_list fun_binding
430       fun_def ident ident_quot implem interf ipatt ipatt_tcon label
431       label_declaration label_declaration_list label_expr label_expr_list
432       label_ipatt label_ipatt_list label_longident label_patt label_patt_list
433       labeled_ipatt let_binding meth_list meth_decl module_binding module_binding0
434       module_binding_quot module_declaration module_expr module_expr_quot
435       module_longident module_longident_with_app module_rec_declaration
436       module_type module_type_quot more_ctyp name_tags opt_as_lident
437       opt_class_self_patt opt_class_self_type opt_comma_ctyp opt_dot_dot opt_eq_ctyp opt_expr
438       opt_meth_list opt_mutable opt_polyt opt_private opt_rec
439       opt_virtual opt_when_expr patt patt_as_patt_opt patt_eoi
440       patt_quot patt_tcon phrase poly_type row_field
441       sem_expr sem_expr_for_list sem_patt sem_patt_for_list semi sequence
442       sig_item sig_item_quot sig_items star_ctyp str_item str_item_quot
443       str_items top_phrase type_constraint type_declaration
444       type_ident_and_parameters type_kind type_longident
445       type_longident_and_parameters type_parameter type_parameters typevars
446       use_file val_longident value_let value_val with_constr with_constr_quot
447       infixop0 infixop1 infixop2 infixop3 infixop4 do_sequence;
448     module_expr:
449       [ "top"
450         [ "functor"; "("; i = a_UIDENT; ":"; t = module_type; ")"; "->";
451           me = SELF ->
452             <:module_expr< functor ( $i$ : $t$ ) -> $me$ >>
453         | "struct"; st = str_items; "end" ->
454             <:module_expr< struct $st$ end >> ]
455       | "apply"
456         [ me1 = SELF; me2 = SELF -> <:module_expr< $me1$ $me2$ >> ]
457       | "simple"
458         [ `ANTIQUOT (""|"mexp"|"anti"|"list" as n) s ->
459             <:module_expr< $anti:mk_anti ~c:"module_expr" n s$ >>
460         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.module_expr_tag
461         | i = module_longident -> <:module_expr< $id:i$ >>
462         | "("; me = SELF; ":"; mt = module_type; ")" ->
463             <:module_expr< ( $me$ : $mt$ ) >>
464         | "("; me = SELF; ")" -> <:module_expr< $me$ >> ] ]
465     ;
466     str_item:
467       [ "top"
468         [ "exception"; t = constructor_declaration ->
469             <:str_item< exception $t$ >>
470         | "exception"; t = constructor_declaration; "="; i = type_longident ->
471             <:str_item< exception $t$ = $i$ >>
472         | "external"; i = a_LIDENT; ":"; t = ctyp; "="; sl = string_list ->
473             <:str_item< external $i$ : $t$ = $sl$ >>
474         | "include"; me = module_expr -> <:str_item< include $me$ >>
475         | "module"; i = a_UIDENT; mb = module_binding0 ->
476             <:str_item< module $i$ = $mb$ >>
477         | "module"; "rec"; mb = module_binding ->
478             <:str_item< module rec $mb$ >>
479         | "module"; "type"; i = a_UIDENT; "="; mt = module_type ->
480             <:str_item< module type $i$ = $mt$ >>
481         | "open"; i = module_longident -> <:str_item< open $i$ >>
482         | "type"; td = type_declaration ->
483             <:str_item< type $td$ >>
484         | value_let; r = opt_rec; bi = binding ->
485             <:str_item< value $rec:r$ $bi$ >>
486         | "class"; cd = class_declaration ->
487             <:str_item< class $cd$ >>
488         | "class"; "type"; ctd = class_type_declaration ->
489             <:str_item< class type $ctd$ >>
490         | `ANTIQUOT (""|"stri"|"anti"|"list" as n) s ->
491             <:str_item< $anti:mk_anti ~c:"str_item" n s$ >>
492         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.str_item_tag
493         | e = expr -> <:str_item< $exp:e$ >> ] ]
494     ;
495     module_binding0:
496       [ RIGHTA
497         [ "("; m = a_UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
498             <:module_expr< functor ( $m$ : $mt$ ) -> $mb$ >>
499         | ":"; mt = module_type; "="; me = module_expr ->
500             <:module_expr< ( $me$ : $mt$ ) >>
501         | "="; me = module_expr -> <:module_expr< $me$ >> ] ]
502     ;
503     module_binding:
504       [ LEFTA
505         [ b1 = SELF; "and"; b2 = SELF ->
506             <:module_binding< $b1$ and $b2$ >>
507         | `ANTIQUOT ("module_binding"|"anti"|"list" as n) s ->
508             <:module_binding< $anti:mk_anti ~c:"module_binding" n s$ >>
509         | `ANTIQUOT ("" as n) s ->
510             <:module_binding< $anti:mk_anti ~c:"module_binding" n s$ >>
511         | `ANTIQUOT ("" as n) m; ":"; mt = module_type; "="; me = module_expr ->
512             <:module_binding< $mk_anti n m$ : $mt$ = $me$ >>
513         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.module_binding_tag
514         | m = a_UIDENT; ":"; mt = module_type; "="; me = module_expr ->
515             <:module_binding< $m$ : $mt$ = $me$ >> ] ]
516     ;
517     module_type:
518       [ "top"
519         [ "functor"; "("; i = a_UIDENT; ":"; t = SELF; ")"; "->"; mt = SELF ->
520             <:module_type< functor ( $i$ : $t$ ) -> $mt$ >> ]
521       | "with"
522         [ mt = SELF; "with"; wc = with_constr ->
523             <:module_type< $mt$ with $wc$ >> ]
524       | "apply"
525         [ mt1 = SELF; mt2 = SELF; dummy -> module_type_app mt1 mt2 ]
526       | "."
527         [ mt1 = SELF; "."; mt2 = SELF -> module_type_acc mt1 mt2 ]
528       | "sig"
529         [ "sig"; sg = sig_items; "end" ->
530             <:module_type< sig $sg$ end >> ]
531       | "simple"
532         [ `ANTIQUOT (""|"mtyp"|"anti"|"list" as n) s ->
533             <:module_type< $anti:mk_anti ~c:"module_type" n s$ >>
534         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.module_type_tag
535         | i = module_longident_with_app -> <:module_type< $id:i$ >>
536         | "'"; i = a_ident -> <:module_type< ' $i$ >>
537         | "("; mt = SELF; ")" -> <:module_type< $mt$ >> ] ]
538     ;
539     sig_item:
540       [ "top"
541         [ `ANTIQUOT (""|"sigi"|"anti"|"list" as n) s ->
542             <:sig_item< $anti:mk_anti ~c:"sig_item" n s$ >>
543         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.sig_item_tag
544         | "exception"; t = constructor_declaration ->
545             <:sig_item< exception $t$ >>
546         | "external"; i = a_LIDENT; ":"; t = ctyp; "="; sl = string_list ->
547             <:sig_item< external $i$ : $t$ = $sl$ >>
548         | "include"; mt = module_type -> <:sig_item< include $mt$ >>
549         | "module"; i = a_UIDENT; mt = module_declaration ->
550             <:sig_item< module $i$ : $mt$ >>
551         | "module"; "rec"; mb = module_rec_declaration ->
552             <:sig_item< module rec $mb$ >>
553         | "module"; "type"; i = a_UIDENT; "="; mt = module_type ->
554             <:sig_item< module type $i$ = $mt$ >>
555         | "module"; "type"; i = a_UIDENT ->
556             <:sig_item< module type $i$ >>
557         | "open"; i = module_longident -> <:sig_item< open $i$ >>
558         | "type"; t = type_declaration ->
559             <:sig_item< type $t$ >>
560         | value_val; i = a_LIDENT; ":"; t = ctyp ->
561             <:sig_item< value $i$ : $t$ >>
562         | "class"; cd = class_description ->
563             <:sig_item< class $cd$ >>
564         | "class"; "type"; ctd = class_type_declaration ->
565             <:sig_item< class type $ctd$ >> ] ]
566     ;
567     module_declaration:
568       [ RIGHTA
569         [ ":"; mt = module_type -> <:module_type< $mt$ >>
570         | "("; i = a_UIDENT; ":"; t = module_type; ")"; mt = SELF ->
571             <:module_type< functor ( $i$ : $t$ ) -> $mt$ >> ] ]
572     ;
573     module_rec_declaration:
574       [ LEFTA
575         [ m1 = SELF; "and"; m2 = SELF -> <:module_binding< $m1$ and $m2$ >>
576         | `ANTIQUOT (""|"module_binding"|"anti"|"list" as n) s ->
577             <:module_binding< $anti:mk_anti ~c:"module_binding" n s$ >>
578         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.module_binding_tag
579         | m = a_UIDENT; ":"; mt = module_type -> <:module_binding< $m$ : $mt$ >>
580       ] ]
581     ;
582     with_constr:
583       [ LEFTA
584         [ wc1 = SELF; "and"; wc2 = SELF -> <:with_constr< $wc1$ and $wc2$ >>
585         | `ANTIQUOT (""|"with_constr"|"anti"|"list" as n) s ->
586             <:with_constr< $anti:mk_anti ~c:"with_constr" n s$ >>
587         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.with_constr_tag
588         | "type"; `ANTIQUOT (""|"typ"|"anti" as n) s; "="; t = ctyp ->
589             <:with_constr< type $anti:mk_anti ~c:"ctyp" n s$ = $t$ >>
590         | "type"; t1 = type_longident_and_parameters; "="; t2 = ctyp ->
591             <:with_constr< type $t1$ = $t2$ >>
592         | "module"; i1 = module_longident; "="; i2 = module_longident_with_app ->
593             <:with_constr< module $i1$ = $i2$ >> ] ]
594     ;
595     expr:
596       [ "top" RIGHTA
597         [ "let"; r = opt_rec; bi = binding; "in"; x = SELF ->
598             <:expr< let $rec:r$ $bi$ in $x$ >>
599         | "let"; "module"; m = a_UIDENT; mb = module_binding0; "in"; e = SELF ->
600             <:expr< let module $m$ = $mb$ in $e$ >>
601         | "fun"; "["; a = LIST0 match_case0 SEP "|"; "]" ->
602             <:expr< fun [ $list:a$ ] >>
603         | "fun"; e = fun_def -> e
604         | "match"; e = sequence; "with"; a = match_case ->
605             <:expr< match $mksequence' _loc e$ with [ $a$ ] >>
606         | "try"; e = sequence; "with"; a = match_case ->
607             <:expr< try $mksequence' _loc e$ with [ $a$ ] >>
608         | "if"; e1 = SELF; "then"; e2 = SELF; "else"; e3 = SELF ->
609             <:expr< if $e1$ then $e2$ else $e3$ >>
610         | "do"; seq = do_sequence -> mksequence _loc seq
611         | "for"; i = a_LIDENT; "="; e1 = sequence; df = direction_flag;
612           e2 = sequence; "do"; seq = do_sequence ->
613             <:expr< for $i$ = $mksequence' _loc e1$ $to:df$ $mksequence' _loc e2$ do { $seq$ } >>
614         | "while"; e = sequence; "do"; seq = do_sequence ->
615             <:expr< while $mksequence' _loc e$ do { $seq$ } >>
616         | "object"; csp = opt_class_self_patt; cst = class_structure; "end" ->
617             <:expr< object ($csp$) $cst$ end >> ]
618       | "where"
619         [ e = SELF; "where"; rf = opt_rec; lb = let_binding ->
620             <:expr< let $rec:rf$ $lb$ in $e$ >> ]
621       | ":=" NONA
622         [ e1 = SELF; ":="; e2 = SELF; dummy ->
623             match bigarray_set _loc e1 e2 with
624             [ Some e -> e
625             | None -> <:expr< $e1$ := $e2$ >> ] ]
626       | "||" RIGHTA
627         [ e1 = SELF; op = infixop6; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
628       | "&&" RIGHTA
629         [ e1 = SELF; op = infixop5; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
630       | "<" LEFTA
631         [ e1 = SELF; op = infixop0; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
632       | "^" RIGHTA
633         [ e1 = SELF; op = infixop1; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
634       | "+" LEFTA
635         [ e1 = SELF; op = infixop2; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
636       | "*" LEFTA
637         [ e1 = SELF; "land"; e2 = SELF -> <:expr< $e1$ land $e2$ >>
638         | e1 = SELF; "lor"; e2 = SELF -> <:expr< $e1$ lor $e2$ >>
639         | e1 = SELF; "lxor"; e2 = SELF -> <:expr< $e1$ lxor $e2$ >>
640         | e1 = SELF; "mod"; e2 = SELF -> <:expr< $e1$ mod $e2$ >>
641         | e1 = SELF; op = infixop3; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
642       | "**" RIGHTA
643         [ e1 = SELF; "asr"; e2 = SELF -> <:expr< $e1$ asr $e2$ >>
644         | e1 = SELF; "lsl"; e2 = SELF -> <:expr< $e1$ lsl $e2$ >>
645         | e1 = SELF; "lsr"; e2 = SELF -> <:expr< $e1$ lsr $e2$ >>
646         | e1 = SELF; op = infixop4; e2 = SELF -> <:expr< $op$ $e1$ $e2$ >> ]
647       | "unary minus" NONA
648         [ "-"; e = SELF -> mkumin _loc "-" e
649         | "-."; e = SELF -> mkumin _loc "-." e ]
650       | "apply" LEFTA
651         [ e1 = SELF; e2 = SELF -> <:expr< $e1$ $e2$ >>
652         | "assert"; e = SELF -> mkassert _loc e
653         | "new"; i = class_longident -> <:expr< new $i$ >>
654         | "lazy"; e = SELF -> <:expr< lazy $e$ >> ]
655       | "label" NONA
656         [ "~"; i = a_LIDENT; ":"; e = SELF -> <:expr< ~ $i$ : $e$ >>
657         | "~"; i = a_LIDENT -> <:expr< ~ $i$ >>
658
659         (* Here it's LABEL and not tilde_label since ~a:b is different than ~a : b *)
660         | `LABEL i; e = SELF -> <:expr< ~ $i$ : $e$ >>
661
662         (* Same remark for ?a:b *)
663         | `OPTLABEL i; e = SELF -> <:expr< ? $i$ : $e$ >>
664
665         | "?"; i = a_LIDENT; ":"; e = SELF -> <:expr< ? $i$ : $e$ >>
666         | "?"; i = a_LIDENT -> <:expr< ? $i$ >> ]
667       | "." LEFTA
668         [ e1 = SELF; "."; "("; e2 = SELF; ")" -> <:expr< $e1$ .( $e2$ ) >>
669         | e1 = SELF; "."; "["; e2 = SELF; "]" -> <:expr< $e1$ .[ $e2$ ] >>
670         | e1 = SELF; "."; "{"; e2 = comma_expr; "}" -> bigarray_get _loc e1 e2
671         | e1 = SELF; "."; e2 = SELF -> <:expr< $e1$ . $e2$ >>
672         | e = SELF; "#"; lab = label -> <:expr< $e$ # $lab$ >> ]
673       | "~-" NONA
674         [ "!"; e = SELF -> <:expr< $e$.val >>
675         | f = prefixop; e = SELF -> <:expr< $f$ $e$ >> ]
676       | "simple"
677         [ `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.expr_tag
678         | `ANTIQUOT ("exp"|""|"anti" as n) s ->
679             <:expr< $anti:mk_anti ~c:"expr" n s$ >>
680         | `ANTIQUOT ("`bool" as n) s ->
681             <:expr< $id:<:ident< $anti:mk_anti n s$ >>$ >>
682         | `ANTIQUOT ("tup" as n) s ->
683             <:expr< $tup: <:expr< $anti:mk_anti ~c:"expr" n s$ >>$ >>
684         | `ANTIQUOT ("seq" as n) s ->
685             <:expr< do $anti:mk_anti ~c:"expr" n s$ done >>
686         | s = a_INT -> <:expr< $int:s$ >>
687         | s = a_INT32 -> <:expr< $int32:s$ >>
688         | s = a_INT64 -> <:expr< $int64:s$ >>
689         | s = a_NATIVEINT -> <:expr< $nativeint:s$ >>
690         | s = a_FLOAT -> <:expr< $flo:s$ >>
691         | s = a_STRING -> <:expr< $str:s$ >>
692         | s = a_CHAR -> <:expr< $chr:s$ >>
693         | i = val_longident -> <:expr< $id:i$ >>
694         | "`"; s = a_ident -> <:expr< ` $s$ >>
695         | "["; "]" -> <:expr< [] >>
696         | "["; mk_list = sem_expr_for_list; "::"; last = expr; "]" ->
697             mk_list last
698         | "["; mk_list = sem_expr_for_list; "]" ->
699             mk_list <:expr< [] >>
700         | "[|"; "|]" -> <:expr< [| $<:expr<>>$ |] >>
701         | "[|"; el = sem_expr; "|]" -> <:expr< [| $el$ |] >>
702         | "{"; el = label_expr_list; "}" -> <:expr< { $el$ } >>
703         | "{"; "("; e = SELF; ")"; "with"; el = label_expr_list; "}" ->
704             <:expr< { ($e$) with $el$ } >>
705         | "{<"; ">}" -> <:expr< {<>} >>
706         | "{<"; fel = field_expr_list; ">}" -> <:expr< {< $fel$ >} >>
707         | "("; ")" -> <:expr< () >>
708         | "("; e = SELF; ":"; t = ctyp; ")" -> <:expr< ($e$ : $t$) >>
709         | "("; e = SELF; ","; el = comma_expr; ")" -> <:expr< ( $e$, $el$ ) >>
710         | "("; e = SELF; ";"; seq = sequence; ")" -> mksequence _loc <:expr< $e$; $seq$ >>
711         | "("; e = SELF; ";"; ")" -> mksequence _loc e
712         | "("; e = SELF; ":"; t = ctyp; ":>"; t2 = ctyp; ")" ->
713             <:expr< ($e$ : $t$ :> $t2$ ) >>
714         | "("; e = SELF; ":>"; t = ctyp; ")" -> <:expr< ($e$ :> $t$) >>
715         | "("; e = SELF; ")" -> e
716         | "begin"; seq = sequence; "end" -> mksequence _loc seq
717         | "begin"; "end" -> <:expr< () >> ] ]
718     ;
719     do_sequence:
720       [ [ "{"; seq = sequence; "}" -> seq
721         | test_not_left_brace_nor_do; seq = sequence; "done" -> seq
722       ] ]
723     ;
724     infixop5:
725       [ [ x = [ "&" | "&&" ] -> <:expr< $lid:x$ >> ] ]
726     ;
727     infixop6:
728       [ [ x = [ "or" | "||" ] -> <:expr< $lid:x$ >> ] ]
729     ;
730     sem_expr_for_list:
731       [ [ e = expr; ";"; el = SELF -> fun acc -> <:expr< [ $e$ :: $el acc$ ] >>
732         | e = expr -> fun acc -> <:expr< [ $e$ :: $acc$ ] >>
733       ] ]
734     ;
735     comma_expr:
736       [ [ e1 = SELF; ","; e2 = SELF -> <:expr< $e1$, $e2$ >>
737         | `ANTIQUOT ("list" as n) s -> <:expr< $anti:mk_anti ~c:"expr," n s$ >>
738         | e = expr LEVEL "top" -> e ] ]
739     ;
740     dummy:
741       [ [ -> () ] ]
742     ;
743     sequence':
744       [ [ -> fun e -> e
745         | ";" -> fun e -> e
746         | ";"; el = sequence -> fun e -> <:expr< $e$; $el$ >> ] ]
747     ;
748     sequence:
749       [ [ "let"; rf = opt_rec; bi = binding; "in"; e = expr; k = sequence' ->
750             k <:expr< let $rec:rf$ $bi$ in $e$ >>
751         | "let"; rf = opt_rec; bi = binding; ";"; el = SELF ->
752             <:expr< let $rec:rf$ $bi$ in $mksequence _loc el$ >>
753         | "let"; "module"; m = a_UIDENT; mb = module_binding0; "in"; e = expr; k = sequence' ->
754             k <:expr< let module $m$ = $mb$ in $e$ >>
755         | "let"; "module"; m = a_UIDENT; mb = module_binding0; ";"; el = SELF ->
756             <:expr< let module $m$ = $mb$ in $mksequence _loc el$ >>
757         | `ANTIQUOT ("list" as n) s -> <:expr< $anti:mk_anti ~c:"expr;" n s$ >>
758         | e = expr; k = sequence' -> k e ] ]
759     ;
760     binding:
761       [ LEFTA
762         [ `ANTIQUOT ("binding"|"list" as n) s ->
763             <:binding< $anti:mk_anti ~c:"binding" n s$ >>
764         | `ANTIQUOT (""|"anti" as n) s; "="; e = expr ->
765             <:binding< $anti:mk_anti ~c:"patt" n s$ = $e$ >>
766         | `ANTIQUOT (""|"anti" as n) s -> <:binding< $anti:mk_anti ~c:"binding" n s$ >>
767         | b1 = SELF; "and"; b2 = SELF -> <:binding< $b1$ and $b2$ >>
768         | b = let_binding -> b
769       ] ]
770     ;
771     let_binding:
772       [ [ p = ipatt; e = fun_binding -> <:binding< $p$ = $e$ >> ] ]
773     ;
774     fun_binding:
775       [ RIGHTA
776         [ p = labeled_ipatt; e = SELF ->
777             <:expr< fun $p$ -> $e$ >>
778         | "="; e = expr -> <:expr< $e$ >>
779         | ":"; t = ctyp; "="; e = expr -> <:expr< ($e$ : $t$) >> 
780         | ":>"; t = ctyp; "="; e = expr -> <:expr< ($e$ :> $t$) >> ] ]
781     ;
782     match_case:
783       [ [ "["; l = LIST0 match_case0 SEP "|"; "]" -> Ast.mcOr_of_list l
784         | p = ipatt; "->"; e = expr -> <:match_case< $p$ -> $e$ >> ] ]
785     ;
786     match_case0:
787       [ [ `ANTIQUOT ("match_case"|"list" as n) s ->
788             <:match_case< $anti:mk_anti ~c:"match_case" n s$ >>
789         | `ANTIQUOT (""|"anti" as n) s ->
790             <:match_case< $anti:mk_anti ~c:"match_case" n s$ >>
791         | `ANTIQUOT (""|"anti" as n) s; "->"; e = expr ->
792             <:match_case< $anti:mk_anti ~c:"patt" n s$ -> $e$ >>
793         | `ANTIQUOT (""|"anti" as n) s; "when"; w = expr; "->"; e = expr ->
794             <:match_case< $anti:mk_anti ~c:"patt" n s$ when $w$ -> $e$ >>
795         | p = patt_as_patt_opt; w = opt_when_expr; "->"; e = expr -> <:match_case< $p$ when $w$ -> $e$ >>
796       ] ]
797     ;
798     opt_when_expr:
799       [ [ "when"; w = expr -> w
800         | -> <:expr<>>
801       ] ]
802     ;
803     patt_as_patt_opt:
804       [ [ p1 = patt; "as"; p2 = patt -> <:patt< ($p1$ as $p2$) >>
805         | p = patt -> p
806       ] ]
807     ;
808     label_expr_list:
809       [ [ b1 = label_expr; ";"; b2 = SELF -> <:rec_binding< $b1$ ; $b2$ >>
810         | b1 = label_expr; ";"            -> b1
811         | b1 = label_expr                 -> b1
812       ] ];
813     label_expr:
814       [ [ `ANTIQUOT ("rec_binding" as n) s ->
815             <:rec_binding< $anti:mk_anti ~c:"rec_binding" n s$ >>
816         | `ANTIQUOT (""|"anti" as n) s ->
817             <:rec_binding< $anti:mk_anti ~c:"rec_binding" n s$ >>
818         | `ANTIQUOT (""|"anti" as n) s; "="; e = expr ->
819             <:rec_binding< $anti:mk_anti ~c:"ident" n s$ = $e$ >>
820         | `ANTIQUOT ("list" as n) s ->
821             <:rec_binding< $anti:mk_anti ~c:"rec_binding" n s$ >>
822         | i = label_longident; e = fun_binding -> <:rec_binding< $i$ = $e$ >> ] ]
823     ;
824     fun_def:
825       [ [ p = labeled_ipatt; (w, e) = fun_def_cont ->
826             <:expr< fun [ $p$ when $w$ -> $e$ ] >> ] ]
827     ;
828     fun_def_cont:
829       [ RIGHTA
830         [ p = labeled_ipatt; (w,e) = SELF -> (<:expr<>>, <:expr< fun [ $p$ when $w$ -> $e$ ] >>)
831         | "when"; w = expr; "->"; e = expr -> (w, e)
832         | "->"; e = expr -> (<:expr<>>, e) ] ]
833     ;
834     patt:
835       [ "|" LEFTA
836         [ p1 = SELF; "|"; p2 = SELF -> <:patt< $p1$ | $p2$ >> ]
837       | ".." NONA
838         [ p1 = SELF; ".."; p2 = SELF -> <:patt< $p1$ .. $p2$ >> ]
839       | "apply" LEFTA
840         [ p1 = SELF; p2 = SELF -> <:patt< $p1$ $p2$ >>
841         | "lazy"; p = SELF -> <:patt< lazy $p$ >>  ]
842       | "simple"
843         [ `ANTIQUOT (""|"pat"|"anti" as n) s ->
844             <:patt< $anti:mk_anti ~c:"patt" n s$ >>
845         | `ANTIQUOT ("tup" as n) s -> <:patt< ($tup:<:patt< $anti:mk_anti ~c:"patt" n s$ >>$) >>
846         | `ANTIQUOT ("`bool" as n) s -> <:patt< $id:<:ident< $anti:mk_anti n s$ >>$ >>
847         | i = ident -> <:patt< $id:i$ >>
848         | s = a_INT -> <:patt< $int:s$ >>
849         | s = a_INT32 -> <:patt< $int32:s$ >>
850         | s = a_INT64 -> <:patt< $int64:s$ >>
851         | s = a_NATIVEINT -> <:patt< $nativeint:s$ >>
852         | s = a_FLOAT -> <:patt< $flo:s$ >>
853         | s = a_STRING -> <:patt< $str:s$ >>
854         | s = a_CHAR -> <:patt< $chr:s$ >>
855         | "-"; s = a_INT -> <:patt< $int:neg_string s$ >>
856         | "-"; s = a_INT32 -> <:patt< $int32:neg_string s$ >>
857         | "-"; s = a_INT64 -> <:patt< $int64:neg_string s$ >>
858         | "-"; s = a_NATIVEINT -> <:patt< $nativeint:neg_string s$ >>
859         | "-"; s = a_FLOAT -> <:patt< $flo:neg_string s$ >>
860         | "["; "]" -> <:patt< [] >>
861         | "["; mk_list = sem_patt_for_list; "::"; last = patt; "]" ->
862             mk_list last
863         | "["; mk_list = sem_patt_for_list; "]" ->
864             mk_list <:patt< [] >>
865         | "[|"; "|]" -> <:patt< [| $<:patt<>>$ |] >>
866         | "[|"; pl = sem_patt; "|]" -> <:patt< [| $pl$ |] >>
867         | "{"; pl = label_patt_list; "}" -> <:patt< { $pl$ } >>
868         | "("; ")" -> <:patt< () >>
869         | "("; p = SELF; ")" -> p
870         | "("; p = SELF; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >>
871         | "("; p = SELF; "as"; p2 = SELF; ")" -> <:patt< ($p$ as $p2$) >>
872         | "("; p = SELF; ","; pl = comma_patt; ")" -> <:patt< ($p$, $pl$) >>
873         | "_" -> <:patt< _ >>
874         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.patt_tag
875         | "`"; s = a_ident -> <:patt< ` $s$ >>
876         | "#"; i = type_longident -> <:patt< # $i$ >>
877         | `LABEL i; p = SELF -> <:patt< ~ $i$ : $p$ >>
878         | "~"; `ANTIQUOT (""|"lid" as n) i; ":"; p = SELF ->
879             <:patt< ~ $mk_anti n i$ : $p$ >>
880         | "~"; `ANTIQUOT (""|"lid" as n) i -> <:patt< ~ $mk_anti n i$ >>
881         | "~"; `LIDENT i -> <:patt< ~ $i$ >>
882         (* | i = opt_label; "("; p = patt_tcon; ")" -> *)
883             (* <:patt< ? $i$ : ($p$) >> *)
884         | `OPTLABEL i; "("; p = patt_tcon; f = eq_expr; ")" -> f i p
885         | "?"; `ANTIQUOT (""|"lid" as n) i; ":"; "("; p = patt_tcon; f = eq_expr; ")" ->
886             f (mk_anti n i) p
887         | "?"; `LIDENT i -> <:patt< ? $i$ >>
888         | "?"; `ANTIQUOT (""|"lid" as n) i -> <:patt< ? $mk_anti n i$ >>
889         | "?"; "("; p = patt_tcon; ")" ->
890             <:patt< ? ($p$) >>
891         | "?"; "("; p = patt_tcon; "="; e = expr; ")" ->
892             <:patt< ? ($p$ = $e$) >> ] ]
893     ;
894     comma_patt:
895       [ [ p1 = SELF; ","; p2 = SELF -> <:patt< $p1$, $p2$ >>
896         | `ANTIQUOT ("list" as n) s -> <:patt< $anti:mk_anti ~c:"patt," n s$ >>
897         | p = patt -> p ] ]
898     ;
899     sem_patt:
900       [ LEFTA
901         [ p1 = SELF; ";"; p2 = SELF -> <:patt< $p1$; $p2$ >>
902         | `ANTIQUOT ("list" as n) s -> <:patt< $anti:mk_anti ~c:"patt;" n s$ >>
903         | p = patt -> p ] ]
904     ;
905     sem_patt_for_list:
906       [ [ p = patt; ";"; pl = SELF -> fun acc -> <:patt< [ $p$ :: $pl acc$ ] >>
907         | p = patt -> fun acc -> <:patt< [ $p$ :: $acc$ ] >>
908       ] ]
909     ;
910     label_patt_list:
911       [ [ p1 = label_patt; ";"; p2 = SELF -> <:patt< $p1$ ; $p2$ >>
912         | p1 = label_patt; ";"            -> p1
913         | p1 = label_patt                 -> p1
914       ] ];
915     label_patt:
916       [ [ `ANTIQUOT (""|"pat"|"anti" as n) s ->
917             <:patt< $anti:mk_anti ~c:"patt" n s$ >>
918         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.patt_tag
919         | `ANTIQUOT ("list" as n) s ->
920             <:patt< $anti:mk_anti ~c:"patt;" n s$ >>
921         | i = label_longident; "="; p = patt -> <:patt< $i$ = $p$ >>
922       ] ]
923     ;
924     ipatt:
925       [ [ "{"; pl = label_ipatt_list; "}" -> <:patt< { $pl$ } >>
926         | `ANTIQUOT (""|"pat"|"anti" as n) s ->
927             <:patt< $anti:mk_anti ~c:"patt" n s$ >>
928         | `ANTIQUOT ("tup" as n) s ->
929             <:patt< ($tup:<:patt< $anti:mk_anti ~c:"patt" n s$ >>$) >>
930         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.patt_tag
931         | "("; ")" -> <:patt< () >>
932         | "("; p = SELF; ")" -> p
933         | "("; p = SELF; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >>
934         | "("; p = SELF; "as"; p2 = SELF; ")" -> <:patt< ($p$ as $p2$) >>
935         | "("; p = SELF; ","; pl = comma_ipatt; ")" -> <:patt< ($p$, $pl$) >>
936         | s = a_LIDENT -> <:patt< $lid:s$ >>
937         | "_" -> <:patt< _ >> ] ]
938     ;
939     labeled_ipatt:
940       [ [ p = ipatt -> p ] ]
941     ;
942     comma_ipatt:
943       [ LEFTA
944         [ p1 = SELF; ","; p2 = SELF -> <:patt< $p1$, $p2$ >>
945         | `ANTIQUOT ("list" as n) s -> <:patt< $anti:mk_anti ~c:"patt," n s$ >>
946         | p = ipatt -> p ] ]
947     ;
948     label_ipatt_list:
949       [ [ p1 = label_ipatt; ";"; p2 = SELF -> <:patt< $p1$ ; $p2$ >>
950         | p1 = label_ipatt; ";"            -> p1
951         | p1 = label_ipatt                 -> p1
952       ] ];
953     label_ipatt:
954       [ [ `ANTIQUOT (""|"pat"|"anti" as n) s ->
955             <:patt< $anti:mk_anti ~c:"patt" n s$ >>
956         | `ANTIQUOT ("list" as n) s -> <:patt< $anti:mk_anti ~c:"patt;" n s$ >>
957         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.patt_tag
958         | i = label_longident; "="; p = ipatt -> <:patt< $i$ = $p$ >>
959       ] ]
960     ;
961     type_declaration:
962       [ LEFTA
963         [ `ANTIQUOT (""|"typ"|"anti" as n) s ->
964             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
965         | `ANTIQUOT ("list" as n) s ->
966             <:ctyp< $anti:mk_anti ~c:"ctypand" n s$ >>
967         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
968         | t1 = SELF; "and"; t2 = SELF -> <:ctyp< $t1$ and $t2$ >>
969         | (n, tpl) = type_ident_and_parameters; tk = opt_eq_ctyp;
970           cl = LIST0 constrain -> Ast.TyDcl _loc n tpl tk cl ] ]
971     ;
972     constrain:
973       [ [ "constraint"; t1 = ctyp; "="; t2 = ctyp -> (t1, t2) ] ]
974     ;
975     opt_eq_ctyp:
976       [ [ "="; tk = type_kind -> tk
977         | -> <:ctyp<>> ] ]
978     ;
979     type_kind:
980       [ [ t = ctyp -> t ] ]
981     ;
982     type_ident_and_parameters:
983       [ [ i = a_LIDENT; tpl = LIST0 type_parameter -> (i, tpl) ] ]
984     ;
985     type_longident_and_parameters:
986       [ [ i = type_longident; tpl = type_parameters -> tpl <:ctyp< $id:i$ >>
987       ] ]
988     ;
989     type_parameters:
990       [ [ t1 = type_parameter; t2 = SELF ->
991             fun acc -> t2 <:ctyp< $acc$ $t1$ >>
992         | t = type_parameter -> fun acc -> <:ctyp< $acc$ $t$ >>
993         | -> fun t -> t
994       ] ]
995     ;
996     type_parameter:
997       [ [ `ANTIQUOT (""|"typ"|"anti" as n) s -> <:ctyp< $anti:mk_anti n s$ >>
998         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
999         | "'"; i = a_ident -> <:ctyp< '$lid:i$ >>
1000         | "+"; "'"; i = a_ident -> <:ctyp< +'$lid:i$ >>
1001         | "-"; "'"; i = a_ident -> <:ctyp< -'$lid:i$ >> ] ]
1002     ;
1003     ctyp:
1004       [ "==" LEFTA
1005         [ t1 = SELF; "=="; t2 = SELF -> <:ctyp< $t1$ == $t2$ >> ]
1006       | "private" NONA
1007         [ "private"; t = ctyp LEVEL "alias" -> <:ctyp< private $t$ >> ]
1008       | "alias" LEFTA
1009         [ t1 = SELF; "as"; t2 = SELF -> <:ctyp< $t1$ as $t2$ >> ]
1010       | "forall" LEFTA
1011         [ "!"; t1 = typevars; "."; t2 = ctyp -> <:ctyp< ! $t1$ . $t2$ >> ]
1012       | "arrow" RIGHTA
1013         [ t1 = SELF; "->"; t2 = SELF -> <:ctyp< $t1$ -> $t2$ >> ]
1014       | "label" NONA
1015         [ "~"; i = a_LIDENT; ":"; t = SELF -> <:ctyp< ~ $i$ : $t$ >>
1016         | i = a_LABEL; t =  SELF  -> <:ctyp< ~ $i$ : $t$ >>
1017         | "?"; i = a_LIDENT; ":"; t = SELF -> <:ctyp< ? $i$ : $t$ >>
1018         | i = a_OPTLABEL; t = SELF -> <:ctyp< ? $i$ : $t$ >> ]
1019       | "apply" LEFTA
1020         [ t1 = SELF; t2 = SELF ->
1021             let t = <:ctyp< $t1$ $t2$ >> in
1022             try <:ctyp< $id:Ast.ident_of_ctyp t$ >>
1023             with [ Invalid_argument _ -> t ] ]
1024       | "." LEFTA
1025         [ t1 = SELF; "."; t2 = SELF ->
1026             try <:ctyp< $id:Ast.ident_of_ctyp t1$.$id:Ast.ident_of_ctyp t2$ >>
1027             with [ Invalid_argument s -> raise (Stream.Error s) ] ]
1028       | "simple"
1029         [ "'"; i = a_ident -> <:ctyp< '$i$ >>
1030         | "_" -> <:ctyp< _ >>
1031         | `ANTIQUOT (""|"typ"|"anti" as n) s ->
1032             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1033         | `ANTIQUOT ("tup" as n) s ->
1034             <:ctyp< ($tup:<:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>$) >>
1035         | `ANTIQUOT ("id" as n) s ->
1036             <:ctyp< $id:<:ident< $anti:mk_anti ~c:"ident" n s$ >>$ >>
1037         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1038         | i = a_LIDENT -> <:ctyp< $lid:i$ >>
1039         | i = a_UIDENT -> <:ctyp< $uid:i$ >>
1040         | "("; t = SELF; "*"; tl = star_ctyp; ")" ->
1041             <:ctyp< ( $t$ * $tl$ ) >>
1042         | "("; t = SELF; ")" -> t
1043         | "["; "]" -> <:ctyp< [ ] >>
1044         | "["; t = constructor_declarations; "]" -> <:ctyp< [ $t$ ] >>
1045         | "["; "="; rfl = row_field; "]" ->
1046             <:ctyp< [ = $rfl$ ] >>
1047         | "["; ">"; "]" -> <:ctyp< [ > $<:ctyp<>>$ ] >>
1048         | "["; ">"; rfl = row_field; "]" ->
1049             <:ctyp< [ > $rfl$ ] >>
1050         | "["; "<"; rfl = row_field; "]" ->
1051             <:ctyp< [ < $rfl$ ] >>
1052         | "["; "<"; rfl = row_field; ">"; ntl = name_tags; "]" ->
1053             <:ctyp< [ < $rfl$ > $ntl$ ] >>
1054         | "[<"; rfl = row_field; "]" ->
1055             <:ctyp< [ < $rfl$ ] >>
1056         | "[<"; rfl = row_field; ">"; ntl = name_tags; "]" ->
1057             <:ctyp< [ < $rfl$ > $ntl$ ] >>
1058         | "{"; t = label_declaration_list; "}" -> <:ctyp< { $t$ } >>
1059         | "#"; i = class_longident -> <:ctyp< # $i$ >>
1060         | "<"; t = opt_meth_list; ">" -> t
1061       ] ]
1062     ;
1063     star_ctyp:
1064       [ [ `ANTIQUOT (""|"typ" as n) s ->
1065             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1066         | `ANTIQUOT ("list" as n) s ->
1067             <:ctyp< $anti:mk_anti ~c:"ctyp*" n s$ >>
1068         | t1 = SELF; "*"; t2 = SELF ->
1069             <:ctyp< $t1$ * $t2$ >>
1070         | t = ctyp -> t
1071       ] ]
1072     ;
1073     constructor_declarations:
1074       [ [ `ANTIQUOT (""|"typ" as n) s ->
1075             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1076         | `ANTIQUOT ("list" as n) s ->
1077             <:ctyp< $anti:mk_anti ~c:"ctyp|" n s$ >>
1078         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1079         | t1 = SELF; "|"; t2 = SELF ->
1080             <:ctyp< $t1$ | $t2$ >>
1081         | s = a_UIDENT; "of"; t = constructor_arg_list ->
1082             <:ctyp< $uid:s$ of $t$ >>
1083         | s = a_UIDENT ->
1084             <:ctyp< $uid:s$ >>
1085       ] ]
1086     ;
1087     constructor_declaration:
1088       [ [ `ANTIQUOT (""|"typ" as n) s ->
1089             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1090         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1091         | s = a_UIDENT; "of"; t = constructor_arg_list ->
1092             <:ctyp< $uid:s$ of $t$ >>
1093         | s = a_UIDENT ->
1094             <:ctyp< $uid:s$ >>
1095       ] ]
1096     ;
1097     constructor_arg_list:
1098       [ [ `ANTIQUOT ("list" as n) s ->
1099             <:ctyp< $anti:mk_anti ~c:"ctypand" n s$ >>
1100         | t1 = SELF; "and"; t2 = SELF -> <:ctyp< $t1$ and $t2$ >>
1101         | t = ctyp -> t
1102       ] ]
1103     ;
1104     label_declaration_list:
1105       [ [ t1 = label_declaration; ";"; t2 = SELF -> <:ctyp< $t1$; $t2$ >>
1106         | t1 = label_declaration; ";"            -> t1
1107         | t1 = label_declaration                 -> t1
1108       ] ]
1109     ;
1110     label_declaration:
1111       [ [ `ANTIQUOT (""|"typ" as n) s ->
1112             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1113         | `ANTIQUOT ("list" as n) s ->
1114             <:ctyp< $anti:mk_anti ~c:"ctyp;" n s$ >>
1115         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1116         | s = a_LIDENT; ":"; t = poly_type ->  <:ctyp< $lid:s$ : $t$ >>
1117         | s = a_LIDENT; ":"; "mutable"; t = poly_type ->
1118             <:ctyp< $lid:s$ : mutable $t$ >>
1119       ] ]
1120     ;
1121     a_ident:
1122       [ [ i = a_LIDENT -> i
1123         | i = a_UIDENT -> i ] ]
1124     ;
1125     ident:
1126       [ [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1127             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1128         | i = a_UIDENT -> <:ident< $uid:i$ >>
1129         | i = a_LIDENT -> <:ident< $lid:i$ >>
1130         | `ANTIQUOT (""|"id"|"anti"|"list" as n) s; "."; i = SELF ->
1131             <:ident< $anti:mk_anti ~c:"ident" n s$.$i$ >>
1132         | i = a_UIDENT; "."; j = SELF -> <:ident< $uid:i$.$j$ >> ] ]
1133     ;
1134     module_longident:
1135       [ [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1136             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1137         | m = a_UIDENT; "."; l = SELF -> <:ident< $uid:m$.$l$ >>
1138         | i = a_UIDENT -> <:ident< $uid:i$ >> ] ]
1139     ;
1140     module_longident_with_app:
1141       [ "apply"
1142         [ i = SELF; j = SELF -> <:ident< $i$ $j$ >> ]
1143       | "."
1144         [ i = SELF; "."; j = SELF -> <:ident< $i$.$j$ >> ]
1145       | "simple"
1146         [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1147             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1148         | i = a_UIDENT -> <:ident< $uid:i$ >>
1149         | "("; i = SELF; ")" -> i ] ]
1150     ;
1151     type_longident:
1152       [ "apply"
1153         [ i = SELF; j = SELF -> <:ident< $i$ $j$ >> ]
1154       | "."
1155         [ i = SELF; "."; j = SELF -> <:ident< $i$.$j$ >> ]
1156       | "simple"
1157         [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1158             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1159         | i = a_LIDENT -> <:ident< $lid:i$ >>
1160         | i = a_UIDENT -> <:ident< $uid:i$ >>
1161         | "("; i = SELF; ")" -> i ] ]
1162     ;
1163     label_longident:
1164       [ [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1165             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1166         | m = a_UIDENT; "."; l = SELF -> <:ident< $uid:m$.$l$ >>
1167         | i = a_LIDENT -> <:ident< $lid:i$ >> ] ]
1168     ;
1169     class_type_longident:
1170       [ [ x = type_longident -> x ] ]
1171     ;
1172     val_longident:
1173       [ [ x = ident -> x ] ]
1174     ;
1175     class_longident:
1176       [ [ x = label_longident -> x ] ]
1177     ;
1178     class_declaration:
1179       [ LEFTA
1180         [ c1 = SELF; "and"; c2 = SELF ->
1181             <:class_expr< $c1$ and $c2$ >>
1182         | `ANTIQUOT (""|"cdcl"|"anti"|"list" as n) s ->
1183             <:class_expr< $anti:mk_anti ~c:"class_expr" n s$ >>
1184         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_expr_tag
1185         | ci = class_info_for_class_expr; ce = class_fun_binding ->
1186             <:class_expr< $ci$ = $ce$ >>
1187       ] ]
1188     ;
1189     class_fun_binding:
1190       [ [ "="; ce = class_expr -> ce
1191         | ":"; ct = class_type_plus; "="; ce = class_expr ->
1192             <:class_expr< ($ce$ : $ct$) >>
1193         | p = labeled_ipatt; cfb = SELF ->
1194             <:class_expr< fun $p$ -> $cfb$ >>
1195       ] ]
1196     ;
1197     class_info_for_class_type:
1198       [ [ mv = opt_virtual; (i, ot) = class_name_and_param ->
1199             <:class_type< $virtual:mv$ $lid:i$ [ $ot$ ] >>
1200       ] ]
1201     ;
1202     class_info_for_class_expr:
1203       [ [ mv = opt_virtual; (i, ot) = class_name_and_param ->
1204             <:class_expr< $virtual:mv$ $lid:i$ [ $ot$ ] >>
1205       ] ]
1206     ;
1207     class_name_and_param:
1208       [ [ i = a_LIDENT; "["; x = comma_type_parameter; "]" -> (i, x)
1209         | i = a_LIDENT -> (i, <:ctyp<>>)
1210       ] ]
1211     ;
1212     comma_type_parameter:
1213       [ [ t1 = SELF; ","; t2 = SELF -> <:ctyp< $t1$, $t2$ >>
1214         | `ANTIQUOT ("list" as n) s -> <:ctyp< $anti:mk_anti ~c:"ctyp," n s$ >>
1215         | t = type_parameter -> t
1216       ] ]
1217     ;
1218     opt_comma_ctyp:
1219       [ [ "["; x = comma_ctyp; "]" -> x
1220         | -> <:ctyp<>>
1221       ] ]
1222     ;
1223     comma_ctyp:
1224       [ [ t1 = SELF; ","; t2 = SELF -> <:ctyp< $t1$, $t2$ >>
1225         | `ANTIQUOT ("list" as n) s -> <:ctyp< $anti:mk_anti ~c:"ctyp," n s$ >>
1226         | t = ctyp -> t
1227       ] ]
1228     ;
1229     class_fun_def:
1230       [ [ p = labeled_ipatt; ce = SELF -> <:class_expr< fun $p$ -> $ce$ >>
1231         | "->"; ce = class_expr -> ce ] ]
1232     ;
1233     class_expr:
1234       [ "top"
1235         [ "fun"; p = labeled_ipatt; ce = class_fun_def ->
1236             <:class_expr< fun $p$ -> $ce$ >>
1237         | "let"; rf = opt_rec; bi = binding; "in"; ce = SELF ->
1238             <:class_expr< let $rec:rf$ $bi$ in $ce$ >> ]
1239       | "apply" NONA
1240         [ ce = SELF; e = expr LEVEL "label" ->
1241             <:class_expr< $ce$ $e$ >> ]
1242       | "simple"
1243         [ `ANTIQUOT (""|"cexp"|"anti" as n) s ->
1244             <:class_expr< $anti:mk_anti ~c:"class_expr" n s$ >>
1245         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_expr_tag
1246         | ce = class_longident_and_param -> ce
1247         | "object"; csp = opt_class_self_patt; cst = class_structure; "end" ->
1248             <:class_expr< object ($csp$) $cst$ end >>
1249         | "("; ce = SELF; ":"; ct = class_type; ")" ->
1250             <:class_expr< ($ce$ : $ct$) >>
1251         | "("; ce = SELF; ")" -> ce ] ]
1252     ;
1253     class_longident_and_param:
1254       [ [ ci = class_longident; "["; t = comma_ctyp; "]" ->
1255           <:class_expr< $id:ci$ [ $t$ ] >>
1256         | ci = class_longident -> <:class_expr< $id:ci$ >>
1257       ] ]
1258     ;
1259     class_structure:
1260       [ [ `ANTIQUOT (""|"cst"|"anti"|"list" as n) s ->
1261             <:class_str_item< $anti:mk_anti ~c:"class_str_item" n s$ >>
1262         | `ANTIQUOT (""|"cst"|"anti"|"list" as n) s; semi; cst = SELF ->
1263             <:class_str_item< $anti:mk_anti ~c:"class_str_item" n s$; $cst$ >>
1264         | l = LIST0 [ cst = class_str_item; semi -> cst ] -> Ast.crSem_of_list l
1265       ] ]
1266     ;
1267     opt_class_self_patt:
1268       [ [ "("; p = patt; ")" -> p
1269         | "("; p = patt; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >>
1270         | -> <:patt<>> ] ]
1271     ;
1272     class_str_item:
1273       [ LEFTA
1274         [ `ANTIQUOT (""|"cst"|"anti"|"list" as n) s ->
1275             <:class_str_item< $anti:mk_anti ~c:"class_str_item" n s$ >>
1276         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_str_item_tag
1277         | "inherit"; ce = class_expr; pb = opt_as_lident ->
1278             <:class_str_item< inherit $ce$ as $pb$ >>
1279         | value_val; mf = opt_mutable; lab = label; e = cvalue_binding ->
1280             <:class_str_item< value $mutable:mf$ $lab$ = $e$ >>
1281         | value_val; mf = opt_mutable; "virtual"; l = label; ":"; t = poly_type ->
1282             <:class_str_item< value virtual $mutable:mf$ $l$ : $t$ >>
1283         | value_val; "virtual"; mf = opt_mutable; l = label; ":"; t = poly_type ->
1284             <:class_str_item< value virtual $mutable:mf$ $l$ : $t$ >>
1285         | "method"; "virtual"; pf = opt_private; l = label; ":"; t = poly_type ->
1286             <:class_str_item< method virtual $private:pf$ $l$ : $t$ >>
1287         | "method"; pf = opt_private; "virtual"; l = label; ":"; t = poly_type ->
1288             <:class_str_item< method virtual $private:pf$ $l$ : $t$ >>
1289         | "method"; pf = opt_private; l = label; topt = opt_polyt;
1290           e = fun_binding ->
1291             <:class_str_item< method $private:pf$ $l$ : $topt$ = $e$ >>
1292         | type_constraint; t1 = ctyp; "="; t2 = ctyp ->
1293             <:class_str_item< type $t1$ = $t2$ >>
1294         | "initializer"; se = expr -> <:class_str_item< initializer $se$ >> ] ]
1295     ;
1296     opt_as_lident:
1297       [ [ "as"; i = a_LIDENT -> i
1298         | -> ""
1299       ] ]
1300     ;
1301     opt_polyt:
1302       [ [ ":"; t = poly_type -> t
1303         | -> <:ctyp<>> ] ]
1304     ;
1305     cvalue_binding:
1306       [ [ "="; e = expr -> e
1307         | ":"; t = ctyp; "="; e = expr -> <:expr< ($e$ : $t$) >>
1308         | ":"; t = ctyp; ":>"; t2 = ctyp; "="; e = expr ->
1309             <:expr< ($e$ : $t$ :> $t2$) >>
1310         | ":>"; t = ctyp; "="; e = expr -> <:expr< ($e$ :> $t$) >> ] ]
1311     ;
1312     label:
1313       [ [ i = a_LIDENT -> i ] ]
1314     ;
1315     class_type:
1316       [ [ `ANTIQUOT (""|"ctyp"|"anti" as n) s ->
1317             <:class_type< $anti:mk_anti ~c:"class_type" n s$ >>
1318         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_type_tag
1319         | ct = class_type_longident_and_param -> ct
1320         | "object"; cst = opt_class_self_type; csg = class_signature; "end" ->
1321             <:class_type< object ($cst$) $csg$ end >> ] ]
1322     ;
1323     class_type_longident_and_param:
1324       [ [ i = class_type_longident; "["; t = comma_ctyp; "]" ->
1325             <:class_type< $id:i$ [ $t$ ] >>
1326         | i = class_type_longident -> <:class_type< $id:i$ >> ] ]
1327     ;
1328     class_type_plus:
1329       [ [ "["; t = ctyp; "]"; "->"; ct = SELF -> <:class_type< [ $t$ ] -> $ct$ >>
1330         | ct = class_type -> ct ] ]
1331     ;
1332     opt_class_self_type:
1333       [ [ "("; t = ctyp; ")" -> t
1334         | -> <:ctyp<>> ] ]
1335     ;
1336     class_signature:
1337       [ [ `ANTIQUOT (""|"csg"|"anti"|"list" as n) s ->
1338             <:class_sig_item< $anti:mk_anti ~c:"class_sig_item" n s$ >>
1339         | `ANTIQUOT (""|"csg"|"anti"|"list" as n) s; semi; csg = SELF ->
1340             <:class_sig_item< $anti:mk_anti ~c:"class_sig_item" n s$; $csg$ >>
1341         | l = LIST0 [ csg = class_sig_item; semi -> csg ] -> Ast.cgSem_of_list l
1342       ] ]
1343     ;
1344     class_sig_item:
1345       [ [ `ANTIQUOT (""|"csg"|"anti"|"list" as n) s ->
1346             <:class_sig_item< $anti:mk_anti ~c:"class_sig_item" n s$ >>
1347         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_sig_item_tag
1348         | "inherit"; cs = class_type -> <:class_sig_item< inherit $cs$ >>
1349         | value_val; mf = opt_mutable; mv = opt_virtual;
1350           l = label; ":"; t = ctyp ->
1351             <:class_sig_item< value $mutable:mf$ $virtual:mv$ $l$ : $t$ >>
1352         | "method"; "virtual"; pf = opt_private; l = label; ":"; t = poly_type ->
1353             <:class_sig_item< method virtual $private:pf$ $l$ : $t$ >>
1354         | "method"; pf = opt_private; l = label; ":"; t = poly_type ->
1355             <:class_sig_item< method $private:pf$ $l$ : $t$ >>
1356         | "method"; pf = opt_private; "virtual"; l = label; ":"; t = poly_type ->
1357             <:class_sig_item< method virtual $private:pf$ $l$ : $t$ >>
1358         | type_constraint; t1 = ctyp; "="; t2 = ctyp ->
1359             <:class_sig_item< type $t1$ = $t2$ >> ] ]
1360     ;
1361     type_constraint:
1362       [ [ "type" | "constraint" -> () ] ]
1363     ;
1364     class_description:
1365       [ [ cd1 = SELF; "and"; cd2 = SELF -> <:class_type< $cd1$ and $cd2$ >>
1366         | `ANTIQUOT (""|"typ"|"anti"|"list" as n) s ->
1367             <:class_type< $anti:mk_anti ~c:"class_type" n s$ >>
1368         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_type_tag
1369         | ci = class_info_for_class_type; ":"; ct = class_type_plus -> <:class_type< $ci$ : $ct$ >>
1370       ] ]
1371     ;
1372     class_type_declaration:
1373       [ LEFTA
1374         [ cd1 = SELF; "and"; cd2 = SELF -> <:class_type< $cd1$ and $cd2$ >>
1375         | `ANTIQUOT (""|"typ"|"anti"|"list" as n) s ->
1376             <:class_type< $anti:mk_anti ~c:"class_type" n s$ >>
1377         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.class_type_tag
1378         | ci = class_info_for_class_type; "="; ct = class_type -> <:class_type< $ci$ = $ct$ >>
1379       ] ]
1380     ;
1381     field_expr_list:
1382       [ [ b1 = field_expr; ";"; b2 = SELF -> <:rec_binding< $b1$ ; $b2$ >>
1383         | b1 = field_expr; ";"            -> b1
1384         | b1 = field_expr                 -> b1
1385       ] ];
1386     field_expr:
1387       [ [ `ANTIQUOT (""|"bi"|"anti" as n) s ->
1388             <:rec_binding< $anti:mk_anti ~c:"rec_binding" n s$ >>
1389         | `ANTIQUOT ("list" as n) s ->
1390             <:rec_binding< $anti:mk_anti ~c:"rec_binding" n s$ >>
1391         | l = label; "="; e = expr -> <:rec_binding< $lid:l$ = $e$ >> ] ]
1392     ;
1393     meth_list:
1394       [ [ m = meth_decl; ";"; (ml, v) = SELF  -> (<:ctyp< $m$; $ml$ >>, v)
1395         | m = meth_decl; ";"; v = opt_dot_dot -> (m, v)
1396         | m = meth_decl; v = opt_dot_dot      -> (m, v)
1397       ] ]
1398     ;
1399     meth_decl:
1400       [ [ `ANTIQUOT (""|"typ" as n) s        -> <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1401         | `ANTIQUOT ("list" as n) s          -> <:ctyp< $anti:mk_anti ~c:"ctyp;" n s$ >>
1402         | `QUOTATION x                       -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1403         | lab = a_LIDENT; ":"; t = poly_type -> <:ctyp< $lid:lab$ : $t$ >> ] ]
1404     ;
1405     opt_meth_list:
1406       [ [ (ml, v) = meth_list -> <:ctyp< < $ml$ $..:v$ > >>
1407         | v = opt_dot_dot     -> <:ctyp< < $..:v$ > >>
1408       ] ]
1409     ;
1410     poly_type:
1411       [ [ t = ctyp -> t ] ]
1412     ;
1413     typevars:
1414       [ LEFTA
1415         [ t1 = SELF; t2 = SELF -> <:ctyp< $t1$ $t2$ >>
1416         | `ANTIQUOT (""|"typ" as n) s ->
1417             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1418         | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
1419         | "'"; i = a_ident -> <:ctyp< '$lid:i$ >>
1420       ] ]
1421     ;
1422     row_field:
1423       [ [ `ANTIQUOT (""|"typ" as n) s ->
1424             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1425         | `ANTIQUOT ("list" as n) s ->
1426             <:ctyp< $anti:mk_anti ~c:"ctyp|" n s$ >>
1427         | t1 = SELF; "|"; t2 = SELF -> <:ctyp< $t1$ | $t2$ >>
1428         | "`"; i = a_ident -> <:ctyp< `$i$ >>
1429         | "`"; i = a_ident; "of"; "&"; t = amp_ctyp -> <:ctyp< `$i$ of & $t$ >>
1430         | "`"; i = a_ident; "of"; t = amp_ctyp -> <:ctyp< `$i$ of $t$ >>
1431         | t = ctyp -> t ] ]
1432     ;
1433     amp_ctyp:
1434       [ [ t1 = SELF; "&"; t2 = SELF -> <:ctyp< $t1$ & $t2$ >>
1435         | `ANTIQUOT ("list" as n) s -> <:ctyp< $anti:mk_anti ~c:"ctyp&" n s$ >>
1436         | t = ctyp -> t
1437       ] ]
1438     ;
1439     name_tags:
1440       [ [ `ANTIQUOT (""|"typ" as n) s ->
1441             <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
1442         | t1 = SELF; t2 = SELF -> <:ctyp< $t1$ $t2$ >>
1443         | "`"; i = a_ident -> <:ctyp< `$i$ >>
1444       ] ]
1445     ;
1446     eq_expr:
1447       [ [ "="; e = expr -> fun i p -> <:patt< ? $i$ : ($p$ = $e$) >>
1448         | -> fun i p -> <:patt< ? $i$ : ($p$) >> ] ]
1449     ;
1450     patt_tcon:
1451       [ [ p = patt; ":"; t = ctyp -> <:patt< ($p$ : $t$) >>
1452         | p = patt -> p ] ]
1453     ;
1454     ipatt:
1455       [ [ `LABEL i; p = SELF -> <:patt< ~ $i$ : $p$ >>
1456         | "~"; `ANTIQUOT (""|"lid" as n) i; ":"; p = SELF ->
1457             <:patt< ~ $mk_anti n i$ : $p$ >>
1458         | "~"; `ANTIQUOT (""|"lid" as n) i -> <:patt< ~ $mk_anti n i$ >>
1459         | "~"; `LIDENT i -> <:patt< ~ $i$ >>
1460         (* | i = opt_label; "("; p = ipatt_tcon; ")" ->
1461             <:patt< ? $i$ : ($p$) >>
1462         | i = opt_label; "("; p = ipatt_tcon; "="; e = expr; ")" ->
1463             <:patt< ? $i$ : ($p$ = $e$) >>                             *)
1464         | `OPTLABEL i; "("; p = ipatt_tcon; f = eq_expr; ")" -> f i p
1465         | "?"; `ANTIQUOT (""|"lid" as n) i; ":"; "("; p = ipatt_tcon;
1466           f = eq_expr; ")" -> f (mk_anti n i) p
1467         | "?"; `LIDENT i -> <:patt< ? $i$ >>
1468         | "?"; `ANTIQUOT (""|"lid" as n) i -> <:patt< ? $mk_anti n i$ >>
1469         | "?"; "("; p = ipatt_tcon; ")" ->
1470             <:patt< ? ($p$) >>
1471         | "?"; "("; p = ipatt_tcon; "="; e = expr; ")" ->
1472             <:patt< ? ($p$ = $e$) >> ] ]
1473     ;
1474     ipatt_tcon:
1475       [ [ p = ipatt; ":"; t = ctyp -> <:patt< ($p$ : $t$) >>
1476         | p = ipatt -> p ] ]
1477     ;
1478     direction_flag:
1479       [ [ "to" -> Ast.BTrue
1480         | "downto" -> Ast.BFalse
1481         | `ANTIQUOT ("to" as n) s -> Ast.BAnt (mk_anti n s) ] ]
1482     ;
1483     opt_private:
1484       [ [ "private" -> Ast.BTrue
1485         | `ANTIQUOT ("private" as n) s -> Ast.BAnt (mk_anti n s)
1486         | -> Ast.BFalse
1487       ] ]
1488     ;
1489     opt_mutable:
1490       [ [ "mutable" -> Ast.BTrue
1491         | `ANTIQUOT ("mutable" as n) s -> Ast.BAnt (mk_anti n s)
1492         | -> Ast.BFalse
1493       ] ]
1494     ;
1495     opt_virtual:
1496       [ [ "virtual" -> Ast.BTrue
1497         | `ANTIQUOT ("virtual" as n) s -> Ast.BAnt (mk_anti n s)
1498         | -> Ast.BFalse
1499       ] ]
1500     ;
1501     opt_dot_dot:
1502       [ [ ".." -> Ast.BTrue
1503         | `ANTIQUOT (".." as n) s -> Ast.BAnt (mk_anti n s)
1504         | -> Ast.BFalse
1505       ] ]
1506     ;
1507     opt_rec:
1508       [ [ "rec" -> Ast.BTrue
1509         | `ANTIQUOT ("rec" as n) s -> Ast.BAnt (mk_anti n s)
1510         | -> Ast.BFalse
1511       ] ]
1512     ;
1513     opt_expr:
1514       [ [ e = expr -> e
1515         | -> <:expr<>>
1516       ] ]
1517     ;
1518     interf:
1519       [ [ "#"; n = a_LIDENT; dp = opt_expr; semi ->
1520             ([ <:sig_item< # $n$ $dp$ >> ], stopped_at _loc)
1521         | si = sig_item; semi; (sil, stopped) = SELF -> ([si :: sil], stopped)
1522         | `EOI -> ([], None) ] ]
1523     ;
1524     sig_items:
1525       [ [ `ANTIQUOT (""|"sigi"|"anti"|"list" as n) s ->
1526             <:sig_item< $anti:mk_anti n ~c:"sig_item" s$ >>
1527         | `ANTIQUOT (""|"sigi"|"anti"|"list" as n) s; semi; sg = SELF ->
1528             <:sig_item< $anti:mk_anti n ~c:"sig_item" s$; $sg$ >>
1529         | l = LIST0 [ sg = sig_item; semi -> sg ] -> Ast.sgSem_of_list l
1530       ] ]
1531     ;
1532     implem:
1533       [ [ "#"; n = a_LIDENT; dp = opt_expr; semi ->
1534             ([ <:str_item< # $n$ $dp$ >> ], stopped_at _loc)
1535         | si = str_item; semi; (sil, stopped) = SELF -> ([si :: sil], stopped)
1536         | `EOI -> ([], None)
1537       ] ]
1538     ;
1539     str_items:
1540       [ [ `ANTIQUOT (""|"stri"|"anti"|"list" as n) s ->
1541             <:str_item< $anti:mk_anti n ~c:"str_item" s$ >>
1542         | `ANTIQUOT (""|"stri"|"anti"|"list" as n) s; semi; st = SELF ->
1543             <:str_item< $anti:mk_anti n ~c:"str_item" s$; $st$ >>
1544         | l = LIST0 [ st = str_item; semi -> st ] -> Ast.stSem_of_list l
1545       ] ]
1546     ;
1547     top_phrase:
1548       [ [ ph = phrase -> Some ph
1549         | `EOI -> None
1550       ] ]
1551     ;
1552     use_file:
1553       [ [ "#"; n = a_LIDENT; dp = opt_expr; semi ->
1554             ([ <:str_item< # $n$ $dp$ >> ], stopped_at _loc)
1555         | si = str_item; semi; (sil, stopped) = SELF -> ([si :: sil], stopped)
1556         | `EOI -> ([], None)
1557       ] ]
1558     ;
1559     phrase:
1560       [ [ "#"; n = a_LIDENT; dp = opt_expr; semi ->
1561             <:str_item< # $n$ $dp$ >>
1562         | st = str_item; semi -> st
1563       ] ]
1564     ;
1565     a_INT:
1566       [ [ `ANTIQUOT (""|"int"|"`int" as n) s -> mk_anti n s
1567         | `INT _ s -> s ] ]
1568     ;
1569     a_INT32:
1570       [ [ `ANTIQUOT (""|"int32"|"`int32" as n) s -> mk_anti n s
1571         | `INT32 _ s -> s ] ]
1572     ;
1573     a_INT64:
1574       [ [ `ANTIQUOT (""|"int64"|"`int64" as n) s -> mk_anti n s
1575         | `INT64 _ s -> s ] ]
1576     ;
1577     a_NATIVEINT:
1578       [ [ `ANTIQUOT (""|"nativeint"|"`nativeint" as n) s -> mk_anti n s
1579         | `NATIVEINT _ s -> s ] ]
1580     ;
1581     a_FLOAT:
1582       [ [ `ANTIQUOT (""|"flo"|"`flo" as n) s -> mk_anti n s
1583         | `FLOAT _ s -> s ] ]
1584     ;
1585     a_CHAR:
1586       [ [ `ANTIQUOT (""|"chr"|"`chr" as n) s -> mk_anti n s
1587         | `CHAR _ s -> s ] ]
1588     ;
1589     a_UIDENT:
1590       [ [ `ANTIQUOT (""|"uid" as n) s -> mk_anti n s
1591         | `UIDENT s -> s ] ]
1592     ;
1593     a_LIDENT:
1594       [ [ `ANTIQUOT (""|"lid" as n) s -> mk_anti n s
1595         | `LIDENT s -> s ] ]
1596     ;
1597     a_LABEL:
1598       [ [ "~"; `ANTIQUOT ("" as n) s; ":" -> mk_anti n s
1599         | `LABEL s -> s ] ]
1600     ;
1601     a_OPTLABEL:
1602       [ [ "?"; `ANTIQUOT ("" as n) s; ":" -> mk_anti n s
1603         | `OPTLABEL s -> s ] ]
1604     ;
1605     a_STRING:
1606       [ [ `ANTIQUOT (""|"str"|"`str" as n) s -> mk_anti n s
1607         | `STRING _ s -> s ] ]
1608     ;
1609     string_list:
1610       [ [ `ANTIQUOT (""|"str_list") s -> Ast.LAnt (mk_anti "str_list" s)
1611         | `STRING _ x; xs = string_list -> Ast.LCons x xs
1612         | `STRING _ x -> Ast.LCons x Ast.LNil ] ]
1613     ;
1614     value_let:
1615       [ [ "value" -> () ] ]
1616     ;
1617     value_val:
1618       [ [ "value" -> () ] ]
1619     ;
1620     semi:
1621       [ [ ";" -> () ] ]
1622     ;
1623     expr_quot:
1624       [ [ e1 = expr; ","; e2 = comma_expr -> <:expr< $e1$, $e2$ >>
1625         | e1 = expr; ";"; e2 = sem_expr -> <:expr< $e1$; $e2$ >>
1626         | e = expr -> e
1627         | -> <:expr<>>
1628       ] ]
1629     ;
1630     patt_quot:
1631       [ [ x = patt; ","; y = comma_patt -> <:patt< $x$, $y$ >>
1632         | x = patt; ";"; y = sem_patt -> <:patt< $x$; $y$ >>
1633         | x = patt; "="; y = patt ->
1634             let i =
1635               match x with
1636               [ <:patt@loc< $anti:s$ >> -> <:ident@loc< $anti:s$ >>
1637               | p -> Ast.ident_of_patt p ]
1638             in
1639             <:patt< $i$ = $y$ >>
1640         | x = patt -> x
1641         | -> <:patt<>>
1642       ] ]
1643     ;
1644     ctyp_quot:
1645       [ [ x = more_ctyp; ","; y = comma_ctyp -> <:ctyp< $x$, $y$ >>
1646         | x = more_ctyp; ";"; y = label_declaration_list -> <:ctyp< $x$; $y$ >>
1647         | x = more_ctyp; "|"; y = constructor_declarations -> <:ctyp< $x$ | $y$ >>
1648         | x = more_ctyp; "of"; y = constructor_arg_list -> <:ctyp< $x$ of $y$ >>
1649         | x = more_ctyp; "of"; y = constructor_arg_list; "|"; z = constructor_declarations ->
1650             <:ctyp< $ <:ctyp< $x$ of $y$ >> $ | $z$ >>
1651         | x = more_ctyp; "of"; "&"; y = amp_ctyp -> <:ctyp< $x$ of & $y$ >>
1652         | x = more_ctyp; "of"; "&"; y = amp_ctyp; "|"; z = row_field ->
1653             <:ctyp< $ <:ctyp< $x$ of & $y$ >> $ | $z$ >>
1654         | x = more_ctyp; ":"; y = more_ctyp -> <:ctyp< $x$ : $y$ >>
1655         | x = more_ctyp; ":"; y = more_ctyp; ";"; z = label_declaration_list ->
1656             <:ctyp< $ <:ctyp< $x$ : $y$ >> $ ; $z$ >>
1657         | x = more_ctyp; "*"; y = star_ctyp -> <:ctyp< $x$ * $y$ >>
1658         | x = more_ctyp; "&"; y = amp_ctyp -> <:ctyp< $x$ & $y$ >>
1659         | x = more_ctyp; "and"; y = constructor_arg_list -> <:ctyp< $x$ and $y$ >>
1660         | x = more_ctyp -> x
1661         | -> <:ctyp<>>
1662       ] ]
1663     ;
1664     more_ctyp:
1665       [ [ "mutable"; x = SELF -> <:ctyp< mutable $x$ >>
1666         | "`"; x = a_ident -> <:ctyp< `$x$ >>
1667         | x = type_kind -> x
1668         | x = type_parameter -> x
1669       ] ]
1670     ;
1671     str_item_quot:
1672       [ [ "#"; n = a_LIDENT; dp = opt_expr -> <:str_item< # $n$ $dp$ >>
1673         | st1 = str_item; semi; st2 = SELF -> <:str_item< $st1$; $st2$ >>
1674         | st = str_item -> st
1675         | -> <:str_item<>> ] ]
1676     ;
1677     sig_item_quot:
1678       [ [ "#"; n = a_LIDENT; dp = opt_expr -> <:sig_item< # $n$ $dp$ >>
1679         | sg1 = sig_item; semi; sg2 = SELF -> <:sig_item< $sg1$; $sg2$ >>
1680         | sg = sig_item -> sg
1681         | -> <:sig_item<>> ] ]
1682     ;
1683     module_type_quot:
1684       [ [ x = module_type -> x
1685         | -> <:module_type<>>
1686       ] ]
1687     ;
1688     module_expr_quot:
1689       [ [ x = module_expr -> x
1690         | -> <:module_expr<>>
1691       ] ]
1692     ;
1693     match_case_quot:
1694       [ [ x = LIST0 match_case0 SEP "|" -> <:match_case< $list:x$ >>
1695         | -> <:match_case<>> ] ]
1696     ;
1697     binding_quot:
1698       [ [ x = binding -> x
1699         | -> <:binding<>>
1700       ] ]
1701     ;
1702     rec_binding_quot:
1703       [ [ x = label_expr_list -> x
1704         | -> <:rec_binding<>> ] ]
1705     ;
1706     module_binding_quot:
1707       [ [ b1 = SELF; "and"; b2 = SELF ->
1708             <:module_binding< $b1$ and $b2$ >>
1709         | `ANTIQUOT ("module_binding"|"anti" as n) s ->
1710             <:module_binding< $anti:mk_anti ~c:"module_binding" n s$ >>
1711         | `ANTIQUOT ("" as n) s -> <:module_binding< $anti:mk_anti ~c:"module_binding" n s$ >>
1712         | `ANTIQUOT ("" as n) m; ":"; mt = module_type ->
1713             <:module_binding< $mk_anti n m$ : $mt$ >>
1714         | `ANTIQUOT ("" as n) m; ":"; mt = module_type; "="; me = module_expr ->
1715             <:module_binding< $mk_anti n m$ : $mt$ = $me$ >>
1716         | m = a_UIDENT; ":"; mt = module_type -> <:module_binding< $m$ : $mt$ >>
1717         | m = a_UIDENT; ":"; mt = module_type; "="; me = module_expr ->
1718             <:module_binding< $m$ : $mt$ = $me$ >>
1719         | -> <:module_binding<>>
1720       ] ]
1721     ;
1722     ident_quot:
1723       [ "apply"
1724         [ i = SELF; j = SELF -> <:ident< $i$ $j$ >> ]
1725       | "."
1726         [ i = SELF; "."; j = SELF -> <:ident< $i$.$j$ >> ]
1727       | "simple"
1728         [ `ANTIQUOT (""|"id"|"anti"|"list" as n) s ->
1729             <:ident< $anti:mk_anti ~c:"ident" n s$ >>
1730         | i = a_UIDENT -> <:ident< $uid:i$ >>
1731         | i = a_LIDENT -> <:ident< $lid:i$ >>
1732         | `ANTIQUOT (""|"id"|"anti"|"list" as n) s; "."; i = SELF ->
1733             <:ident< $anti:mk_anti ~c:"ident" n s$.$i$ >>
1734         | "("; i = SELF; ")" -> i
1735       ] ]
1736     ;
1737     class_expr_quot:
1738       [ [ ce1 = SELF; "and"; ce2 = SELF -> <:class_expr< $ce1$ and $ce2$ >>
1739         | ce1 = SELF; "="; ce2 = SELF -> <:class_expr< $ce1$ = $ce2$ >>
1740         | "virtual"; (i, ot) = class_name_and_param ->
1741             <:class_expr< virtual $lid:i$ [ $ot$ ] >>
1742         | `ANTIQUOT ("virtual" as n) s; i = ident; ot = opt_comma_ctyp ->
1743             let anti = Ast.BAnt (mk_anti ~c:"class_expr" n s) in
1744             <:class_expr< $virtual:anti$ $id:i$ [ $ot$ ] >>
1745         | x = class_expr -> x
1746         | -> <:class_expr<>>
1747       ] ]
1748     ;
1749     class_type_quot:
1750       [ [ ct1 = SELF; "and"; ct2 = SELF -> <:class_type< $ct1$ and $ct2$ >>
1751         | ct1 = SELF; "="; ct2 = SELF -> <:class_type< $ct1$ = $ct2$ >>
1752         | ct1 = SELF; ":"; ct2 = SELF -> <:class_type< $ct1$ : $ct2$ >>
1753         | "virtual"; (i, ot) = class_name_and_param ->
1754             <:class_type< virtual $lid:i$ [ $ot$ ] >>
1755         | `ANTIQUOT ("virtual" as n) s; i = ident; ot = opt_comma_ctyp ->
1756             let anti = Ast.BAnt (mk_anti ~c:"class_type" n s) in
1757             <:class_type< $virtual:anti$ $id:i$ [ $ot$ ] >>
1758         | x = class_type_plus -> x
1759         | -> <:class_type<>>
1760       ] ]
1761     ;
1762     class_str_item_quot:
1763       [ [ x1 = class_str_item; semi; x2 = SELF ->
1764           <:class_str_item< $x1$; $x2$ >>
1765         | x = class_str_item -> x
1766         | -> <:class_str_item<>> ] ]
1767     ;
1768     class_sig_item_quot:
1769       [ [ x1 = class_sig_item; semi; x2 = SELF -> <:class_sig_item< $x1$; $x2$ >>
1770         | x = class_sig_item -> x
1771         | -> <:class_sig_item<>> ] ]
1772     ;
1773     with_constr_quot:
1774       [ [ x = with_constr -> x
1775         | -> <:with_constr<>> ] ]
1776     ;
1777     patt_eoi:
1778       [ [ x = patt; `EOI -> x ] ]
1779     ;
1780     expr_eoi:
1781       [ [ x = expr; `EOI -> x ] ]
1782     ;
1783   END;
1784
1785 end;
1786
1787 let module M = Register.OCamlSyntaxExtension Id Make in ();