Update from HH
[hl193./.git] / pa_j_3.1x_6.xx.ml
1 (* ------------------------------------------------------------------------- *)
2 (* New version.                                                              *)
3 (* ------------------------------------------------------------------------- *)
4
5 (* camlp5r *)
6 (* $Id: pa_o.ml,v 6.33 2010-11-16 16:48:21 deraugla Exp $ *)
7 (* Copyright (c) INRIA 2007-2010 *)
8
9 #load "pa_extend.cmo";
10 #load "q_MLast.cmo";
11 #load "pa_reloc.cmo";
12
13 open Pcaml;
14
15 Pcaml.syntax_name.val := "OCaml";
16 Pcaml.no_constructors_arity.val := True;
17
18 (* ------------------------------------------------------------------------- *)
19 (* The main/reloc.ml file.                                                   *)
20 (* ------------------------------------------------------------------------- *)
21
22 (* camlp5r *)
23 (* $Id: reloc.ml,v 6.15 2010-11-14 11:20:26 deraugla Exp $ *)
24 (* Copyright (c) INRIA 2007-2010 *)
25
26 #load "pa_macro.cmo";
27
28 open MLast;
29
30 value option_map f =
31   fun
32   [ Some x -> Some (f x)
33   | None -> None ]
34 ;
35
36 value vala_map f =
37   IFNDEF STRICT THEN
38     fun x -> f x
39   ELSE
40     fun
41     [ Ploc.VaAnt s -> Ploc.VaAnt s
42     | Ploc.VaVal x -> Ploc.VaVal (f x) ]
43   END
44 ;
45
46 value class_infos_map floc f x =
47   {ciLoc = floc x.ciLoc; ciVir = x.ciVir;
48    ciPrm =
49      let (x1, x2) = x.ciPrm in
50      (floc x1, x2);
51    ciNam = x.ciNam; ciExp = f x.ciExp}
52 ;
53
54 value anti_loc qloc sh loc loc1 =
55   (*
56     ...<:expr<.....$lid:...xxxxxxxx...$...>>...
57     |..|-----------------------------------|    qloc
58        <----->                                  sh
59               |.........|------------|          loc
60                         |..|------|             loc1
61   *)
62   let sh1 = Ploc.first_pos qloc + sh in
63   let sh2 = sh1 + Ploc.first_pos loc in
64   let line_nb_qloc = Ploc.line_nb qloc in
65   let line_nb_loc = Ploc.line_nb loc in
66   let line_nb_loc1 = Ploc.line_nb loc1 in
67   if line_nb_qloc < 0 || line_nb_loc < 0 || line_nb_loc1 < 0 then
68     Ploc.make_unlined
69       (sh2 + Ploc.first_pos loc1, sh2 + Ploc.last_pos loc1)
70   else
71     Ploc.make_loc (Ploc.file_name loc)
72       (line_nb_qloc + line_nb_loc + line_nb_loc1 - 2)
73       (if line_nb_loc1 = 1 then
74          if line_nb_loc = 1 then Ploc.bol_pos qloc
75          else sh1 + Ploc.bol_pos loc
76        else sh2 + Ploc.bol_pos loc1)
77       (sh2 + Ploc.first_pos loc1, sh2 + Ploc.last_pos loc1) ""
78 ;
79
80 value rec reloc_ctyp floc sh =
81   self where rec self =
82     fun
83     [ TyAcc loc x1 x2 ->
84         let loc = floc loc in
85         TyAcc loc (self x1) (self x2)
86     | TyAli loc x1 x2 ->
87         let loc = floc loc in
88         TyAli loc (self x1) (self x2)
89     | TyAny loc ->
90         let loc = floc loc in
91         TyAny loc
92     | TyApp loc x1 x2 ->
93         let loc = floc loc in
94         TyApp loc (self x1) (self x2)
95     | TyArr loc x1 x2 ->
96         let loc = floc loc in
97         TyArr loc (self x1) (self x2)
98     | TyCls loc x1 ->
99         let loc = floc loc in
100         TyCls loc x1
101     | TyLab loc x1 x2 ->
102         let loc = floc loc in
103         TyLab loc x1 (self x2)
104     | TyLid loc x1 ->
105         let loc = floc loc in
106         TyLid loc x1
107     | TyMan loc x1 x2 x3 ->
108         let loc = floc loc in
109         TyMan loc (self x1) x2 (self x3)
110     | TyObj loc x1 x2 ->
111         let loc = floc loc in
112         TyObj loc (vala_map (List.map (fun (x1, x2) -> (x1, self x2))) x1) x2
113     | TyOlb loc x1 x2 ->
114         let loc = floc loc in
115         TyOlb loc x1 (self x2)
116     | TyPck loc x1 ->
117         let loc = floc loc in
118         TyPck loc (reloc_module_type floc sh x1)
119     | TyPol loc x1 x2 ->
120         let loc = floc loc in
121         TyPol loc x1 (self x2)
122     | TyPot loc x1 x2 ->
123         let loc = floc loc in
124         TyPot loc x1 (self x2)
125     | TyQuo loc x1 ->
126         let loc = floc loc in
127         TyQuo loc x1
128     | TyRec loc x1 ->
129         let loc = floc loc in
130         TyRec loc
131           (vala_map
132              (List.map (fun (loc, x1, x2, x3) -> (floc loc, x1, x2, self x3)))
133              x1)
134     | TySum loc x1 ->
135         let loc = floc loc in
136         TySum loc
137           (vala_map
138              (List.map
139                 (fun (loc, x1, x2, x3) ->
140                    (floc loc, x1, vala_map (List.map self) x2,
141                     option_map self x3)))
142              x1)
143     | TyTup loc x1 ->
144         let loc = floc loc in
145         TyTup loc (vala_map (List.map self) x1)
146     | TyUid loc x1 ->
147         let loc = floc loc in
148         TyUid loc x1
149     | TyVrn loc x1 x2 ->
150         let loc = floc loc in
151         TyVrn loc (vala_map (List.map (reloc_poly_variant floc sh)) x1) x2
152     | IFDEF STRICT THEN
153         TyXtr loc x1 x2 ->
154           let loc = floc loc in
155           TyXtr loc x1 (option_map (vala_map self) x2)
156       END ]
157 and reloc_poly_variant floc sh =
158   fun
159   [ PvTag loc x1 x2 x3 ->
160       let loc = floc loc in
161       PvTag loc x1 x2 (vala_map (List.map (reloc_ctyp floc sh)) x3)
162   | PvInh loc x1 ->
163       let loc = floc loc in
164       PvInh loc (reloc_ctyp floc sh x1) ]
165 and reloc_patt floc sh =
166   self where rec self =
167     fun
168     [ PaAcc loc x1 x2 ->
169         let loc = floc loc in
170         PaAcc loc (self x1) (self x2)
171     | PaAli loc x1 x2 ->
172         let loc = floc loc in
173         PaAli loc (self x1) (self x2)
174     | PaAnt loc x1 ->
175         let new_floc loc1 = anti_loc (floc loc) sh loc loc1 in
176         reloc_patt new_floc sh x1
177     | PaAny loc ->
178         let loc = floc loc in
179         PaAny loc
180     | PaApp loc x1 x2 ->
181         let loc = floc loc in
182         PaApp loc (self x1) (self x2)
183     | PaArr loc x1 ->
184         let loc = floc loc in
185         PaArr loc (vala_map (List.map self) x1)
186     | PaChr loc x1 ->
187         let loc = floc loc in
188         PaChr loc x1
189     | PaFlo loc x1 ->
190         let loc = floc loc in
191         PaFlo loc x1
192     | PaInt loc x1 x2 ->
193         let loc = floc loc in
194         PaInt loc x1 x2
195     | PaLab loc x1 x2 ->
196         let loc = floc loc in
197         PaLab loc (self x1) (vala_map (option_map self) x2)
198     | PaLaz loc x1 ->
199         let loc = floc loc in
200         PaLaz loc (self x1)
201     | PaLid loc x1 ->
202         let loc = floc loc in
203         PaLid loc x1
204     | PaNty loc x1 ->
205         let loc = floc loc in
206         PaNty loc x1
207     | PaOlb loc x1 x2 ->
208         let loc = floc loc in
209         PaOlb loc (self x1) (vala_map (option_map (reloc_expr floc sh)) x2)
210     | PaOrp loc x1 x2 ->
211         let loc = floc loc in
212         PaOrp loc (self x1) (self x2)
213     | PaRec loc x1 ->
214         let loc = floc loc in
215         PaRec loc
216           (vala_map (List.map (fun (x1, x2) -> (self x1, self x2))) x1)
217     | PaRng loc x1 x2 ->
218         let loc = floc loc in
219         PaRng loc (self x1) (self x2)
220     | PaStr loc x1 ->
221         let loc = floc loc in
222         PaStr loc x1
223     | PaTup loc x1 ->
224         let loc = floc loc in
225         PaTup loc (vala_map (List.map self) x1)
226     | PaTyc loc x1 x2 ->
227         let loc = floc loc in
228         PaTyc loc (self x1) (reloc_ctyp floc sh x2)
229     | PaTyp loc x1 ->
230         let loc = floc loc in
231         PaTyp loc x1
232     | PaUid loc x1 ->
233         let loc = floc loc in
234         PaUid loc x1
235     | PaUnp loc x1 x2 ->
236         let loc = floc loc in
237         PaUnp loc x1 (option_map (reloc_module_type floc sh) x2)
238     | PaVrn loc x1 ->
239         let loc = floc loc in
240         PaVrn loc x1
241     | IFDEF STRICT THEN
242         PaXtr loc x1 x2 ->
243           let loc = floc loc in
244           PaXtr loc x1 (option_map (vala_map self) x2)
245       END ]
246 and reloc_expr floc sh =
247   self where rec self =
248     fun
249     [ ExAcc loc x1 x2 ->
250         let loc = floc loc in
251         ExAcc loc (self x1) (self x2)
252     | ExAnt loc x1 ->
253         let new_floc loc1 = anti_loc (floc loc) sh loc loc1 in
254         reloc_expr new_floc sh x1
255     | ExApp loc x1 x2 ->
256         let loc = floc loc in
257         ExApp loc (self x1) (self x2)
258     | ExAre loc x1 x2 ->
259         let loc = floc loc in
260         ExAre loc (self x1) (self x2)
261     | ExArr loc x1 ->
262         let loc = floc loc in
263         ExArr loc (vala_map (List.map self) x1)
264     | ExAsr loc x1 ->
265         let loc = floc loc in
266         ExAsr loc (self x1)
267     | ExAss loc x1 x2 ->
268         let loc = floc loc in
269         ExAss loc (self x1) (self x2)
270     | ExBae loc x1 x2 ->
271         let loc = floc loc in
272         ExBae loc (self x1) (vala_map (List.map self) x2)
273     | ExChr loc x1 ->
274         let loc = floc loc in
275         ExChr loc x1
276     | ExCoe loc x1 x2 x3 ->
277         let loc = floc loc in
278         ExCoe loc (self x1) (option_map (reloc_ctyp floc sh) x2) (reloc_ctyp floc sh x3)
279     | ExFlo loc x1 ->
280         let loc = floc loc in
281         ExFlo loc x1
282     | ExFor loc x1 x2 x3 x4 x5 ->
283         let loc = floc loc in
284         ExFor loc x1 (self x2) (self x3) x4 (vala_map (List.map self) x5)
285     | ExFun loc x1 ->
286         let loc = floc loc in
287         ExFun loc
288           (vala_map
289              (List.map
290                 (fun (x1, x2, x3) ->
291                    (reloc_patt floc sh x1, vala_map (option_map self) x2, self x3)))
292              x1)
293     | ExIfe loc x1 x2 x3 ->
294         let loc = floc loc in
295         ExIfe loc (self x1) (self x2) (self x3)
296     | ExInt loc x1 x2 ->
297         let loc = floc loc in
298         ExInt loc x1 x2
299     | ExLab loc x1 x2 ->
300         let loc = floc loc in
301         ExLab loc (reloc_patt floc sh x1) (vala_map (option_map self) x2)
302     | ExLaz loc x1 ->
303         let loc = floc loc in
304         ExLaz loc (self x1)
305     | ExLet loc x1 x2 x3 ->
306         let loc = floc loc in
307         ExLet loc x1
308           (vala_map (List.map (fun (x1, x2) -> (reloc_patt floc sh x1, self x2)))
309              x2)
310           (self x3)
311     | ExLid loc x1 ->
312         let loc = floc loc in
313         ExLid loc x1
314     | ExLmd loc x1 x2 x3 ->
315         let loc = floc loc in
316         ExLmd loc x1 (reloc_module_expr floc sh x2) (self x3)
317     | ExMat loc x1 x2 ->
318         let loc = floc loc in
319         ExMat loc (self x1)
320           (vala_map
321              (List.map
322                 (fun (x1, x2, x3) ->
323                    (reloc_patt floc sh x1, vala_map (option_map self) x2, self x3)))
324              x2)
325     | ExNew loc x1 ->
326         let loc = floc loc in
327         ExNew loc x1
328     | ExObj loc x1 x2 ->
329         let loc = floc loc in
330         ExObj loc (vala_map (option_map (reloc_patt floc sh)) x1)
331           (vala_map (List.map (reloc_class_str_item floc sh)) x2)
332     | ExOlb loc x1 x2 ->
333         let loc = floc loc in
334         ExOlb loc (reloc_patt floc sh x1) (vala_map (option_map self) x2)
335     | ExOvr loc x1 ->
336         let loc = floc loc in
337         ExOvr loc (vala_map (List.map (fun (x1, x2) -> (x1, self x2))) x1)
338     | ExPck loc x1 x2 ->
339         let loc = floc loc in
340         ExPck loc (reloc_module_expr floc sh x1)
341           (option_map (reloc_module_type floc sh) x2)
342     | ExRec loc x1 x2 ->
343         let loc = floc loc in
344         ExRec loc
345           (vala_map (List.map (fun (x1, x2) -> (reloc_patt floc sh x1, self x2)))
346              x1)
347           (option_map self x2)
348     | ExSeq loc x1 ->
349         let loc = floc loc in
350         ExSeq loc (vala_map (List.map self) x1)
351     | ExSnd loc x1 x2 ->
352         let loc = floc loc in
353         ExSnd loc (self x1) x2
354     | ExSte loc x1 x2 ->
355         let loc = floc loc in
356         ExSte loc (self x1) (self x2)
357     | ExStr loc x1 ->
358         let loc = floc loc in
359         ExStr loc x1
360     | ExTry loc x1 x2 ->
361         let loc = floc loc in
362         ExTry loc (self x1)
363           (vala_map
364              (List.map
365                 (fun (x1, x2, x3) ->
366                    (reloc_patt floc sh x1, vala_map (option_map self) x2, self x3)))
367              x2)
368     | ExTup loc x1 ->
369         let loc = floc loc in
370         ExTup loc (vala_map (List.map self) x1)
371     | ExTyc loc x1 x2 ->
372         let loc = floc loc in
373         ExTyc loc (self x1) (reloc_ctyp floc sh x2)
374     | ExUid loc x1 ->
375         let loc = floc loc in
376         ExUid loc x1
377     | ExVrn loc x1 ->
378         let loc = floc loc in
379         ExVrn loc x1
380     | ExWhi loc x1 x2 ->
381         let loc = floc loc in
382         ExWhi loc (self x1) (vala_map (List.map self) x2)
383     | IFDEF STRICT THEN
384         ExXtr loc x1 x2 ->
385           let loc = floc loc in
386           ExXtr loc x1 (option_map (vala_map self) x2)
387       END ]
388 and reloc_module_type floc sh =
389   self where rec self =
390     fun
391     [ MtAcc loc x1 x2 ->
392         let loc = floc loc in
393         MtAcc loc (self x1) (self x2)
394     | MtApp loc x1 x2 ->
395         let loc = floc loc in
396         MtApp loc (self x1) (self x2)
397     | MtFun loc x1 x2 x3 ->
398         let loc = floc loc in
399         MtFun loc x1 (self x2) (self x3)
400     | MtLid loc x1 ->
401         let loc = floc loc in
402         MtLid loc x1
403     | MtQuo loc x1 ->
404         let loc = floc loc in
405         MtQuo loc x1
406     | MtSig loc x1 ->
407         let loc = floc loc in
408         MtSig loc (vala_map (List.map (reloc_sig_item floc sh)) x1)
409     | MtTyo loc x1 ->
410         let loc = floc loc in
411         MtTyo loc (reloc_module_expr floc sh x1)
412     | MtUid loc x1 ->
413         let loc = floc loc in
414         MtUid loc x1
415     | MtWit loc x1 x2 ->
416         let loc = floc loc in
417         MtWit loc (self x1) (vala_map (List.map (reloc_with_constr floc sh)) x2)
418     | IFDEF STRICT THEN
419         MtXtr loc x1 x2 ->
420           let loc = floc loc in
421           MtXtr loc x1 (option_map (vala_map self) x2)
422       END ]
423 and reloc_sig_item floc sh =
424   self where rec self =
425     fun
426     [ SgCls loc x1 ->
427         let loc = floc loc in
428         SgCls loc
429           (vala_map (List.map (class_infos_map floc (reloc_class_type floc sh))) x1)
430     | SgClt loc x1 ->
431         let loc = floc loc in
432         SgClt loc
433           (vala_map (List.map (class_infos_map floc (reloc_class_type floc sh))) x1)
434     | SgDcl loc x1 ->
435         let loc = floc loc in
436         SgDcl loc (vala_map (List.map self) x1)
437     | SgDir loc x1 x2 ->
438         let loc = floc loc in
439         SgDir loc x1 (vala_map (option_map (reloc_expr floc sh)) x2)
440     | SgExc loc x1 x2 ->
441         let loc = floc loc in
442         SgExc loc x1 (vala_map (List.map (reloc_ctyp floc sh)) x2)
443     | SgExt loc x1 x2 x3 ->
444         let loc = floc loc in
445         SgExt loc x1 (reloc_ctyp floc sh x2) x3
446     | SgInc loc x1 ->
447         let loc = floc loc in
448         SgInc loc (reloc_module_type floc sh x1)
449     | SgMod loc x1 x2 ->
450         let loc = floc loc in
451         SgMod loc x1
452           (vala_map (List.map (fun (x1, x2) -> (x1, reloc_module_type floc sh x2)))
453              x2)
454     | SgMty loc x1 x2 ->
455         let loc = floc loc in
456         SgMty loc x1 (reloc_module_type floc sh x2)
457     | SgOpn loc x1 ->
458         let loc = floc loc in
459         SgOpn loc x1
460     | SgTyp loc x1 ->
461         let loc = floc loc in
462         SgTyp loc (vala_map (List.map (reloc_type_decl floc sh)) x1)
463     | SgUse loc x1 x2 ->
464         let loc = floc loc in
465         SgUse loc x1
466           (vala_map (List.map (fun (x1, loc) -> (self x1, floc loc))) x2)
467     | SgVal loc x1 x2 ->
468         let loc = floc loc in
469         SgVal loc x1 (reloc_ctyp floc sh x2)
470     | IFDEF STRICT THEN
471         SgXtr loc x1 x2 ->
472           let loc = floc loc in
473           SgXtr loc x1 (option_map (vala_map self) x2)
474       END ]
475 and reloc_with_constr floc sh =
476   fun
477   [ WcMod loc x1 x2 ->
478       let loc = floc loc in
479       WcMod loc x1 (reloc_module_expr floc sh x2)
480   | WcMos loc x1 x2 ->
481       let loc = floc loc in
482       WcMos loc x1 (reloc_module_expr floc sh x2)
483   | WcTyp loc x1 x2 x3 x4 ->
484       let loc = floc loc in
485       WcTyp loc x1 x2 x3 (reloc_ctyp floc sh x4)
486   | WcTys loc x1 x2 x3 ->
487       let loc = floc loc in
488       WcTys loc x1 x2 (reloc_ctyp floc sh x3) ]
489 and reloc_module_expr floc sh =
490   self where rec self =
491     fun
492     [ MeAcc loc x1 x2 ->
493         let loc = floc loc in
494         MeAcc loc (self x1) (self x2)
495     | MeApp loc x1 x2 ->
496         let loc = floc loc in
497         MeApp loc (self x1) (self x2)
498     | MeFun loc x1 x2 x3 ->
499         let loc = floc loc in
500         MeFun loc x1 (reloc_module_type floc sh x2) (self x3)
501     | MeStr loc x1 ->
502         let loc = floc loc in
503         MeStr loc (vala_map (List.map (reloc_str_item floc sh)) x1)
504     | MeTyc loc x1 x2 ->
505         let loc = floc loc in
506         MeTyc loc (self x1) (reloc_module_type floc sh x2)
507     | MeUid loc x1 ->
508         let loc = floc loc in
509         MeUid loc x1
510     | MeUnp loc x1 x2 ->
511         let loc = floc loc in
512         MeUnp loc (reloc_expr floc sh x1) (option_map (reloc_module_type floc sh) x2)
513     | IFDEF STRICT THEN
514         MeXtr loc x1 x2 ->
515           let loc = floc loc in
516           MeXtr loc x1 (option_map (vala_map self) x2)
517       END ]
518 and reloc_str_item floc sh =
519   self where rec self =
520     fun
521     [ StCls loc x1 ->
522         let loc = floc loc in
523         StCls loc
524           (vala_map (List.map (class_infos_map floc (reloc_class_expr floc sh))) x1)
525     | StClt loc x1 ->
526         let loc = floc loc in
527         StClt loc
528           (vala_map (List.map (class_infos_map floc (reloc_class_type floc sh))) x1)
529     | StDcl loc x1 ->
530         let loc = floc loc in
531         StDcl loc (vala_map (List.map self) x1)
532     | StDir loc x1 x2 ->
533         let loc = floc loc in
534         StDir loc x1 (vala_map (option_map (reloc_expr floc sh)) x2)
535     | StExc loc x1 x2 x3 ->
536         let loc = floc loc in
537         StExc loc x1 (vala_map (List.map (reloc_ctyp floc sh)) x2) x3
538     | StExp loc x1 ->
539         let loc = floc loc in
540         StExp loc (reloc_expr floc sh x1)
541     | StExt loc x1 x2 x3 ->
542         let loc = floc loc in
543         StExt loc x1 (reloc_ctyp floc sh x2) x3
544     | StInc loc x1 ->
545         let loc = floc loc in
546         StInc loc (reloc_module_expr floc sh x1)
547     | StMod loc x1 x2 ->
548         let loc = floc loc in
549         StMod loc x1
550           (vala_map (List.map (fun (x1, x2) -> (x1, reloc_module_expr floc sh x2)))
551              x2)
552     | StMty loc x1 x2 ->
553         let loc = floc loc in
554         StMty loc x1 (reloc_module_type floc sh x2)
555     | StOpn loc x1 ->
556         let loc = floc loc in
557         StOpn loc x1
558     | StTyp loc x1 ->
559         let loc = floc loc in
560         StTyp loc (vala_map (List.map (reloc_type_decl floc sh)) x1)
561     | StUse loc x1 x2 ->
562         let loc = floc loc in
563         StUse loc x1
564           (vala_map (List.map (fun (x1, loc) -> (self x1, floc loc))) x2)
565     | StVal loc x1 x2 ->
566         let loc = floc loc in
567         StVal loc x1
568           (vala_map
569              (List.map (fun (x1, x2) -> (reloc_patt floc sh x1, reloc_expr floc sh x2)))
570              x2)
571     | IFDEF STRICT THEN
572         StXtr loc x1 x2 ->
573           let loc = floc loc in
574           StXtr loc x1 (option_map (vala_map self) x2)
575       END ]
576 and reloc_type_decl floc sh x =
577   {tdNam = vala_map (fun (loc, x1) -> (floc loc, x1)) x.tdNam;
578    tdPrm = x.tdPrm; tdPrv = x.tdPrv; tdDef = reloc_ctyp floc sh x.tdDef;
579    tdCon =
580      vala_map (List.map (fun (x1, x2) -> (reloc_ctyp floc sh x1, reloc_ctyp floc sh x2)))
581        x.tdCon}
582 and reloc_class_type floc sh =
583   self where rec self =
584     fun
585     [ CtAcc loc x1 x2 ->
586         let loc = floc loc in
587         CtAcc loc (self x1) (self x2)
588     | CtApp loc x1 x2 ->
589         let loc = floc loc in
590         CtApp loc (self x1) (self x2)
591     | CtCon loc x1 x2 ->
592         let loc = floc loc in
593         CtCon loc (self x1) (vala_map (List.map (reloc_ctyp floc sh)) x2)
594     | CtFun loc x1 x2 ->
595         let loc = floc loc in
596         CtFun loc (reloc_ctyp floc sh x1) (self x2)
597     | CtIde loc x1 ->
598         let loc = floc loc in
599         CtIde loc x1
600     | CtSig loc x1 x2 ->
601         let loc = floc loc in
602         CtSig loc (vala_map (option_map (reloc_ctyp floc sh)) x1)
603           (vala_map (List.map (reloc_class_sig_item floc sh)) x2)
604     | IFDEF STRICT THEN
605         CtXtr loc x1 x2 ->
606           let loc = floc loc in
607           CtXtr loc x1 (option_map (vala_map self) x2)
608       END ]
609 and reloc_class_sig_item floc sh =
610   self where rec self =
611     fun
612     [ CgCtr loc x1 x2 ->
613         let loc = floc loc in
614         CgCtr loc (reloc_ctyp floc sh x1) (reloc_ctyp floc sh x2)
615     | CgDcl loc x1 ->
616         let loc = floc loc in
617         CgDcl loc (vala_map (List.map self) x1)
618     | CgInh loc x1 ->
619         let loc = floc loc in
620         CgInh loc (reloc_class_type floc sh x1)
621     | CgMth loc x1 x2 x3 ->
622         let loc = floc loc in
623         CgMth loc x1 x2 (reloc_ctyp floc sh x3)
624     | CgVal loc x1 x2 x3 ->
625         let loc = floc loc in
626         CgVal loc x1 x2 (reloc_ctyp floc sh x3)
627     | CgVir loc x1 x2 x3 ->
628         let loc = floc loc in
629         CgVir loc x1 x2 (reloc_ctyp floc sh x3) ]
630 and reloc_class_expr floc sh =
631   self where rec self =
632     fun
633     [ CeApp loc x1 x2 ->
634         let loc = floc loc in
635         CeApp loc (self x1) (reloc_expr floc sh x2)
636     | CeCon loc x1 x2 ->
637         let loc = floc loc in
638         CeCon loc x1 (vala_map (List.map (reloc_ctyp floc sh)) x2)
639     | CeFun loc x1 x2 ->
640         let loc = floc loc in
641         CeFun loc (reloc_patt floc sh x1) (self x2)
642     | CeLet loc x1 x2 x3 ->
643         let loc = floc loc in
644         CeLet loc x1
645           (vala_map
646              (List.map (fun (x1, x2) -> (reloc_patt floc sh x1, reloc_expr floc sh x2)))
647              x2)
648           (self x3)
649     | CeStr loc x1 x2 ->
650         let loc = floc loc in
651         CeStr loc (vala_map (option_map (reloc_patt floc sh)) x1)
652           (vala_map (List.map (reloc_class_str_item floc sh)) x2)
653     | CeTyc loc x1 x2 ->
654         let loc = floc loc in
655         CeTyc loc (self x1) (reloc_class_type floc sh x2)
656     | IFDEF STRICT THEN
657         CeXtr loc x1 x2 ->
658           let loc = floc loc in
659           CeXtr loc x1 (option_map (vala_map self) x2)
660       END ]
661 and reloc_class_str_item floc sh =
662   self where rec self =
663     fun
664     [ CrCtr loc x1 x2 ->
665         let loc = floc loc in
666         CrCtr loc (reloc_ctyp floc sh x1) (reloc_ctyp floc sh x2)
667     | CrDcl loc x1 ->
668         let loc = floc loc in
669         CrDcl loc (vala_map (List.map self) x1)
670     | CrInh loc x1 x2 ->
671         let loc = floc loc in
672         CrInh loc (reloc_class_expr floc sh x1) x2
673     | CrIni loc x1 ->
674         let loc = floc loc in
675         CrIni loc (reloc_expr floc sh x1)
676     | CrMth loc x1 x2 x3 x4 x5 ->
677         let loc = floc loc in
678         CrMth loc x1 x2 x3 (vala_map (option_map (reloc_ctyp floc sh)) x4)
679           (reloc_expr floc sh x5)
680     | CrVal loc x1 x2 x3 x4 ->
681         let loc = floc loc in
682         CrVal loc x1 x2 x3 (reloc_expr floc sh x4)
683     | CrVav loc x1 x2 x3 ->
684         let loc = floc loc in
685         CrVav loc x1 x2 (reloc_ctyp floc sh x3)
686     | CrVir loc x1 x2 x3 ->
687         let loc = floc loc in
688         CrVir loc x1 x2 (reloc_ctyp floc sh x3) ]
689 ;
690
691 (* Equality over syntax trees *)
692
693 value eq_expr x y =
694   reloc_expr (fun _ -> Ploc.dummy) 0 x =
695   reloc_expr (fun _ -> Ploc.dummy) 0 y
696 ;
697 value eq_patt x y =
698   reloc_patt (fun _ -> Ploc.dummy) 0 x =
699   reloc_patt (fun _ -> Ploc.dummy) 0 y
700 ;
701 value eq_ctyp x y =
702   reloc_ctyp (fun _ -> Ploc.dummy) 0 x =
703   reloc_ctyp (fun _ -> Ploc.dummy) 0 y
704 ;
705 value eq_str_item x y =
706   reloc_str_item (fun _ -> Ploc.dummy) 0 x =
707   reloc_str_item (fun _ -> Ploc.dummy) 0 y
708 ;
709 value eq_sig_item x y =
710   reloc_sig_item (fun _ -> Ploc.dummy) 0 x =
711   reloc_sig_item (fun _ -> Ploc.dummy) 0 y
712 ;
713 value eq_module_expr x y =
714   reloc_module_expr (fun _ -> Ploc.dummy) 0 x =
715   reloc_module_expr (fun _ -> Ploc.dummy) 0 y
716 ;
717 value eq_module_type x y =
718   reloc_module_type (fun _ -> Ploc.dummy) 0 x =
719   reloc_module_type (fun _ -> Ploc.dummy) 0 y
720 ;
721 value eq_class_sig_item x y =
722   reloc_class_sig_item (fun _ -> Ploc.dummy) 0 x =
723   reloc_class_sig_item (fun _ -> Ploc.dummy) 0 y
724 ;
725 value eq_class_str_item x y =
726   reloc_class_str_item (fun _ -> Ploc.dummy) 0 x =
727   reloc_class_str_item (fun _ -> Ploc.dummy) 0 y
728 ;
729 value eq_class_type x y =
730   reloc_class_type (fun _ -> Ploc.dummy) 0 x =
731   reloc_class_type (fun _ -> Ploc.dummy) 0 y
732 ;
733 value eq_class_expr x y =
734   reloc_class_expr (fun _ -> Ploc.dummy) 0 x =
735   reloc_class_expr (fun _ -> Ploc.dummy) 0 y
736 ;
737
738 (* ------------------------------------------------------------------------- *)
739 (* Now the lexer.                                                            *)
740 (* ------------------------------------------------------------------------- *)
741
742 (* camlp5r *)
743 (* $Id: plexer.ml,v 6.11 2010-10-04 20:14:58 deraugla Exp $ *)
744 (* Copyright (c) INRIA 2007-2010 *)
745
746 #load "pa_lexer.cmo";
747
748 (* ------------------------------------------------------------------------- *)
749 (* Added by JRH as a backdoor to change lexical conventions.                 *)
750 (* ------------------------------------------------------------------------- *)
751
752 value jrh_lexer = ref False;
753
754 open Versdep;
755
756 value no_quotations = ref False;
757 value error_on_unknown_keywords = ref False;
758
759 value dollar_for_antiquotation = ref True;
760 value specific_space_dot = ref False;
761
762 value force_antiquot_loc = ref False;
763
764 type context =
765   { after_space : mutable bool;
766     dollar_for_antiquotation : bool;
767     specific_space_dot : bool;
768     find_kwd : string -> string;
769     line_cnt : int -> char -> unit;
770     set_line_nb : unit -> unit;
771     make_lined_loc : (int * int) -> string -> Ploc.t }
772 ;
773
774 value err ctx loc msg =
775   Ploc.raise (ctx.make_lined_loc loc "") (Plexing.Error msg)
776 ;
777
778 (* ------------------------------------------------------------------------- *)
779 (* JRH's hack to make the case distinction "unmixed" versus "mixed"          *)
780 (* ------------------------------------------------------------------------- *)
781
782 value is_uppercase s = String.uppercase s = s;
783 value is_only_lowercase s = String.lowercase s = s && not(is_uppercase s);
784
785 value jrh_identifier find_kwd id =
786   let jflag = jrh_lexer.val in
787   if id = "set_jrh_lexer" then
788     (let _ = jrh_lexer.val := True in ("",find_kwd "true"))
789   else if id = "unset_jrh_lexer" then
790     (let _ = jrh_lexer.val := False in ("",find_kwd "false"))
791   else
792   try ("", find_kwd id) with
793    [ Not_found ->
794         if not(jflag) then
795           if is_uppercase (String.sub id 0 1) then ("UIDENT", id)
796           else ("LIDENT", id)
797         else if is_uppercase (String.sub id 0 1) &&
798         is_only_lowercase (String.sub id 1 (String.length id - 1))
799 (***** JRH: Carl's alternative version
800         then ("UIDENT", id)
801         else if is_uppercase (String.sub id 0 1) then ("LIDENT", "__uc_"^id)
802         else ("LIDENT", id)];
803  *****)
804         then ("UIDENT", id) else ("LIDENT", id)];
805
806 (* ------------------------------------------------------------------------- *)
807 (* Back to original file with the mod of using the above.                    *)
808 (* ------------------------------------------------------------------------- *)
809
810 value keyword_or_error ctx loc s =
811   try ("", ctx.find_kwd s) with
812   [ Not_found ->
813       if error_on_unknown_keywords.val then
814         err ctx loc ("illegal token: " ^ s)
815       else ("", s) ]
816 ;
817
818 value stream_peek_nth n strm =
819   loop n (Stream.npeek n strm) where rec loop n =
820     fun
821     [ [] -> None
822     | [x] -> if n == 1 then Some x else None
823     | [_ :: l] -> loop (n - 1) l ]
824 ;
825
826 value utf8_lexing = ref False;
827
828 value misc_letter buf strm =
829   if utf8_lexing.val then
830     match strm with lexer [ '\128'-'\225' | '\227'-'\255' ]
831   else
832     match strm with lexer [ '\128'-'\255' ]
833 ;
834
835 value misc_punct buf strm =
836   if utf8_lexing.val then
837     match strm with lexer [ '\226' _ _ ]
838   else
839     match strm with parser []
840 ;
841
842 value rec ident =
843   lexer
844   [ [ 'A'-'Z' | 'a'-'z' | '0'-'9' | '_' | ''' | misc_letter ] ident! | ]
845 ;
846
847 value rec ident2 =
848   lexer
849   [ [ '!' | '?' | '~' | '=' | '@' | '^' | '&' | '+' | '-' | '*' | '/' |
850       '%' | '.' | ':' | '<' | '>' | '|' | '$' | misc_punct ]
851       ident2!
852   | ]
853 ;
854
855 value rec ident3 =
856   lexer
857   [ [ '0'-'9' | 'A'-'Z' | 'a'-'z' | '_' | '!' | '%' | '&' | '*' | '+' | '-' |
858       '.' | '/' | ':' | '<' | '=' | '>' | '?' | '@' | '^' | '|' | '~' | ''' |
859       '$' | '\128'-'\255' ] ident3!
860   | ]
861 ;
862
863 value binary = lexer [ '0' | '1' ];
864 value octal = lexer [ '0'-'7' ];
865 value decimal = lexer [ '0'-'9' ];
866 value hexa = lexer [ '0'-'9' | 'a'-'f' | 'A'-'F' ];
867
868 value end_integer =
869   lexer
870   [ "l"/ -> ("INT_l", $buf)
871   | "L"/ -> ("INT_L", $buf)
872   | "n"/ -> ("INT_n", $buf)
873   | -> ("INT", $buf) ]
874 ;
875
876 value rec digits_under kind =
877   lexer
878   [ kind (digits_under kind)!
879   | "_" (digits_under kind)!
880   | end_integer ]
881 ;
882
883 value digits kind =
884   lexer
885   [ kind (digits_under kind)!
886   | -> raise (Stream.Error "ill-formed integer constant") ]
887 ;
888
889 value rec decimal_digits_under =
890   lexer [ [ '0'-'9' | '_' ] decimal_digits_under! | ]
891 ;
892
893 value exponent_part =
894   lexer
895   [ [ 'e' | 'E' ] [ '+' | '-' | ]
896     '0'-'9' ? "ill-formed floating-point constant"
897     decimal_digits_under! ]
898 ;
899
900 value number =
901   lexer
902   [ decimal_digits_under "." decimal_digits_under! exponent_part ->
903       ("FLOAT", $buf)
904   | decimal_digits_under "." decimal_digits_under! -> ("FLOAT", $buf)
905   | decimal_digits_under exponent_part -> ("FLOAT", $buf)
906   | decimal_digits_under end_integer! ]
907 ;
908
909 value char_after_bslash =
910   lexer
911   [ "'"/
912   | _ [ "'"/ | _ [ "'"/ | ] ] ]
913 ;
914
915 value char ctx bp =
916   lexer
917   [ "\\" _ char_after_bslash!
918   | "\\" -> err ctx (bp, $pos) "char not terminated"
919   | ?= [ _ '''] _! "'"/ ]
920 ;
921
922 value any ctx buf =
923   parser bp [: `c :] -> do { ctx.line_cnt bp c; $add c }
924 ;
925
926 value rec string ctx bp =
927   lexer
928   [ "\""/
929   | "\\" (any ctx) (string ctx bp)!
930   | (any ctx) (string ctx bp)!
931   | -> err ctx (bp, $pos) "string not terminated" ]
932 ;
933
934 value rec qstring ctx bp =
935   lexer
936   [ "`"/
937   | (any ctx) (qstring ctx bp)!
938   | -> err ctx (bp, $pos) "quotation not terminated" ]
939 ;
940
941 value comment ctx bp =
942   comment where rec comment =
943     lexer
944     [ "*)"
945     | "*" comment!
946     | "(*" comment! comment!
947     | "(" comment!
948     | "\"" (string ctx bp)! [ -> $add "\"" ] comment!
949     | "'*)"
950     | "'*" comment!
951     | "'" (any ctx) comment!
952     | (any ctx) comment!
953     | -> err ctx (bp, $pos) "comment not terminated" ]
954 ;
955
956 value rec quotation ctx bp =
957   lexer
958   [ ">>"/
959   | ">" (quotation ctx bp)!
960   | "<<" (quotation ctx bp)! [ -> $add ">>" ]! (quotation ctx bp)!
961   | "<:" ident! "<" (quotation ctx bp)! [ -> $add ">>" ]! (quotation ctx bp)!
962   | "<:" ident! (quotation ctx bp)!
963   | "<" (quotation ctx bp)!
964   | "\\"/ [ '>' | '<' | '\\' ] (quotation ctx bp)!
965   | "\\" (quotation ctx bp)!
966   | (any ctx) (quotation ctx bp)!
967   | -> err ctx (bp, $pos) "quotation not terminated" ]
968 ;
969
970 value less_expected = "character '<' expected";
971
972 value less ctx bp buf strm =
973   if no_quotations.val then
974     match strm with lexer
975     [ [ -> $add "<" ] ident2! -> keyword_or_error ctx (bp, $pos) $buf ]
976   else
977     match strm with lexer
978     [ "<"/ (quotation ctx bp) -> ("QUOTATION", ":" ^ $buf)
979     | ":"/ ident! "<"/ ? less_expected [ -> $add ":" ]! (quotation ctx bp) ->
980         ("QUOTATION", $buf)
981     | ":"/ ident! ":<"/ ? less_expected [ -> $add "@" ]! (quotation ctx bp) ->
982         ("QUOTATION", $buf)
983     | [ -> $add "<" ] ident2! -> keyword_or_error ctx (bp, $pos) $buf ]
984 ;
985
986 value rec antiquot_rest ctx bp =
987   lexer
988   [ "$"/
989   | "\\"/ (any ctx) (antiquot_rest ctx bp)!
990   | (any ctx) (antiquot_rest ctx bp)!
991   | -> err ctx (bp, $pos) "antiquotation not terminated" ]
992 ;
993
994 value rec antiquot ctx bp =
995   lexer
996   [ "$"/ -> ":" ^ $buf
997   | [ 'a'-'z' | 'A'-'Z' | '0'-'9' | '!' | '_' ] (antiquot ctx bp)!
998   | ":" (antiquot_rest ctx bp)! -> $buf
999   | "\\"/ (any ctx) (antiquot_rest ctx bp)! -> ":" ^ $buf
1000   | (any ctx) (antiquot_rest ctx bp)! -> ":" ^ $buf
1001   | -> err ctx (bp, $pos) "antiquotation not terminated" ]
1002 ;
1003
1004 value antiloc bp ep s = Printf.sprintf "%d,%d:%s" bp ep s;
1005
1006 value rec antiquot_loc ctx bp =
1007   lexer
1008   [ "$"/ -> antiloc bp $pos (":" ^ $buf)
1009   | [ 'a'-'z' | 'A'-'Z' | '0'-'9' | '!' | '_' ] (antiquot_loc ctx bp)!
1010   | ":" (antiquot_rest ctx bp)! -> antiloc bp $pos $buf
1011   | "\\"/ (any ctx) (antiquot_rest ctx bp)! -> antiloc bp $pos (":" ^ $buf)
1012   | (any ctx) (antiquot_rest ctx bp)! -> antiloc bp $pos (":" ^ $buf)
1013   | -> err ctx (bp, $pos) "antiquotation not terminated" ]
1014 ;
1015
1016 value dollar ctx bp buf strm =
1017   if not no_quotations.val && ctx.dollar_for_antiquotation then
1018     ("ANTIQUOT", antiquot ctx bp buf strm)
1019   else if force_antiquot_loc.val then
1020     ("ANTIQUOT_LOC", antiquot_loc ctx bp buf strm)
1021   else
1022     match strm with lexer
1023     [ [ -> $add "$" ] ident2! -> ("", $buf) ]
1024 ;
1025
1026 (* ANTIQUOT - specific case for QUESTIONIDENT and QUESTIONIDENTCOLON
1027     input         expr        patt
1028     -----         ----        ----
1029     ?$abc:d$      ?abc:d      ?abc
1030     ?$abc:d$:     ?abc:d:     ?abc:
1031     ?$d$          ?:d         ?
1032     ?$d$:         ?:d:        ?:
1033 *)
1034
1035 (* ANTIQUOT_LOC - specific case for QUESTIONIDENT and QUESTIONIDENTCOLON
1036     input         expr             patt
1037     -----         ----             ----
1038     ?$abc:d$      ?8,13:abc:d      ?abc
1039     ?$abc:d$:     ?8,13:abc:d:     ?abc:
1040     ?$d$          ?8,9::d          ?
1041     ?$d$:         ?8,9::d:         ?:
1042 *)
1043
1044 value question ctx bp buf strm =
1045   if ctx.dollar_for_antiquotation then
1046     match strm with parser
1047     [ [: `'$'; s = antiquot ctx bp $empty; `':' :] ->
1048         ("ANTIQUOT", "?" ^ s ^ ":")
1049     | [: `'$'; s = antiquot ctx bp $empty :] ->
1050         ("ANTIQUOT", "?" ^ s)
1051     | [: :] ->
1052         match strm with lexer
1053         [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ] ]
1054   else if force_antiquot_loc.val then
1055     match strm with parser
1056     [ [: `'$'; s = antiquot_loc ctx bp $empty; `':' :] ->
1057         ("ANTIQUOT_LOC", "?" ^ s ^ ":")
1058     | [: `'$'; s = antiquot_loc ctx bp $empty :] ->
1059         ("ANTIQUOT_LOC", "?" ^ s)
1060     | [: :] ->
1061         match strm with lexer
1062         [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ] ]
1063   else
1064     match strm with lexer
1065     [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ]
1066 ;
1067
1068 value tilde ctx bp buf strm =
1069   if ctx.dollar_for_antiquotation then
1070     match strm with parser
1071     [ [: `'$'; s = antiquot ctx bp $empty; `':' :] ->
1072         ("ANTIQUOT", "~" ^ s ^ ":")
1073     | [: `'$'; s = antiquot ctx bp $empty :] ->
1074         ("ANTIQUOT", "~" ^ s)
1075     | [: :] ->
1076         match strm with lexer
1077         [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ] ]
1078   else if force_antiquot_loc.val then
1079     match strm with parser
1080     [ [: `'$'; s = antiquot_loc ctx bp $empty; `':' :] ->
1081         ("ANTIQUOT_LOC", "~" ^ s ^ ":")
1082     | [: `'$'; s = antiquot_loc ctx bp $empty :] ->
1083         ("ANTIQUOT_LOC", "~" ^ s)
1084     | [: :] ->
1085         match strm with lexer
1086         [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ] ]
1087   else
1088     match strm with lexer
1089     [ ident2! -> keyword_or_error ctx (bp, $pos) $buf ]
1090 ;
1091
1092 value tildeident =
1093   lexer
1094   [ ":"/ -> ("TILDEIDENTCOLON", $buf)
1095   | -> ("TILDEIDENT", $buf) ]
1096 ;
1097
1098 value questionident =
1099   lexer
1100   [ ":"/ -> ("QUESTIONIDENTCOLON", $buf)
1101   | -> ("QUESTIONIDENT", $buf) ]
1102 ;
1103
1104 value rec linedir n s =
1105   match stream_peek_nth n s with
1106   [ Some (' ' | '\t') -> linedir (n + 1) s
1107   | Some ('0'..'9') -> linedir_digits (n + 1) s
1108   | _ -> False ]
1109 and linedir_digits n s =
1110   match stream_peek_nth n s with
1111   [ Some ('0'..'9') -> linedir_digits (n + 1) s
1112   | _ -> linedir_quote n s ]
1113 and linedir_quote n s =
1114   match stream_peek_nth n s with
1115   [ Some (' ' | '\t') -> linedir_quote (n + 1) s
1116   | Some '"' -> True
1117   | _ -> False ]
1118 ;
1119
1120 value rec any_to_nl =
1121   lexer
1122   [ "\r" | "\n"
1123   | _ any_to_nl!
1124   | ]
1125 ;
1126
1127 value next_token_after_spaces ctx bp =
1128   lexer
1129   [ 'A'-'Z' ident! ->
1130       let id = $buf in
1131      jrh_identifier ctx.find_kwd id
1132 (********** JRH: original was
1133       try ("", ctx.find_kwd id) with [ Not_found -> ("UIDENT", id) ]
1134  *********)
1135   | [ 'a'-'z' | '_' | misc_letter ] ident! ->
1136       let id = $buf in
1137       jrh_identifier ctx.find_kwd id
1138 (********** JRH: original was
1139       try ("", ctx.find_kwd id) with [ Not_found -> ("LIDENT", id) ]
1140  *********)               
1141   | '1'-'9' number!
1142   | "0" [ 'o' | 'O' ] (digits octal)!
1143   | "0" [ 'x' | 'X' ] (digits hexa)!
1144   | "0" [ 'b' | 'B' ] (digits binary)!
1145   | "0" number!
1146   | "'"/ ?= [ '\\' 'a'-'z' 'a'-'z' ] -> keyword_or_error ctx (bp, $pos) "'"
1147   | "'"/ (char ctx bp) -> ("CHAR", $buf)
1148   | "'" -> keyword_or_error ctx (bp, $pos) "'"
1149   | "\""/ (string ctx bp)! -> ("STRING", $buf)
1150 (*** Line added by JRH ***)
1151   | "`"/ (qstring ctx bp)! -> ("QUOTATION", "tot:" ^ $buf)
1152   | "$"/ (dollar ctx bp)!
1153   | [ '!' | '=' | '@' | '^' | '&' | '+' | '-' | '*' | '/' | '%' ] ident2! ->
1154       keyword_or_error ctx (bp, $pos) $buf
1155   | "~"/ 'a'-'z' ident! tildeident!
1156   | "~"/ '_' ident! tildeident!
1157   | "~" (tilde ctx bp)
1158   | "?"/ 'a'-'z' ident! questionident!
1159   | "?" (question ctx bp)!
1160   | "<"/ (less ctx bp)!
1161   | ":]" -> keyword_or_error ctx (bp, $pos) $buf
1162   | "::" -> keyword_or_error ctx (bp, $pos) $buf
1163   | ":=" -> keyword_or_error ctx (bp, $pos) $buf
1164   | ":>" -> keyword_or_error ctx (bp, $pos) $buf
1165   | ":" -> keyword_or_error ctx (bp, $pos) $buf
1166   | ">]" -> keyword_or_error ctx (bp, $pos) $buf
1167   | ">}" -> keyword_or_error ctx (bp, $pos) $buf
1168   | ">" ident2! -> keyword_or_error ctx (bp, $pos) $buf
1169   | "|]" -> keyword_or_error ctx (bp, $pos) $buf
1170   | "|}" -> keyword_or_error ctx (bp, $pos) $buf
1171   | "|" ident2! -> keyword_or_error ctx (bp, $pos) $buf
1172   | "[" ?= [ "<<" | "<:" ] -> keyword_or_error ctx (bp, $pos) $buf
1173   | "[|" -> keyword_or_error ctx (bp, $pos) $buf
1174   | "[<" -> keyword_or_error ctx (bp, $pos) $buf
1175   | "[:" -> keyword_or_error ctx (bp, $pos) $buf
1176   | "[" -> keyword_or_error ctx (bp, $pos) $buf
1177   | "{" ?= [ "<<" | "<:" ] -> keyword_or_error ctx (bp, $pos) $buf
1178   | "{|" -> keyword_or_error ctx (bp, $pos) $buf
1179   | "{<" -> keyword_or_error ctx (bp, $pos) $buf
1180   | "{:" -> keyword_or_error ctx (bp, $pos) $buf
1181   | "{" -> keyword_or_error ctx (bp, $pos) $buf
1182   | ".." -> keyword_or_error ctx (bp, $pos) ".."
1183   | "." ->
1184       let id =
1185         if ctx.specific_space_dot && ctx.after_space then " ." else "."
1186       in
1187       keyword_or_error ctx (bp, $pos) id
1188   | ";;" -> keyword_or_error ctx (bp, $pos) ";;"
1189   | ";" -> keyword_or_error ctx (bp, $pos) ";"
1190   | misc_punct ident2! -> keyword_or_error ctx (bp, $pos) $buf
1191   | "\\"/ ident3! -> ("LIDENT", $buf)
1192   | (any ctx) -> keyword_or_error ctx (bp, $pos) $buf ]
1193 ;
1194
1195 value get_comment buf strm = $buf;
1196
1197 value rec next_token ctx buf =
1198   parser bp
1199   [ [: `('\n' | '\r' as c); s :] ep -> do {
1200       if c = '\n' then incr Plexing.line_nb.val else ();
1201       Plexing.bol_pos.val.val := ep;
1202       ctx.set_line_nb ();
1203       ctx.after_space := True;
1204       next_token ctx ($add c) s
1205     }
1206   | [: `(' ' | '\t' | '\026' | '\012' as c); s :] -> do {
1207       ctx.after_space := True;
1208       next_token ctx ($add c) s
1209     }
1210   | [: `'#' when bp = Plexing.bol_pos.val.val; s :] ->
1211       let comm = get_comment buf () in
1212       if linedir 1 s then do {
1213         let buf = any_to_nl ($add '#') s in
1214         incr Plexing.line_nb.val;
1215         Plexing.bol_pos.val.val := Stream.count s;
1216         ctx.set_line_nb ();
1217         ctx.after_space := True;
1218         next_token ctx buf s
1219       }
1220       else
1221         let loc = ctx.make_lined_loc (bp, bp + 1) comm in
1222         (keyword_or_error ctx (bp, bp + 1) "#", loc)
1223   | [: `'(';
1224        a =
1225          parser
1226          [ [: `'*'; buf = comment ctx bp ($add "(*") !; s :] -> do {
1227              ctx.set_line_nb ();
1228              ctx.after_space := True;
1229              next_token ctx buf s
1230            }
1231          | [: :] ep ->
1232              let loc = ctx.make_lined_loc (bp, ep) $buf in
1233              (keyword_or_error ctx (bp, ep) "(", loc) ] ! :] -> a
1234   | [: comm = get_comment buf;
1235        tok = next_token_after_spaces ctx bp $empty :] ep ->
1236       let loc = ctx.make_lined_loc (bp, max (bp + 1) ep) comm in
1237       (tok, loc)
1238   | [: comm = get_comment buf; _ = Stream.empty :] ->
1239       let loc = ctx.make_lined_loc (bp, bp + 1) comm in
1240       (("EOI", ""), loc) ]
1241 ;
1242
1243 value next_token_fun ctx glexr (cstrm, s_line_nb, s_bol_pos) =
1244   try do {
1245     match Plexing.restore_lexing_info.val with
1246     [ Some (line_nb, bol_pos) -> do {
1247         s_line_nb.val := line_nb;
1248         s_bol_pos.val := bol_pos;
1249         Plexing.restore_lexing_info.val := None;
1250       }
1251     | None -> () ];
1252     Plexing.line_nb.val := s_line_nb;
1253     Plexing.bol_pos.val := s_bol_pos;
1254     let comm_bp = Stream.count cstrm in
1255     ctx.set_line_nb ();
1256     ctx.after_space := False;
1257     let (r, loc) = next_token ctx $empty cstrm in
1258     match glexr.val.Plexing.tok_comm with
1259     [ Some list ->
1260         if Ploc.first_pos loc > comm_bp then
1261           let comm_loc = Ploc.make_unlined (comm_bp, Ploc.last_pos loc) in
1262           glexr.val.Plexing.tok_comm := Some [comm_loc :: list]
1263         else ()
1264     | None -> () ];
1265     (r, loc)
1266   }
1267   with
1268   [ Stream.Error str ->
1269       err ctx (Stream.count cstrm, Stream.count cstrm + 1) str ]
1270 ;
1271
1272 value func kwd_table glexr =
1273   let ctx =
1274     let line_nb = ref 0 in
1275     let bol_pos = ref 0 in
1276     {after_space = False;
1277      dollar_for_antiquotation = dollar_for_antiquotation.val;
1278      specific_space_dot = specific_space_dot.val;
1279      find_kwd = Hashtbl.find kwd_table;
1280      line_cnt bp1 c =
1281        match c with
1282        [ '\n' | '\r' -> do {
1283            if c = '\n' then incr Plexing.line_nb.val else ();
1284            Plexing.bol_pos.val.val := bp1 + 1;
1285          }
1286        | c -> () ];
1287      set_line_nb () = do {
1288        line_nb.val := Plexing.line_nb.val.val;
1289        bol_pos.val := Plexing.bol_pos.val.val;
1290      };
1291      make_lined_loc loc comm =
1292        Ploc.make_loc Plexing.input_file.val line_nb.val bol_pos.val loc comm}
1293   in
1294   Plexing.lexer_func_of_parser (next_token_fun ctx glexr)
1295 ;
1296
1297 value rec check_keyword_stream =
1298   parser [: _ = check $empty; _ = Stream.empty :] -> True
1299 and check =
1300   lexer
1301   [ [ 'A'-'Z' | 'a'-'z' | misc_letter ] check_ident!
1302   | [ '!' | '?' | '~' | '=' | '@' | '^' | '&' | '+' | '-' | '*' | '/' | '%' |
1303       '.' ]
1304       check_ident2!
1305   | "$" check_ident2!
1306   | "<" ?= [ ":" | "<" ]
1307   | "<" check_ident2!
1308   | ":]"
1309   | "::"
1310   | ":="
1311   | ":>"
1312   | ":"
1313   | ">]"
1314   | ">}"
1315   | ">" check_ident2!
1316   | "|]"
1317   | "|}"
1318   | "|" check_ident2!
1319   | "[" ?= [ "<<" | "<:" ]
1320   | "[|"
1321   | "[<"
1322   | "[:"
1323   | "["
1324   | "{" ?= [ "<<" | "<:" ]
1325   | "{|"
1326   | "{<"
1327   | "{:"
1328   | "{"
1329   | ";;"
1330   | ";"
1331   | misc_punct check_ident2!
1332   | _ ]
1333 and check_ident =
1334   lexer
1335   [ [ 'A'-'Z' | 'a'-'z' | '0'-'9' | '_' | ''' | misc_letter ]
1336     check_ident! | ]
1337 and check_ident2 =
1338   lexer
1339   [ [ '!' | '?' | '~' | '=' | '@' | '^' | '&' | '+' | '-' | '*' | '/' | '%' |
1340       '.' | ':' | '<' | '>' | '|' | misc_punct ]
1341     check_ident2! | ]
1342 ;
1343
1344 value check_keyword s =
1345   try check_keyword_stream (Stream.of_string s) with _ -> False
1346 ;
1347
1348 value error_no_respect_rules p_con p_prm =
1349   raise
1350     (Plexing.Error
1351        ("the token " ^
1352           (if p_con = "" then "\"" ^ p_prm ^ "\""
1353            else if p_prm = "" then p_con
1354            else p_con ^ " \"" ^ p_prm ^ "\"") ^
1355           " does not respect Plexer rules"))
1356 ;
1357
1358 value error_ident_and_keyword p_con p_prm =
1359   raise
1360     (Plexing.Error
1361        ("the token \"" ^ p_prm ^ "\" is used as " ^ p_con ^
1362           " and as keyword"))
1363 ;
1364
1365 value using_token kwd_table ident_table (p_con, p_prm) =
1366   match p_con with
1367   [ "" ->
1368       if not (hashtbl_mem kwd_table p_prm) then
1369         if check_keyword p_prm then
1370           if hashtbl_mem ident_table p_prm then
1371             error_ident_and_keyword (Hashtbl.find ident_table p_prm) p_prm
1372           else Hashtbl.add kwd_table p_prm p_prm
1373         else error_no_respect_rules p_con p_prm
1374       else ()
1375   | "LIDENT" ->
1376       if p_prm = "" then ()
1377       else
1378         match p_prm.[0] with
1379         [ 'A'..'Z' -> error_no_respect_rules p_con p_prm
1380         | _ ->
1381             if hashtbl_mem kwd_table p_prm then
1382               error_ident_and_keyword p_con p_prm
1383             else Hashtbl.add ident_table p_prm p_con ]
1384   | "UIDENT" ->
1385       if p_prm = "" then ()
1386       else
1387         match p_prm.[0] with
1388         [ 'a'..'z' -> error_no_respect_rules p_con p_prm
1389         | _ ->
1390             if hashtbl_mem kwd_table p_prm then
1391               error_ident_and_keyword p_con p_prm
1392             else Hashtbl.add ident_table p_prm p_con ]
1393   | "TILDEIDENT" | "TILDEIDENTCOLON" | "QUESTIONIDENT" |
1394     "QUESTIONIDENTCOLON" | "INT" | "INT_l" | "INT_L" | "INT_n" | "FLOAT" |
1395     "CHAR" | "STRING" | "QUOTATION" |
1396     "ANTIQUOT" | "ANTIQUOT_LOC" | "EOI" ->
1397       ()
1398   | _ ->
1399       raise
1400         (Plexing.Error
1401            ("the constructor \"" ^ p_con ^
1402               "\" is not recognized by Plexer")) ]
1403 ;
1404
1405 value removing_token kwd_table ident_table (p_con, p_prm) =
1406   match p_con with
1407   [ "" -> Hashtbl.remove kwd_table p_prm
1408   | "LIDENT" | "UIDENT" ->
1409       if p_prm <> "" then Hashtbl.remove ident_table p_prm else ()
1410   | _ -> () ]
1411 ;
1412
1413 value text =
1414   fun
1415   [ ("", t) -> "'" ^ t ^ "'"
1416   | ("LIDENT", "") -> "lowercase identifier"
1417   | ("LIDENT", t) -> "'" ^ t ^ "'"
1418   | ("UIDENT", "") -> "uppercase identifier"
1419   | ("UIDENT", t) -> "'" ^ t ^ "'"
1420   | ("INT", "") -> "integer"
1421   | ("INT", s) -> "'" ^ s ^ "'"
1422   | ("FLOAT", "") -> "float"
1423   | ("STRING", "") -> "string"
1424   | ("CHAR", "") -> "char"
1425   | ("QUOTATION", "") -> "quotation"
1426   | ("ANTIQUOT", k) -> "antiquot \"" ^ k ^ "\""
1427   | ("EOI", "") -> "end of input"
1428   | (con, "") -> con
1429   | (con, prm) -> con ^ " \"" ^ prm ^ "\"" ]
1430 ;
1431
1432 value eq_before_colon p e =
1433   loop 0 where rec loop i =
1434     if i == String.length e then
1435       failwith "Internal error in Plexer: incorrect ANTIQUOT"
1436     else if i == String.length p then e.[i] == ':'
1437     else if p.[i] == e.[i] then loop (i + 1)
1438     else False
1439 ;
1440
1441 value after_colon e =
1442   try
1443     let i = String.index e ':' in
1444     String.sub e (i + 1) (String.length e - i - 1)
1445   with
1446   [ Not_found -> "" ]
1447 ;
1448
1449 value after_colon_except_last e =
1450   try
1451     let i = String.index e ':' in
1452     String.sub e (i + 1) (String.length e - i - 2)
1453   with
1454   [ Not_found -> "" ]
1455 ;
1456
1457 value tok_match =
1458   fun
1459   [ ("ANTIQUOT", p_prm) ->
1460       if p_prm <> "" && (p_prm.[0] = '~' || p_prm.[0] = '?') then
1461         if p_prm.[String.length p_prm - 1] = ':' then
1462           let p_prm = String.sub p_prm 0 (String.length p_prm - 1) in
1463           fun
1464           [ ("ANTIQUOT", prm) ->
1465               if prm <> "" && prm.[String.length prm - 1] = ':' then
1466                 if eq_before_colon p_prm prm then after_colon_except_last prm
1467                 else raise Stream.Failure
1468               else raise Stream.Failure
1469           | _ -> raise Stream.Failure ]
1470         else
1471           fun
1472           [ ("ANTIQUOT", prm) ->
1473               if prm <> "" && prm.[String.length prm - 1] = ':' then
1474                 raise Stream.Failure
1475               else if eq_before_colon p_prm prm then after_colon prm
1476               else raise Stream.Failure
1477           | _ -> raise Stream.Failure ]
1478       else
1479         fun
1480         [ ("ANTIQUOT", prm) when eq_before_colon p_prm prm -> after_colon prm
1481         | _ -> raise Stream.Failure ]
1482   | tok -> Plexing.default_match tok ]
1483 ;
1484
1485 value gmake () =
1486   let kwd_table = Hashtbl.create 301 in
1487   let id_table = Hashtbl.create 301 in
1488   let glexr =
1489     ref
1490      {Plexing.tok_func = fun []; tok_using = fun []; tok_removing = fun [];
1491       tok_match = fun []; tok_text = fun []; tok_comm = None}
1492   in
1493   let glex =
1494     {Plexing.tok_func = func kwd_table glexr;
1495      tok_using = using_token kwd_table id_table;
1496      tok_removing = removing_token kwd_table id_table; tok_match = tok_match;
1497      tok_text = text; tok_comm = None}
1498   in
1499   do { glexr.val := glex; glex }
1500 ;
1501
1502 (* ------------------------------------------------------------------------- *)
1503 (* Back to etc/pa_o.ml                                                       *)
1504 (* ------------------------------------------------------------------------- *)
1505
1506 do {
1507   let odfa = dollar_for_antiquotation.val in
1508   dollar_for_antiquotation.val := False;
1509   Grammar.Unsafe.gram_reinit gram (gmake ());
1510   dollar_for_antiquotation.val := odfa;
1511   Grammar.Unsafe.clear_entry interf;
1512   Grammar.Unsafe.clear_entry implem;
1513   Grammar.Unsafe.clear_entry top_phrase;
1514   Grammar.Unsafe.clear_entry use_file;
1515   Grammar.Unsafe.clear_entry module_type;
1516   Grammar.Unsafe.clear_entry module_expr;
1517   Grammar.Unsafe.clear_entry sig_item;
1518   Grammar.Unsafe.clear_entry str_item;
1519   Grammar.Unsafe.clear_entry signature;
1520   Grammar.Unsafe.clear_entry structure;
1521   Grammar.Unsafe.clear_entry expr;
1522   Grammar.Unsafe.clear_entry patt;
1523   Grammar.Unsafe.clear_entry ctyp;
1524   Grammar.Unsafe.clear_entry let_binding;
1525   Grammar.Unsafe.clear_entry type_decl;
1526   Grammar.Unsafe.clear_entry constructor_declaration;
1527   Grammar.Unsafe.clear_entry label_declaration;
1528   Grammar.Unsafe.clear_entry match_case;
1529   Grammar.Unsafe.clear_entry with_constr;
1530   Grammar.Unsafe.clear_entry poly_variant;
1531   Grammar.Unsafe.clear_entry class_type;
1532   Grammar.Unsafe.clear_entry class_expr;
1533   Grammar.Unsafe.clear_entry class_sig_item;
1534   Grammar.Unsafe.clear_entry class_str_item
1535 };
1536
1537 Pcaml.parse_interf.val := Grammar.Entry.parse interf;
1538 Pcaml.parse_implem.val := Grammar.Entry.parse implem;
1539
1540 value mklistexp loc last =
1541   loop True where rec loop top =
1542     fun
1543     [ [] ->
1544         match last with
1545         [ Some e -> e
1546         | None -> <:expr< [] >> ]
1547     | [e1 :: el] ->
1548         let loc =
1549           if top then loc else Ploc.encl (MLast.loc_of_expr e1) loc
1550         in
1551         <:expr< [$e1$ :: $loop False el$] >> ]
1552 ;
1553
1554 value mklistpat loc last =
1555   loop True where rec loop top =
1556     fun
1557     [ [] ->
1558         match last with
1559         [ Some p -> p
1560         | None -> <:patt< [] >> ]
1561     | [p1 :: pl] ->
1562         let loc =
1563           if top then loc else Ploc.encl (MLast.loc_of_patt p1) loc
1564         in
1565         <:patt< [$p1$ :: $loop False pl$] >> ]
1566 ;
1567
1568 (*** JRH pulled this outside so user can add new infixes here too ***)
1569
1570 value ht = Hashtbl.create 73;
1571
1572 (*** And JRH added all the new HOL Light infixes here already ***)
1573
1574 value is_operator = do {
1575   let ct = Hashtbl.create 73 in
1576   List.iter (fun x -> Hashtbl.add ht x True)
1577     ["asr"; "land"; "lor"; "lsl"; "lsr"; "lxor"; "mod"; "or"; "o"; "upto";
1578      "F_F"; "THENC"; "THEN"; "THENL"; "ORELSE"; "ORELSEC";
1579      "THEN_TCL"; "ORELSE_TCL"];
1580   List.iter (fun x -> Hashtbl.add ct x True)
1581     ['!'; '&'; '*'; '+'; '-'; '/'; ':'; '<'; '='; '>'; '@'; '^'; '|'; '~';
1582      '?'; '%'; '.'; '$'];
1583   fun x ->
1584     try Hashtbl.find ht x with
1585     [ Not_found -> try Hashtbl.find ct x.[0] with _ -> False ]
1586 };
1587
1588 (*** JRH added this so parenthesised operators undergo same mapping ***)
1589
1590 value translate_operator =
1591   fun s ->
1592    match s with
1593     [ "THEN" -> "then_"
1594     | "THENC" -> "thenc_"
1595     | "THENL" -> "thenl_"
1596     | "ORELSE" -> "orelse_"
1597     | "ORELSEC" -> "orelsec_"
1598     | "THEN_TCL" -> "then_tcl_"
1599     | "ORELSE_TCL" -> "orelse_tcl_"
1600     | "F_F" -> "f_f_"
1601     | _ -> s];
1602
1603 value operator_rparen =
1604   Grammar.Entry.of_parser gram "operator_rparen"
1605     (fun strm ->
1606        match Stream.npeek 2 strm with
1607        [ [("", s); ("", ")")] when is_operator s -> do {
1608            Stream.junk strm;
1609            Stream.junk strm;
1610            translate_operator s
1611          }
1612        | _ -> raise Stream.Failure ])
1613 ;
1614
1615 value check_not_part_of_patt =
1616   Grammar.Entry.of_parser gram "check_not_part_of_patt"
1617     (fun strm ->
1618        let tok =
1619          match Stream.npeek 4 strm with
1620          [ [("LIDENT", _); tok :: _] -> tok
1621          | [("", "("); ("", s); ("", ")"); tok] when is_operator s -> tok
1622          | _ -> raise Stream.Failure ]
1623        in
1624        match tok with
1625        [ ("", "," | "as" | "|" | "::") -> raise Stream.Failure
1626        | _ -> () ])
1627 ;
1628
1629 value symbolchar =
1630   let list =
1631     ['!'; '$'; '%'; '&'; '*'; '+'; '-'; '.'; '/'; ':'; '<'; '='; '>'; '?';
1632      '@'; '^'; '|'; '~']
1633   in
1634   loop where rec loop s i =
1635     if i == String.length s then True
1636     else if List.mem s.[i] list then loop s (i + 1)
1637     else False
1638 ;
1639
1640 value prefixop =
1641   let list = ['!'; '?'; '~'] in
1642   let excl = ["!="; "??"; "?!"] in
1643   Grammar.Entry.of_parser gram "prefixop"
1644     (parser
1645        [: `("", x)
1646            when
1647              not (List.mem x excl) && String.length x >= 2 &&
1648              List.mem x.[0] list && symbolchar x 1 :] ->
1649          x)
1650 ;
1651
1652 value infixop0 =
1653   let list = ['='; '<'; '>'; '|'; '&'; '$'] in
1654   let excl = ["<-"; "||"; "&&"] in
1655   Grammar.Entry.of_parser gram "infixop0"
1656     (parser
1657        [: `("", x)
1658            when
1659              not (List.mem x excl) && (x = "$" || String.length x >= 2) &&
1660              List.mem x.[0] list && symbolchar x 1 :] ->
1661          x)
1662 ;
1663
1664 value infixop1 =
1665   let list = ['@'; '^'] in
1666   Grammar.Entry.of_parser gram "infixop1"
1667     (parser
1668        [: `("", x)
1669            when
1670              String.length x >= 2 && List.mem x.[0] list &&
1671              symbolchar x 1 :] ->
1672          x)
1673 ;
1674
1675 value infixop2 =
1676   let list = ['+'; '-'] in
1677   Grammar.Entry.of_parser gram "infixop2"
1678     (parser
1679        [: `("", x)
1680            when
1681              x <> "->" && String.length x >= 2 && List.mem x.[0] list &&
1682              symbolchar x 1 :] ->
1683          x)
1684 ;
1685
1686 value infixop3 =
1687   let list = ['*'; '/'; '%'] in
1688   Grammar.Entry.of_parser gram "infixop3"
1689     (parser
1690        [: `("", x)
1691            when
1692              String.length x >= 2 && List.mem x.[0] list &&
1693              symbolchar x 1 :] ->
1694          x)
1695 ;
1696
1697 value infixop4 =
1698   Grammar.Entry.of_parser gram "infixop4"
1699     (parser
1700        [: `("", x)
1701            when
1702              String.length x >= 3 && x.[0] == '*' && x.[1] == '*' &&
1703              symbolchar x 2 :] ->
1704          x)
1705 ;
1706
1707 value test_constr_decl =
1708   Grammar.Entry.of_parser gram "test_constr_decl"
1709     (fun strm ->
1710        match Stream.npeek 1 strm with
1711        [ [("UIDENT", _)] ->
1712            match Stream.npeek 2 strm with
1713            [ [_; ("", ".")] -> raise Stream.Failure
1714            | [_; ("", "(")] -> raise Stream.Failure
1715            | [_ :: _] -> ()
1716            | _ -> raise Stream.Failure ]
1717        | [("", "|")] -> ()
1718        | _ -> raise Stream.Failure ])
1719 ;
1720
1721 value stream_peek_nth n strm =
1722   loop n (Stream.npeek n strm) where rec loop n =
1723     fun
1724     [ [] -> None
1725     | [x] -> if n == 1 then Some x else None
1726     | [_ :: l] -> loop (n - 1) l ]
1727 ;
1728
1729 (* horrible hack to be able to parse class_types *)
1730
1731 value test_ctyp_minusgreater =
1732   Grammar.Entry.of_parser gram "test_ctyp_minusgreater"
1733     (fun strm ->
1734        let rec skip_simple_ctyp n =
1735          match stream_peek_nth n strm with
1736          [ Some ("", "->") -> n
1737          | Some ("", "[" | "[<") ->
1738              skip_simple_ctyp (ignore_upto "]" (n + 1) + 1)
1739          | Some ("", "(") -> skip_simple_ctyp (ignore_upto ")" (n + 1) + 1)
1740          | Some
1741              ("",
1742               "as" | "'" | ":" | "*" | "." | "#" | "<" | ">" | ".." | ";" |
1743               "_") ->
1744              skip_simple_ctyp (n + 1)
1745          | Some ("QUESTIONIDENT" | "LIDENT" | "UIDENT", _) ->
1746              skip_simple_ctyp (n + 1)
1747          | Some _ | None -> raise Stream.Failure ]
1748        and ignore_upto end_kwd n =
1749          match stream_peek_nth n strm with
1750          [ Some ("", prm) when prm = end_kwd -> n
1751          | Some ("", "[" | "[<") ->
1752              ignore_upto end_kwd (ignore_upto "]" (n + 1) + 1)
1753          | Some ("", "(") -> ignore_upto end_kwd (ignore_upto ")" (n + 1) + 1)
1754          | Some _ -> ignore_upto end_kwd (n + 1)
1755          | None -> raise Stream.Failure ]
1756        in
1757        match Stream.peek strm with
1758        [ Some (("", "[") | ("LIDENT" | "UIDENT", _)) -> skip_simple_ctyp 1
1759        | Some ("", "object") -> raise Stream.Failure
1760        | _ -> 1 ])
1761 ;
1762
1763 value test_label_eq =
1764   Grammar.Entry.of_parser gram "test_label_eq"
1765     (test 1 where rec test lev strm =
1766        match stream_peek_nth lev strm with
1767        [ Some (("UIDENT", _) | ("LIDENT", _) | ("", ".")) ->
1768            test (lev + 1) strm
1769        | Some ("ANTIQUOT_LOC", _) -> ()
1770        | Some ("", "=") -> ()
1771        | _ -> raise Stream.Failure ])
1772 ;
1773
1774 value test_typevar_list_dot =
1775   Grammar.Entry.of_parser gram "test_typevar_list_dot"
1776     (let rec test lev strm =
1777        match stream_peek_nth lev strm with
1778        [ Some ("", "'") -> test2 (lev + 1) strm
1779        | Some ("", ".") -> ()
1780        | _ -> raise Stream.Failure ]
1781      and test2 lev strm =
1782        match stream_peek_nth lev strm with
1783        [ Some ("UIDENT" | "LIDENT", _) -> test (lev + 1) strm
1784        | _ -> raise Stream.Failure ]
1785      in
1786      test 1)
1787 ;
1788
1789 value e_phony =
1790   Grammar.Entry.of_parser gram "e_phony"
1791     (parser [])
1792 ;
1793 value p_phony =
1794   Grammar.Entry.of_parser gram "p_phony"
1795     (parser [])
1796 ;
1797
1798 value constr_arity = ref [("Some", 1); ("Match_Failure", 1)];
1799
1800 value rec is_expr_constr_call =
1801   fun
1802   [ <:expr< $uid:_$ >> -> True
1803   | <:expr< $uid:_$.$e$ >> -> is_expr_constr_call e
1804   | <:expr< $e$ $_$ >> -> is_expr_constr_call e
1805   | _ -> False ]
1806 ;
1807
1808 value rec constr_expr_arity loc =
1809   fun
1810   [ <:expr< $uid:c$ >> ->
1811       try List.assoc c constr_arity.val with [ Not_found -> 0 ]
1812   | <:expr< $uid:_$.$e$ >> -> constr_expr_arity loc e
1813   | _ -> 1 ]
1814 ;
1815
1816 value rec constr_patt_arity loc =
1817   fun
1818   [ <:patt< $uid:c$ >> ->
1819       try List.assoc c constr_arity.val with [ Not_found -> 0 ]
1820   | <:patt< $uid:_$.$p$ >> -> constr_patt_arity loc p
1821   | _ -> 1 ]
1822 ;
1823
1824 value get_seq =
1825   fun
1826   [ <:expr< do { $list:el$ } >> -> el
1827   | e -> [e] ]
1828 ;
1829
1830 value mem_tvar s tpl =
1831   List.exists (fun (t, _) -> Pcaml.unvala t = Some s) tpl
1832 ;
1833
1834 value choose_tvar tpl =
1835   let rec find_alpha v =
1836     let s = String.make 1 v in
1837     if mem_tvar s tpl then
1838       if v = 'z' then None else find_alpha (Char.chr (Char.code v + 1))
1839     else Some (String.make 1 v)
1840   in
1841   let rec make_n n =
1842     let v = "a" ^ string_of_int n in
1843     if mem_tvar v tpl then make_n (succ n) else v
1844   in
1845   match find_alpha 'a' with
1846   [ Some x -> x
1847   | None -> make_n 1 ]
1848 ;
1849
1850 value quotation_content s = do {
1851   loop 0 where rec loop i =
1852     if i = String.length s then ("", s)
1853     else if s.[i] = ':' || s.[i] = '@' then
1854       let i = i + 1 in
1855       (String.sub s 0 i, String.sub s i (String.length s - i))
1856     else loop (i + 1)
1857 };
1858
1859 value concat_comm loc e =
1860   let loc =
1861     Ploc.with_comment loc
1862       (Ploc.comment loc ^ Ploc.comment (MLast.loc_of_expr e))
1863   in
1864   let floc =
1865     let first = ref True in
1866     fun loc1 ->
1867       if first.val then do {first.val := False; loc}
1868       else loc1
1869   in
1870   reloc_expr floc 0 e
1871 ;
1872
1873 EXTEND
1874   GLOBAL: sig_item str_item ctyp patt expr module_type module_expr
1875     signature structure class_type class_expr class_sig_item class_str_item
1876     let_binding type_decl constructor_declaration label_declaration
1877     match_case with_constr poly_variant;
1878   module_expr:
1879     [ [ "functor"; "("; i = V UIDENT "uid" ""; ":"; t = module_type; ")";
1880         "->"; me = SELF ->
1881           <:module_expr< functor ( $_uid:i$ : $t$ ) -> $me$ >>
1882       | "struct"; st = structure; "end" ->
1883           <:module_expr< struct $_list:st$ end >> ]
1884     | [ me1 = SELF; "."; me2 = SELF -> <:module_expr< $me1$ . $me2$ >> ]
1885     | [ me1 = SELF; "("; me2 = SELF; ")" -> <:module_expr< $me1$ $me2$ >> ]
1886     | [ i = mod_expr_ident -> i
1887       | "("; "val"; e = expr; ":"; mt = module_type; ")" ->
1888          <:module_expr< (value $e$ : $mt$) >>
1889       | "("; "val"; e = expr; ")" ->
1890          <:module_expr< (value $e$) >>
1891       | "("; me = SELF; ":"; mt = module_type; ")" ->
1892           <:module_expr< ( $me$ : $mt$ ) >>
1893       | "("; me = SELF; ")" -> <:module_expr< $me$ >> ] ]
1894   ;
1895   structure:
1896     [ [ st = V (LIST0 [ s = str_item; OPT ";;" -> s ]) -> st ] ]
1897   ;
1898   mod_expr_ident:
1899     [ LEFTA
1900       [ i = SELF; "."; j = SELF -> <:module_expr< $i$ . $j$ >> ]
1901     | [ i = V UIDENT -> <:module_expr< $_uid:i$ >> ] ]
1902   ;
1903   str_item:
1904     [ "top"
1905       [ "exception"; (_, c, tl, _) = constructor_declaration;
1906         b = rebind_exn ->
1907           <:str_item< exception $_uid:c$ of $_list:tl$ = $_list:b$ >>
1908       | "external"; i = V LIDENT "lid" ""; ":"; t = ctyp; "=";
1909         pd = V (LIST1 STRING) ->
1910           <:str_item< external $_lid:i$ : $t$ = $_list:pd$ >>
1911       | "external"; "("; i = operator_rparen; ":"; t = ctyp; "=";
1912         pd = V (LIST1 STRING) ->
1913           <:str_item< external $lid:i$ : $t$ = $_list:pd$ >>
1914       | "include"; me = module_expr -> <:str_item< include $me$ >>
1915       | "module"; r = V (FLAG "rec"); l = V (LIST1 mod_binding SEP "and") ->
1916           <:str_item< module $_flag:r$ $_list:l$ >>
1917       | "module"; "type"; i = V UIDENT "uid" ""; "="; mt = module_type ->
1918           <:str_item< module type $_uid:i$ = $mt$ >>
1919       | "open"; i = V mod_ident "list" "" ->
1920           <:str_item< open $_:i$ >>
1921       | "type"; tdl = V (LIST1 type_decl SEP "and") ->
1922           <:str_item< type $_list:tdl$ >>
1923       | "let"; r = V (FLAG "rec"); l = V (LIST1 let_binding SEP "and"); "in";
1924         x = expr ->
1925           let e = <:expr< let $_flag:r$ $_list:l$ in $x$ >> in
1926           <:str_item< $exp:e$ >>
1927       | "let"; r = V (FLAG "rec"); l = V (LIST1 let_binding SEP "and") ->
1928           match l with
1929           [ <:vala< [(p, e)] >> ->
1930               match p with
1931               [ <:patt< _ >> -> <:str_item< $exp:e$ >>
1932               | _ -> <:str_item< value $_flag:r$ $_list:l$ >> ]
1933           | _ -> <:str_item< value $_flag:r$ $_list:l$ >> ]
1934       | "let"; "module"; m = V UIDENT; mb = mod_fun_binding; "in"; e = expr ->
1935           <:str_item< let module $_uid:m$ = $mb$ in $e$ >>
1936       | e = expr -> <:str_item< $exp:e$ >> ] ]
1937   ;
1938   rebind_exn:
1939     [ [ "="; sl = V mod_ident "list" -> sl
1940       | -> <:vala< [] >> ] ]
1941   ;
1942   mod_binding:
1943     [ [ i = V UIDENT; me = mod_fun_binding -> (i, me) ] ]
1944   ;
1945   mod_fun_binding:
1946     [ RIGHTA
1947       [ "("; m = UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
1948           <:module_expr< functor ( $uid:m$ : $mt$ ) -> $mb$ >>
1949       | ":"; mt = module_type; "="; me = module_expr ->
1950           <:module_expr< ( $me$ : $mt$ ) >>
1951       | "="; me = module_expr -> <:module_expr< $me$ >> ] ]
1952   ;
1953   (* Module types *)
1954   module_type:
1955     [ [ "functor"; "("; i = V UIDENT "uid" ""; ":"; t = SELF; ")"; "->";
1956         mt = SELF ->
1957           <:module_type< functor ( $_uid:i$ : $t$ ) -> $mt$ >> ]
1958     | [ mt = SELF; "with"; wcl = V (LIST1 with_constr SEP "and") ->
1959           <:module_type< $mt$ with $_list:wcl$ >> ]
1960     | [ "sig"; sg = signature; "end" ->
1961           <:module_type< sig $_list:sg$ end >>
1962       | "module"; "type"; "of"; me = module_expr ->
1963           <:module_type< module type of $me$ >>
1964       | i = mod_type_ident -> i
1965       | "("; mt = SELF; ")" -> <:module_type< $mt$ >> ] ]
1966   ;
1967   signature:
1968     [ [ sg = V (LIST0 [ s = sig_item; OPT ";;" -> s ]) -> sg ] ]
1969   ;
1970   mod_type_ident:
1971     [ LEFTA
1972       [ m1 = SELF; "."; m2 = SELF -> <:module_type< $m1$ . $m2$ >>
1973       | m1 = SELF; "("; m2 = SELF; ")" -> <:module_type< $m1$ $m2$ >> ]
1974     | [ m = V UIDENT -> <:module_type< $_uid:m$ >>
1975       | m = V LIDENT -> <:module_type< $_lid:m$ >> ] ]
1976   ;
1977   sig_item:
1978     [ "top"
1979       [ "exception"; (_, c, tl, _) = constructor_declaration ->
1980           <:sig_item< exception $_uid:c$ of $_list:tl$ >>
1981       | "external"; i = V LIDENT "lid" ""; ":"; t = ctyp; "=";
1982         pd = V (LIST1 STRING) ->
1983           <:sig_item< external $_lid:i$ : $t$ = $_list:pd$ >>
1984       | "external"; "("; i = operator_rparen; ":"; t = ctyp; "=";
1985         pd = V (LIST1 STRING) ->
1986           <:sig_item< external $lid:i$ : $t$ = $_list:pd$ >>
1987       | "include"; mt = module_type ->
1988           <:sig_item< include $mt$ >>
1989       | "module"; rf = V (FLAG "rec");
1990         l = V (LIST1 mod_decl_binding SEP "and") ->
1991           <:sig_item< module $_flag:rf$ $_list:l$ >>
1992       | "module"; "type"; i = V UIDENT "uid" ""; "="; mt = module_type ->
1993           <:sig_item< module type $_uid:i$ = $mt$ >>
1994       | "module"; "type"; i = V UIDENT "uid" "" ->
1995           <:sig_item< module type $_uid:i$ = 'abstract >>
1996       | "open"; i = V mod_ident "list" "" ->
1997           <:sig_item< open $_:i$ >>
1998       | "type"; tdl = V (LIST1 type_decl SEP "and") ->
1999           <:sig_item< type $_list:tdl$ >>
2000       | "val"; i = V LIDENT "lid" ""; ":"; t = ctyp ->
2001           <:sig_item< value $_lid:i$ : $t$ >>
2002       | "val"; "("; i = operator_rparen; ":"; t = ctyp ->
2003           <:sig_item< value $lid:i$ : $t$ >> ] ]
2004   ;
2005   mod_decl_binding:
2006     [ [ i = V UIDENT; mt = module_declaration -> (i, mt) ] ]
2007   ;
2008   module_declaration:
2009     [ RIGHTA
2010       [ ":"; mt = module_type -> <:module_type< $mt$ >>
2011       | "("; i = UIDENT; ":"; t = module_type; ")"; mt = SELF ->
2012           <:module_type< functor ( $uid:i$ : $t$ ) -> $mt$ >> ] ]
2013   ;
2014   (* "with" constraints (additional type equations over signature
2015      components) *)
2016   with_constr:
2017     [ [ "type"; tpl = V type_parameters "list"; i = V mod_ident ""; "=";
2018         pf = V (FLAG "private"); t = ctyp ->
2019           <:with_constr< type $_:i$ $_list:tpl$ = $_flag:pf$ $t$ >>
2020       | "type"; tpl = V type_parameters "list"; i = V mod_ident ""; ":=";
2021         t = ctyp ->
2022           <:with_constr< type $_:i$ $_list:tpl$ := $t$ >>
2023       | "module"; i = V mod_ident ""; "="; me = module_expr ->
2024           <:with_constr< module $_:i$ = $me$ >>
2025       | "module"; i = V mod_ident ""; ":="; me = module_expr ->
2026           <:with_constr< module $_:i$ := $me$ >> ] ]
2027   ;
2028   (* Core expressions *)
2029   expr:
2030     [ "top" RIGHTA
2031       [ e1 = SELF; ";"; e2 = SELF ->
2032           <:expr< do { $list:[e1 :: get_seq e2]$ } >>
2033       | e1 = SELF; ";" -> e1
2034       | el = V e_phony "list" -> <:expr< do { $_list:el$ } >> ]
2035     | "expr1"
2036       [ "let"; o = V (FLAG "rec"); l = V (LIST1 let_binding SEP "and"); "in";
2037         x = expr LEVEL "top" ->
2038           <:expr< let $_flag:o$ $_list:l$ in $x$ >>
2039       | "let"; "module"; m = V UIDENT; mb = mod_fun_binding; "in";
2040         e = expr LEVEL "top" ->
2041           <:expr< let module $_uid:m$ = $mb$ in $e$ >>
2042       | "function"; OPT "|"; l = V (LIST1 match_case SEP "|") ->
2043           <:expr< fun [ $_list:l$ ] >>
2044       | "fun"; p = patt LEVEL "simple"; (eo, e) = fun_def ->
2045           <:expr< fun [$p$ $opt:eo$ -> $e$] >>
2046       | "match"; e = SELF; "with"; OPT "|";
2047         l = V (LIST1 match_case SEP "|") ->
2048           <:expr< match $e$ with [ $_list:l$ ] >>
2049       | "try"; e = SELF; "with"; OPT "|"; l = V (LIST1 match_case SEP "|") ->
2050           <:expr< try $e$ with [ $_list:l$ ] >>
2051       | "if"; e1 = SELF; "then"; e2 = expr LEVEL "expr1"; "else";
2052         e3 = expr LEVEL "expr1" ->
2053           <:expr< if $e1$ then $e2$ else $e3$ >>
2054       | "if"; e1 = SELF; "then"; e2 = expr LEVEL "expr1" ->
2055           <:expr< if $e1$ then $e2$ else () >>
2056       | "for"; i = V LIDENT; "="; e1 = SELF; df = V direction_flag "to";
2057         e2 = SELF; "do"; e = V SELF "list"; "done" ->
2058           let el = Pcaml.vala_map get_seq e in
2059           <:expr< for $_lid:i$ = $e1$ $_to:df$ $e2$ do { $_list:el$ } >>
2060       | "while"; e1 = SELF; "do"; e2 = V SELF "list"; "done" ->
2061           let el = Pcaml.vala_map get_seq e2 in
2062           <:expr< while $e1$ do { $_list:el$ } >> ]
2063     | [ e = SELF; ","; el = LIST1 NEXT SEP "," ->
2064           <:expr< ( $list:[e :: el]$ ) >> ]
2065     | ":=" NONA
2066       [ e1 = SELF; ":="; e2 = expr LEVEL "expr1" ->
2067           <:expr< $e1$.val := $e2$ >>
2068       | e1 = SELF; "<-"; e2 = expr LEVEL "expr1" -> <:expr< $e1$ := $e2$ >> ]
2069     | "||" RIGHTA
2070       [ e1 = SELF; "or"; e2 = SELF -> <:expr< $lid:"or"$ $e1$ $e2$ >>
2071       | e1 = SELF; "||"; e2 = SELF -> <:expr< $e1$ || $e2$ >> ]
2072     | "&&" RIGHTA
2073       [ e1 = SELF; "&"; e2 = SELF -> <:expr< $lid:"&"$ $e1$ $e2$ >>
2074       | e1 = SELF; "&&"; e2 = SELF -> <:expr< $e1$ && $e2$ >> ]
2075     | "<" LEFTA
2076       [ e1 = SELF; "<"; e2 = SELF -> <:expr< $e1$ < $e2$ >>
2077       | e1 = SELF; ">"; e2 = SELF -> <:expr< $e1$ > $e2$ >>
2078       | e1 = SELF; "<="; e2 = SELF -> <:expr< $e1$ <= $e2$ >>
2079       | e1 = SELF; ">="; e2 = SELF -> <:expr< $e1$ >= $e2$ >>
2080       | e1 = SELF; "="; e2 = SELF -> <:expr< $e1$ = $e2$ >>
2081       | e1 = SELF; "<>"; e2 = SELF -> <:expr< $e1$ <> $e2$ >>
2082       | e1 = SELF; "=="; e2 = SELF -> <:expr< $e1$ == $e2$ >>
2083       | e1 = SELF; "!="; e2 = SELF -> <:expr< $e1$ != $e2$ >>
2084       | e1 = SELF; op = infixop0; e2 = SELF -> <:expr< $lid:op$ $e1$ $e2$ >> ]
2085     | "^" RIGHTA
2086       [ e1 = SELF; "^"; e2 = SELF -> <:expr< $e1$ ^ $e2$ >>
2087       | e1 = SELF; "@"; e2 = SELF -> <:expr< $e1$ @ $e2$ >>
2088       | e1 = SELF; op = infixop1; e2 = SELF -> <:expr< $lid:op$ $e1$ $e2$ >> ]
2089     | RIGHTA
2090       [ e1 = SELF; "::"; e2 = SELF -> <:expr< [$e1$ :: $e2$] >> ]
2091     | "+" LEFTA
2092       [ e1 = SELF; "+"; e2 = SELF -> <:expr< $e1$ + $e2$ >>
2093       | e1 = SELF; "-"; e2 = SELF -> <:expr< $e1$ - $e2$ >>
2094       | e1 = SELF; op = infixop2; e2 = SELF -> <:expr< $lid:op$ $e1$ $e2$ >> ]
2095     | "*" LEFTA
2096       [ e1 = SELF; "*"; e2 = SELF -> <:expr< $e1$ * $e2$ >>
2097       | e1 = SELF; "/"; e2 = SELF -> <:expr< $e1$ / $e2$ >>
2098       | e1 = SELF; "%"; e2 = SELF -> <:expr< $lid:"%"$ $e1$ $e2$ >>
2099       | e1 = SELF; "land"; e2 = SELF -> <:expr< $e1$ land $e2$ >>
2100       | e1 = SELF; "lor"; e2 = SELF -> <:expr< $e1$ lor $e2$ >>
2101       | e1 = SELF; "lxor"; e2 = SELF -> <:expr< $e1$ lxor $e2$ >>
2102       | e1 = SELF; "mod"; e2 = SELF -> <:expr< $e1$ mod $e2$ >>
2103       | e1 = SELF; op = infixop3; e2 = SELF -> <:expr< $lid:op$ $e1$ $e2$ >> ]
2104     | "**" RIGHTA
2105       [ e1 = SELF; "**"; e2 = SELF -> <:expr< $e1$ ** $e2$ >>
2106       | e1 = SELF; "asr"; e2 = SELF -> <:expr< $e1$ asr $e2$ >>
2107       | e1 = SELF; "lsl"; e2 = SELF -> <:expr< $e1$ lsl $e2$ >>
2108       | e1 = SELF; "lsr"; e2 = SELF -> <:expr< $e1$ lsr $e2$ >>
2109       | e1 = SELF; op = infixop4; e2 = SELF -> <:expr< $lid:op$ $e1$ $e2$ >> ]
2110     | "unary minus" NONA
2111       [ "-"; e = SELF -> <:expr< - $e$ >>
2112       | "-."; e = SELF -> <:expr< -. $e$ >> ]
2113     | "apply" LEFTA
2114       [ e1 = SELF; e2 = SELF ->
2115           let (e1, e2) =
2116             if is_expr_constr_call e1 then
2117               match e1 with
2118               [ <:expr< $e11$ $e12$ >> -> (e11, <:expr< $e12$ $e2$ >>)
2119               | _ -> (e1, e2) ]
2120             else (e1, e2)
2121           in
2122           match constr_expr_arity loc e1 with
2123           [ 1 -> <:expr< $e1$ $e2$ >>
2124           | _ ->
2125               match e2 with
2126               [ <:expr< ( $list:el$ ) >> ->
2127                   List.fold_left (fun e1 e2 -> <:expr< $e1$ $e2$ >>) e1 el
2128               | _ -> <:expr< $e1$ $e2$ >> ] ]
2129       | "assert"; e = SELF -> <:expr< assert $e$ >>
2130       | "lazy"; e = SELF -> <:expr< lazy ($e$) >> ]
2131     | "." LEFTA
2132       [ e1 = SELF; "."; "("; op = operator_rparen ->
2133           <:expr< $e1$ .( $lid:op$ ) >>
2134       | e1 = SELF; "."; "("; e2 = SELF; ")" ->
2135           <:expr< $e1$ .( $e2$ ) >>
2136       | e1 = SELF; "."; "["; e2 = SELF; "]" -> <:expr< $e1$ .[ $e2$ ] >>
2137       | e = SELF; "."; "{"; el = V (LIST1 expr LEVEL "+" SEP ","); "}" ->
2138           <:expr< $e$ .{ $_list:el$ } >>
2139       | e1 = SELF; "."; e2 = SELF ->
2140           let rec loop m =
2141             fun
2142             [ <:expr< $x$ . $y$ >> -> loop <:expr< $m$ . $x$ >> y
2143             | e -> <:expr< $m$ . $e$ >> ]
2144           in
2145           loop e1 e2 ]
2146     | "~-" NONA
2147       [ "!"; e = SELF -> <:expr< $e$ . val >>
2148       | "~-"; e = SELF -> <:expr< ~- $e$ >>
2149       | "~-."; e = SELF -> <:expr< ~-. $e$ >>
2150       | f = prefixop; e = SELF -> <:expr< $lid:f$ $e$ >> ]
2151     | "simple" LEFTA
2152       [ s = V INT -> <:expr< $_int:s$ >>
2153       | s = V INT_l -> <:expr< $_int32:s$ >>
2154       | s = V INT_L -> <:expr< $_int64:s$ >>
2155       | s = V INT_n -> <:expr< $_nativeint:s$ >>
2156       | s = V FLOAT -> <:expr< $_flo:s$ >>
2157       | s = V STRING -> <:expr< $_str:s$ >>
2158       | c = V CHAR -> <:expr< $_chr:c$ >>
2159       | UIDENT "True" -> <:expr< True_ >>
2160       | UIDENT "False" -> <:expr< False_ >>
2161       | i = expr_ident -> i
2162       | "false" -> <:expr< False >>
2163       | "true" -> <:expr< True >>
2164       | "["; "]" -> <:expr< [] >>
2165       | "["; el = expr1_semi_list; "]" -> <:expr< $mklistexp loc None el$ >>
2166       | "[|"; "|]" -> <:expr< [| |] >>
2167       | "[|"; el = V expr1_semi_list "list"; "|]" ->
2168           <:expr< [| $_list:el$ |] >>
2169       | "{"; test_label_eq; lel = V lbl_expr_list "list"; "}" ->
2170           <:expr< { $_list:lel$ } >>
2171       | "{"; e = expr LEVEL "."; "with"; lel = V lbl_expr_list "list"; "}" ->
2172           <:expr< { ($e$) with $_list:lel$ } >>
2173       | "("; ")" -> <:expr< () >>
2174       | "("; "module"; me = module_expr; ":"; mt = module_type; ")" ->
2175           <:expr< (module $me$ : $mt$) >>
2176       | "("; "module"; me = module_expr; ")" ->
2177           <:expr< (module $me$) >>
2178       | "("; op = operator_rparen -> <:expr< $lid:op$ >>
2179       | "("; el = V e_phony "list"; ")" -> <:expr< ($_list:el$) >>
2180       | "("; e = SELF; ":"; t = ctyp; ")" -> <:expr< ($e$ : $t$) >>
2181       | "("; e = SELF; ")" -> concat_comm loc <:expr< $e$ >>
2182       | "begin"; e = SELF; "end" -> concat_comm loc <:expr< $e$ >>
2183       | "begin"; "end" -> <:expr< () >>
2184       | x = QUOTATION ->
2185           let con = quotation_content x in
2186           Pcaml.handle_expr_quotation loc con ] ]
2187   ;
2188   let_binding:
2189     [ [ p = val_ident; e = fun_binding -> (p, e)
2190       | p = patt; "="; e = expr -> (p, e)
2191       | p = patt; ":"; t = poly_type; "="; e = expr ->
2192           (<:patt< ($p$ : $t$) >>, e) ] ]
2193   ;
2194 (*** JRH added the "translate_operator" here ***)
2195   val_ident:
2196     [ [ check_not_part_of_patt; s = LIDENT -> <:patt< $lid:s$ >>
2197       | check_not_part_of_patt; "("; s = ANY; ")" ->
2198            let s' = translate_operator s in <:patt< $lid:s'$ >> ] ]
2199   ;
2200   fun_binding:
2201     [ RIGHTA
2202       [ p = patt LEVEL "simple"; e = SELF -> <:expr< fun $p$ -> $e$ >>
2203       | "="; e = expr -> <:expr< $e$ >>
2204       | ":"; t = poly_type; "="; e = expr -> <:expr< ($e$ : $t$) >> ] ]
2205   ;
2206   match_case:
2207     [ [ x1 = patt; w = V (OPT [ "when"; e = expr -> e ]); "->"; x2 = expr ->
2208           (x1, w, x2) ] ]
2209   ;
2210   lbl_expr_list:
2211     [ [ le = lbl_expr; ";"; lel = SELF -> [le :: lel]
2212       | le = lbl_expr; ";" -> [le]
2213       | le = lbl_expr -> [le] ] ]
2214   ;
2215   lbl_expr:
2216     [ [ i = patt_label_ident; "="; e = expr LEVEL "expr1" -> (i, e) ] ]
2217   ;
2218   expr1_semi_list:
2219     [ [ el = LIST1 (expr LEVEL "expr1") SEP ";" OPT_SEP -> el ] ]
2220   ;
2221   fun_def:
2222     [ RIGHTA
2223       [ p = patt LEVEL "simple"; (eo, e) = SELF ->
2224           (None, <:expr< fun [ $p$ $opt:eo$ -> $e$ ] >>)
2225       | eo = OPT [ "when"; e = expr -> e ]; "->"; e = expr ->
2226           (eo, <:expr< $e$ >>) ] ]
2227   ;
2228   expr_ident:
2229     [ RIGHTA
2230       [ i = V LIDENT -> <:expr< $_lid:i$ >>
2231       | i = V UIDENT -> <:expr< $_uid:i$ >>
2232       | i = V UIDENT; "."; j = SELF ->
2233           let rec loop m =
2234             fun
2235             [ <:expr< $x$ . $y$ >> -> loop <:expr< $m$ . $x$ >> y
2236             | e -> <:expr< $m$ . $e$ >> ]
2237           in
2238           loop <:expr< $_uid:i$ >> j
2239       | i = V UIDENT; "."; "("; j = operator_rparen ->
2240           <:expr< $_uid:i$ . $lid:j$ >> ] ]
2241   ;
2242   (* Patterns *)
2243   patt:
2244     [ LEFTA
2245       [ p1 = SELF; "as"; i = LIDENT -> <:patt< ($p1$ as $lid:i$) >> ]
2246     | LEFTA
2247       [ p1 = SELF; "|"; p2 = SELF -> <:patt< $p1$ | $p2$ >> ]
2248     | [ p = SELF; ","; pl = LIST1 NEXT SEP "," ->
2249           <:patt< ( $list:[p :: pl]$) >> ]
2250     | NONA
2251       [ p1 = SELF; ".."; p2 = SELF -> <:patt< $p1$ .. $p2$ >> ]
2252     | RIGHTA
2253       [ p1 = SELF; "::"; p2 = SELF -> <:patt< [$p1$ :: $p2$] >> ]
2254     | LEFTA
2255       [ p1 = SELF; p2 = SELF ->
2256           let (p1, p2) =
2257             match p1 with
2258             [ <:patt< $p11$ $p12$ >> -> (p11, <:patt< $p12$ $p2$ >>)
2259             | _ -> (p1, p2) ]
2260           in
2261           match constr_patt_arity loc p1 with
2262           [ 1 -> <:patt< $p1$ $p2$ >>
2263           | n ->
2264               let p2 =
2265                 match p2 with
2266                 [ <:patt< _ >> when n > 1 ->
2267                     let pl =
2268                       loop n where rec loop n =
2269                         if n = 0 then [] else [<:patt< _ >> :: loop (n - 1)]
2270                     in
2271                     <:patt< ( $list:pl$ ) >>
2272                 | _ -> p2 ]
2273               in
2274               match p2 with
2275               [ <:patt< ( $list:pl$ ) >> ->
2276                   List.fold_left (fun p1 p2 -> <:patt< $p1$ $p2$ >>) p1 pl
2277               | _ -> <:patt< $p1$ $p2$ >> ] ]
2278       | "lazy"; p = SELF -> <:patt< lazy $p$ >> ]
2279     | LEFTA
2280       [ p1 = SELF; "."; p2 = SELF -> <:patt< $p1$ . $p2$ >> ]
2281     | "simple"
2282       [ s = V LIDENT -> <:patt< $_lid:s$ >>
2283       | s = V UIDENT -> <:patt< $_uid:s$ >>
2284       | s = V INT -> <:patt< $_int:s$ >>
2285       | s = V INT_l -> <:patt< $_int32:s$ >>
2286       | s = V INT_L -> <:patt< $_int64:s$ >>
2287       | s = V INT_n -> <:patt< $_nativeint:s$ >>
2288       | "-"; s = INT -> <:patt< $int:"-" ^ s$ >>
2289       | "-"; s = FLOAT -> <:patt< $flo:"-" ^ s$ >>
2290       | s = V FLOAT -> <:patt< $_flo:s$ >>
2291       | s = V STRING -> <:patt< $_str:s$ >>
2292       | s = V CHAR -> <:patt< $_chr:s$ >>
2293       | UIDENT "True" -> <:patt< True_ >>
2294       | UIDENT "False" -> <:patt< False_ >>
2295       | "false" -> <:patt< False >>
2296       | "true" -> <:patt< True >>
2297       | "["; "]" -> <:patt< [] >>
2298       | "["; pl = patt_semi_list; "]" -> <:patt< $mklistpat loc None pl$ >>
2299       | "[|"; "|]" -> <:patt< [| |] >>
2300       | "[|"; pl = V patt_semi_list "list"; "|]" ->
2301           <:patt< [| $_list:pl$ |] >>
2302       | "{"; lpl = V lbl_patt_list "list"; "}" ->
2303           <:patt< { $_list:lpl$ } >>
2304       | "("; ")" -> <:patt< () >>
2305       | "("; op = operator_rparen -> <:patt< $lid:op$ >>
2306       | "("; pl = V p_phony "list"; ")" -> <:patt< ($_list:pl$) >>
2307       | "("; p = SELF; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >>
2308       | "("; p = SELF; ")" -> <:patt< $p$ >>
2309       | "("; "type"; s = V LIDENT; ")" -> <:patt< (type $_lid:s$) >>
2310       | "("; "module"; s = V UIDENT; ":"; mt = module_type; ")" ->
2311           <:patt< (module $_uid:s$ : $mt$) >>
2312       | "("; "module"; s = V UIDENT; ")" ->
2313           <:patt< (module $_uid:s$) >>
2314       | "_" -> <:patt< _ >>
2315       | x = QUOTATION ->
2316           let con = quotation_content x in
2317           Pcaml.handle_patt_quotation loc con ] ]
2318   ;
2319   patt_semi_list:
2320     [ [ p = patt; ";"; pl = SELF -> [p :: pl]
2321       | p = patt; ";" -> [p]
2322       | p = patt -> [p] ] ]
2323   ;
2324   lbl_patt_list:
2325     [ [ le = lbl_patt; ";"; lel = SELF -> [le :: lel]
2326       | le = lbl_patt; ";" -> [le]
2327       | le = lbl_patt -> [le] ] ]
2328   ;
2329   lbl_patt:
2330     [ [ i = patt_label_ident; "="; p = patt -> (i, p) ] ]
2331   ;
2332   patt_label_ident:
2333     [ LEFTA
2334       [ p1 = SELF; "."; p2 = SELF -> <:patt< $p1$ . $p2$ >> ]
2335     | RIGHTA
2336       [ i = UIDENT -> <:patt< $uid:i$ >>
2337       | i = LIDENT -> <:patt< $lid:i$ >> ] ]
2338   ;
2339   (* Type declaration *)
2340   type_decl:
2341     [ [ tpl = type_parameters; n = V type_patt; "="; pf = V (FLAG "private");
2342         tk = type_kind; cl = V (LIST0 constrain) ->
2343           <:type_decl< $_tp:n$ $list:tpl$ = $_priv:pf$ $tk$ $_list:cl$ >>
2344       | tpl = type_parameters; n = V type_patt; cl = V (LIST0 constrain) ->
2345           let tk = <:ctyp< '$choose_tvar tpl$ >> in
2346           <:type_decl< $_tp:n$ $list:tpl$ = $tk$ $_list:cl$ >> ] ]
2347   ;
2348   type_patt:
2349     [ [ n = V LIDENT -> (loc, n) ] ]
2350   ;
2351   constrain:
2352     [ [ "constraint"; t1 = ctyp; "="; t2 = ctyp -> (t1, t2) ] ]
2353   ;
2354   type_kind:
2355     [ [ test_constr_decl; OPT "|";
2356         cdl = LIST1 constructor_declaration SEP "|" ->
2357           <:ctyp< [ $list:cdl$ ] >>
2358       | t = ctyp ->
2359           <:ctyp< $t$ >>
2360       | t = ctyp; "="; pf = FLAG "private"; "{";
2361         ldl = V label_declarations "list"; "}" ->
2362           <:ctyp< $t$ == $priv:pf$ { $_list:ldl$ } >>
2363       | t = ctyp; "="; pf = FLAG "private"; OPT "|";
2364         cdl = LIST1 constructor_declaration SEP "|" ->
2365           <:ctyp< $t$ == $priv:pf$ [ $list:cdl$ ] >>
2366       | "{"; ldl = V label_declarations "list"; "}" ->
2367           <:ctyp< { $_list:ldl$ } >> ] ]
2368   ;
2369   type_parameters:
2370     [ [ -> (* empty *) []
2371       | tp = type_parameter -> [tp]
2372       | "("; tpl = LIST1 type_parameter SEP ","; ")" -> tpl ] ]
2373   ;
2374   type_parameter:
2375     [ [ "+"; p = V simple_type_parameter -> (p, Some True)
2376       | "-"; p = V simple_type_parameter -> (p, Some False)
2377       | p = V simple_type_parameter -> (p, None) ] ]
2378   ;
2379   simple_type_parameter:
2380     [ [ "'"; i = ident -> Some i
2381       | "_" -> None ] ]
2382   ;
2383   constructor_declaration:
2384     [ [ ci = cons_ident; "of"; cal = V (LIST1 (ctyp LEVEL "apply") SEP "*") ->
2385           (loc, ci, cal, None)
2386       | ci = cons_ident; ":"; cal = V (LIST1 (ctyp LEVEL "apply") SEP "*");
2387         "->"; t = ctyp ->
2388           (loc, ci, cal, Some t)
2389       | ci = cons_ident; ":"; cal = V (LIST1 (ctyp LEVEL "apply") SEP "*") ->
2390           let t =
2391             match cal with
2392             [ <:vala< [t] >> -> t
2393             | <:vala< [t :: tl] >> -> <:ctyp< ($list:[t :: tl]$) >>
2394             | _ -> assert False ]
2395           in
2396           (loc, ci, <:vala< [] >>, Some t)
2397       | ci = cons_ident -> (loc, ci, <:vala< [] >>, None) ] ]
2398   ;
2399   cons_ident:
2400     [ [ i = V UIDENT "uid" "" -> i
2401       | UIDENT "True" -> <:vala< "True_" >>
2402       | UIDENT "False" -> <:vala< "False_" >> ] ]
2403   ;
2404   label_declarations:
2405     [ [ ld = label_declaration; ";"; ldl = SELF -> [ld :: ldl]
2406       | ld = label_declaration; ";" -> [ld]
2407       | ld = label_declaration -> [ld] ] ]
2408   ;
2409   label_declaration:
2410     [ [ i = LIDENT; ":"; t = poly_type -> (loc, i, False, t)
2411       | "mutable"; i = LIDENT; ":"; t = poly_type -> (loc, i, True, t) ] ]
2412   ;
2413   (* Core types *)
2414   ctyp:
2415     [ [ t1 = SELF; "as"; "'"; i = ident -> <:ctyp< $t1$ as '$i$ >> ]
2416     | "arrow" RIGHTA
2417       [ t1 = SELF; "->"; t2 = SELF -> <:ctyp< $t1$ -> $t2$ >> ]
2418     | "star"
2419       [ t = SELF; "*"; tl = LIST1 (ctyp LEVEL "apply") SEP "*" ->
2420           <:ctyp< ( $list:[t :: tl]$ ) >> ]
2421     | "apply"
2422       [ t1 = SELF; t2 = SELF -> <:ctyp< $t2$ $t1$ >> ]
2423     | "ctyp2"
2424       [ t1 = SELF; "."; t2 = SELF -> <:ctyp< $t1$ . $t2$ >>
2425       | t1 = SELF; "("; t2 = SELF; ")" -> <:ctyp< $t1$ $t2$ >> ]
2426     | "simple"
2427       [ "'"; i = V ident "" -> <:ctyp< '$_:i$ >>
2428       | "_" -> <:ctyp< _ >>
2429       | i = V LIDENT -> <:ctyp< $_lid:i$ >>
2430       | i = V UIDENT -> <:ctyp< $_uid:i$ >>
2431       | "("; "module"; mt = module_type; ")" -> <:ctyp< module $mt$ >>
2432       | "("; t = SELF; ","; tl = LIST1 ctyp SEP ","; ")";
2433         i = ctyp LEVEL "ctyp2" ->
2434           List.fold_left (fun c a -> <:ctyp< $c$ $a$ >>) i [t :: tl]
2435       | "("; t = SELF; ")" -> <:ctyp< $t$ >> ] ]
2436   ;
2437   (* Identifiers *)
2438   ident:
2439     [ [ i = LIDENT -> i
2440       | i = UIDENT -> i ] ]
2441   ;
2442   mod_ident:
2443     [ RIGHTA
2444       [ i = UIDENT -> [i]
2445       | i = LIDENT -> [i]
2446       | i = UIDENT; "."; j = SELF -> [i :: j] ] ]
2447   ;
2448   (* Miscellaneous *)
2449   direction_flag:
2450     [ [ "to" -> True
2451       | "downto" -> False ] ]
2452   ;
2453   (* Objects and Classes *)
2454   str_item:
2455     [ [ "class"; cd = V (LIST1 class_declaration SEP "and") ->
2456           <:str_item< class $_list:cd$ >>
2457       | "class"; "type"; ctd = V (LIST1 class_type_declaration SEP "and") ->
2458           <:str_item< class type $_list:ctd$ >> ] ]
2459   ;
2460   sig_item:
2461     [ [ "class"; cd = V (LIST1 class_description SEP "and") ->
2462           <:sig_item< class $_list:cd$ >>
2463       | "class"; "type"; ctd = V (LIST1 class_type_declaration SEP "and") ->
2464           <:sig_item< class type $_list:ctd$ >> ] ]
2465   ;
2466   (* Class expressions *)
2467   class_declaration:
2468     [ [ vf = V (FLAG "virtual"); ctp = class_type_parameters; i = V LIDENT;
2469         cfb = class_fun_binding ->
2470           {MLast.ciLoc = loc; MLast.ciVir = vf; MLast.ciPrm = ctp;
2471            MLast.ciNam = i; MLast.ciExp = cfb} ] ]
2472   ;
2473   class_fun_binding:
2474     [ [ "="; ce = class_expr -> ce
2475       | ":"; ct = class_type; "="; ce = class_expr ->
2476           <:class_expr< ($ce$ : $ct$) >>
2477       | p = patt LEVEL "simple"; cfb = SELF ->
2478           <:class_expr< fun $p$ -> $cfb$ >> ] ]
2479   ;
2480   class_type_parameters:
2481     [ [ -> (loc, <:vala< [] >>)
2482       | "["; tpl = V (LIST1 type_parameter SEP ","); "]" -> (loc, tpl) ] ]
2483   ;
2484   class_fun_def:
2485     [ [ p = patt LEVEL "simple"; "->"; ce = class_expr ->
2486           <:class_expr< fun $p$ -> $ce$ >>
2487       | p = patt LEVEL "simple"; cfd = SELF ->
2488           <:class_expr< fun $p$ -> $cfd$ >> ] ]
2489   ;
2490   class_expr:
2491     [ "top"
2492       [ "fun"; cfd = class_fun_def -> cfd
2493       | "let"; rf = V (FLAG "rec"); lb = V (LIST1 let_binding SEP "and");
2494         "in"; ce = SELF ->
2495           <:class_expr< let $_flag:rf$ $_list:lb$ in $ce$ >> ]
2496     | "apply" LEFTA
2497       [ ce = SELF; e = expr LEVEL "label" ->
2498           <:class_expr< $ce$ $e$ >> ]
2499     | "simple"
2500       [ "["; ct = ctyp; ","; ctcl = LIST1 ctyp SEP ","; "]";
2501         ci = class_longident ->
2502           <:class_expr< [ $list:[ct :: ctcl]$ ] $list:ci$ >>
2503       | "["; ct = ctyp; "]"; ci = class_longident ->
2504           <:class_expr< [ $ct$ ] $list:ci$ >>
2505       | ci = class_longident -> <:class_expr< $list:ci$ >>
2506       | "object"; cspo = V (OPT class_self_patt);
2507         cf = V class_structure "list"; "end" ->
2508           <:class_expr< object $_opt:cspo$ $_list:cf$ end >>
2509       | "("; ce = SELF; ":"; ct = class_type; ")" ->
2510           <:class_expr< ($ce$ : $ct$) >>
2511       | "("; ce = SELF; ")" -> ce ] ]
2512   ;
2513   class_structure:
2514     [ [ cf = LIST0 class_str_item -> cf ] ]
2515   ;
2516   class_self_patt:
2517     [ [ "("; p = patt; ")" -> p
2518       | "("; p = patt; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >> ] ]
2519   ;
2520   class_str_item:
2521     [ [ "inherit"; ce = class_expr; pb = V (OPT [ "as"; i = LIDENT -> i ]) ->
2522           <:class_str_item< inherit $ce$ $_opt:pb$ >>
2523       | "val"; ov = V (FLAG "!") "!"; mf = V (FLAG "mutable");
2524         lab = V LIDENT "lid" ""; e = cvalue_binding ->
2525           <:class_str_item< value $_!:ov$ $_flag:mf$ $_lid:lab$ = $e$ >>
2526       | "val"; ov = V (FLAG "!") "!"; mf = V (FLAG "mutable");
2527         "virtual"; lab = V LIDENT "lid" ""; ":"; t = ctyp ->
2528           if Pcaml.unvala ov then
2529             Ploc.raise loc (Stream.Error "virtual value cannot override")
2530           else
2531             <:class_str_item< value virtual $_flag:mf$ $_lid:lab$ : $t$ >>
2532       | "val"; "virtual"; mf = V (FLAG "mutable"); lab = V LIDENT "lid" "";
2533         ":"; t = ctyp ->
2534           <:class_str_item< value virtual $_flag:mf$ $_lid:lab$ : $t$ >>
2535       | "method"; "private"; "virtual"; l = V LIDENT "lid" ""; ":";
2536         t = poly_type ->
2537           <:class_str_item< method virtual private $_lid:l$ : $t$ >>
2538       | "method"; "virtual"; "private"; l = V LIDENT "lid" ""; ":";
2539         t = poly_type ->
2540           <:class_str_item< method virtual private $_lid:l$ : $t$ >>
2541       | "method"; "virtual"; l = V LIDENT "lid" ""; ":"; t = poly_type ->
2542           <:class_str_item< method virtual $_lid:l$ : $t$ >>
2543       | "method"; ov = V (FLAG "!") "!"; "private"; l = V LIDENT "lid" "";
2544         ":"; t = poly_type; "="; e = expr ->
2545           <:class_str_item< method $_!:ov$ private $_lid:l$ : $t$ = $e$ >>
2546       | "method"; ov = V (FLAG "!") "!"; "private"; l = V LIDENT "lid" "";
2547         sb = fun_binding ->
2548           <:class_str_item< method $_!:ov$ private $_lid:l$ = $sb$ >>
2549       | "method"; ov = V (FLAG "!") "!"; l = V LIDENT "lid" ""; ":";
2550         t = poly_type; "="; e = expr ->
2551           <:class_str_item< method $_!:ov$ $_lid:l$ : $t$ = $e$ >>
2552       | "method"; ov = V (FLAG "!") "!"; l = V LIDENT "lid" "";
2553         sb = fun_binding ->
2554           <:class_str_item< method $_!:ov$ $_lid:l$ = $sb$ >>
2555       | "constraint"; t1 = ctyp; "="; t2 = ctyp ->
2556           <:class_str_item< type $t1$ = $t2$ >>
2557       | "initializer"; se = expr -> <:class_str_item< initializer $se$ >> ] ]
2558   ;
2559   cvalue_binding:
2560     [ [ "="; e = expr -> e
2561       | ":"; t = ctyp; "="; e = expr -> <:expr< ($e$ : $t$) >>
2562       | ":"; t = ctyp; ":>"; t2 = ctyp; "="; e = expr ->
2563           <:expr< ($e$ : $t$ :> $t2$) >>
2564       | ":>"; t = ctyp; "="; e = expr ->
2565           <:expr< ($e$ :> $t$) >> ] ]
2566   ;
2567   label:
2568     [ [ i = LIDENT -> i ] ]
2569   ;
2570   (* Class types *)
2571   class_type:
2572     [ [ test_ctyp_minusgreater; t = ctyp LEVEL "star"; "->"; ct = SELF ->
2573           <:class_type< [ $t$ ] -> $ct$ >>
2574       | cs = class_signature -> cs ] ]
2575   ;
2576   class_signature:
2577     [ [ "["; tl = LIST1 ctyp SEP ","; "]"; id = SELF ->
2578           <:class_type< $id$ [ $list:tl$ ] >>
2579       | "object"; cst = V (OPT class_self_type);
2580         csf = V (LIST0 class_sig_item); "end" ->
2581           <:class_type< object $_opt:cst$ $_list:csf$ end >> ]
2582     | [ ct1 = SELF; "."; ct2 = SELF -> <:class_type< $ct1$ . $ct2$ >>
2583       | ct1 = SELF; "("; ct2 = SELF; ")" -> <:class_type< $ct1$ $ct2$ >> ]
2584     | [ i = V LIDENT -> <:class_type< $_id: i$ >>
2585       | i = V UIDENT -> <:class_type< $_id: i$ >> ] ]
2586   ;
2587   class_self_type:
2588     [ [ "("; t = ctyp; ")" -> t ] ]
2589   ;
2590   class_sig_item:
2591     [ [ "inherit"; cs = class_signature ->
2592           <:class_sig_item< inherit $cs$ >>
2593       | "val"; mf = V (FLAG "mutable"); l = V LIDENT "lid" ""; ":"; t = ctyp ->
2594           <:class_sig_item< value $_flag:mf$ $_lid:l$ : $t$ >>
2595       | "method"; "private"; "virtual"; l = V LIDENT "lid" ""; ":";
2596         t = poly_type ->
2597           <:class_sig_item< method virtual private $_lid:l$ : $t$ >>
2598       | "method"; "virtual"; "private"; l = V LIDENT "lid" ""; ":";
2599         t = poly_type ->
2600           <:class_sig_item< method virtual private $_lid:l$ : $t$ >>
2601       | "method"; "virtual"; l = V LIDENT "lid" ""; ":"; t = poly_type ->
2602           <:class_sig_item< method virtual $_lid:l$ : $t$ >>
2603       | "method"; "private"; l = V LIDENT "lid" ""; ":"; t = poly_type ->
2604           <:class_sig_item< method private $_lid:l$ : $t$ >>
2605       | "method"; l = V LIDENT "lid" ""; ":"; t = poly_type ->
2606           <:class_sig_item< method $_lid:l$ : $t$ >>
2607       | "constraint"; t1 = ctyp; "="; t2 = ctyp ->
2608           <:class_sig_item< type $t1$ = $t2$ >> ] ]
2609   ;
2610   class_description:
2611     [ [ vf = V (FLAG "virtual"); ctp = class_type_parameters; n = V LIDENT;
2612         ":"; ct = class_type ->
2613           {MLast.ciLoc = loc; MLast.ciVir = vf; MLast.ciPrm = ctp;
2614            MLast.ciNam = n; MLast.ciExp = ct} ] ]
2615   ;
2616   class_type_declaration:
2617     [ [ vf = V (FLAG "virtual"); ctp = class_type_parameters; n = V LIDENT;
2618         "="; cs = class_signature ->
2619           {MLast.ciLoc = loc; MLast.ciVir = vf; MLast.ciPrm = ctp;
2620            MLast.ciNam = n; MLast.ciExp = cs} ] ]
2621   ;
2622   (* Expressions *)
2623   expr: LEVEL "simple"
2624     [ LEFTA
2625       [ "new"; i = V class_longident "list" -> <:expr< new $_list:i$ >>
2626       | "object"; cspo = V (OPT class_self_patt);
2627         cf = V class_structure "list"; "end" ->
2628           <:expr< object $_opt:cspo$ $_list:cf$ end >> ] ]
2629   ;
2630   expr: LEVEL "."
2631     [ [ e = SELF; "#"; lab = V LIDENT "lid" -> <:expr< $e$ # $_lid:lab$ >> ] ]
2632   ;
2633   expr: LEVEL "simple"
2634     [ [ "("; e = SELF; ":"; t = ctyp; ":>"; t2 = ctyp; ")" ->
2635           <:expr< ($e$ : $t$ :> $t2$) >>
2636       | "("; e = SELF; ":>"; t = ctyp; ")" -> <:expr< ($e$ :> $t$) >>
2637       | "{<"; ">}" -> <:expr< {< >} >>
2638       | "{<"; fel = V field_expr_list "list"; ">}" ->
2639           <:expr< {< $_list:fel$ >} >> ] ]
2640   ;
2641   field_expr_list:
2642     [ [ l = label; "="; e = expr LEVEL "expr1"; ";"; fel = SELF ->
2643           [(l, e) :: fel]
2644       | l = label; "="; e = expr LEVEL "expr1"; ";" -> [(l, e)]
2645       | l = label; "="; e = expr LEVEL "expr1" -> [(l, e)] ] ]
2646   ;
2647   (* Core types *)
2648   ctyp: LEVEL "simple"
2649     [ [ "#"; id = V class_longident "list" ->
2650          <:ctyp< # $_list:id$ >>
2651       | "<"; ml = V meth_list "list"; v = V (FLAG ".."); ">" ->
2652           <:ctyp< < $_list:ml$ $_flag:v$ > >>
2653       | "<"; ".."; ">" ->
2654          <:ctyp< < .. > >>
2655       | "<"; ">" ->
2656           <:ctyp< < > >> ] ]
2657   ;
2658   meth_list:
2659     [ [ f = field; ";"; ml = SELF -> [f :: ml]
2660       | f = field; ";" -> [f]
2661       | f = field -> [f] ] ]
2662   ;
2663   field:
2664     [ [ lab = LIDENT; ":"; t = poly_type -> (lab, t) ] ]
2665   ;
2666   (* Polymorphic types *)
2667   typevar:
2668     [ [ "'"; i = ident -> i ] ]
2669   ;
2670   poly_type:
2671     [ [ "type"; nt = LIST1 LIDENT; "."; ct = ctyp ->
2672           <:ctyp< type $list:nt$ . $ct$ >>
2673       | test_typevar_list_dot; tpl = LIST1 typevar; "."; t2 = ctyp ->
2674           <:ctyp< ! $list:tpl$ . $t2$ >>
2675       | t = ctyp -> t ] ]
2676   ;
2677   (* Identifiers *)
2678   class_longident:
2679     [ [ m = UIDENT; "."; l = SELF -> [m :: l]
2680       | i = LIDENT -> [i] ] ]
2681   ;
2682   (* Labels *)
2683   ctyp: AFTER "arrow"
2684     [ NONA
2685       [ i = V LIDENT; ":"; t = SELF -> <:ctyp< ~$_:i$: $t$ >>
2686       | i = V QUESTIONIDENTCOLON; t = SELF -> <:ctyp< ?$_:i$: $t$ >>
2687       | i = V QUESTIONIDENT; ":"; t = SELF -> <:ctyp< ?$_:i$: $t$ >> ] ]
2688   ;
2689   ctyp: LEVEL "simple"
2690     [ [ "["; OPT "|"; rfl = V (LIST1 poly_variant SEP "|"); "]" ->
2691           <:ctyp< [ = $_list:rfl$ ] >>
2692       | "["; ">"; "]" -> <:ctyp< [ > $list:[]$ ] >>
2693       | "["; ">"; OPT "|"; rfl = V (LIST1 poly_variant SEP "|"); "]" ->
2694           <:ctyp< [ > $_list:rfl$ ] >>
2695       | "[<"; OPT "|"; rfl = V (LIST1 poly_variant SEP "|"); "]" ->
2696           <:ctyp< [ < $_list:rfl$ ] >>
2697       | "[<"; OPT "|"; rfl = V (LIST1 poly_variant SEP "|"); ">";
2698         ntl = V (LIST1 name_tag); "]" ->
2699           <:ctyp< [ < $_list:rfl$ > $_list:ntl$ ] >> ] ]
2700   ;
2701   poly_variant:
2702     [ [ "`"; i = V ident "" -> <:poly_variant< ` $_:i$ >>
2703       | "`"; i = V ident ""; "of"; ao = V (FLAG "&");
2704         l = V (LIST1 ctyp SEP "&") ->
2705           <:poly_variant< `$_:i$ of $_flag:ao$ $_list:l$ >>
2706       | t = ctyp -> <:poly_variant< $t$ >> ] ]
2707   ;
2708   name_tag:
2709     [ [ "`"; i = ident -> i ] ]
2710   ;
2711   expr: LEVEL "expr1"
2712     [ [ "fun"; p = labeled_patt; (eo, e) = fun_def ->
2713           <:expr< fun [ $p$ $opt:eo$ -> $e$ ] >> ] ]
2714   ;
2715   expr: AFTER "apply"
2716     [ "label"
2717       [ i = V TILDEIDENTCOLON; e = SELF -> <:expr< ~{$_:i$ = $e$} >>
2718       | i = V TILDEIDENT -> <:expr< ~{$_:i$} >>
2719       | i = V QUESTIONIDENTCOLON; e = SELF -> <:expr< ?{$_:i$ = $e$} >>
2720       | i = V QUESTIONIDENT -> <:expr< ?{$_:i$} >> ] ]
2721   ;
2722   expr: LEVEL "simple"
2723     [ [ "`"; s = V ident "" -> <:expr< ` $_:s$ >> ] ]
2724   ;
2725   fun_def:
2726     [ [ p = labeled_patt; (eo, e) = SELF ->
2727           (None, <:expr< fun [ $p$ $opt:eo$ -> $e$ ] >>) ] ]
2728   ;
2729   fun_binding:
2730     [ [ p = labeled_patt; e = SELF -> <:expr< fun $p$ -> $e$ >> ] ]
2731   ;
2732   patt: LEVEL "simple"
2733     [ [ "`"; s = V ident "" -> <:patt< ` $_:s$ >>
2734       | "#"; t = V mod_ident "list" "" -> <:patt< # $_list:t$ >>
2735       | p = labeled_patt -> p ] ]
2736   ;
2737   labeled_patt:
2738     [ [ i = V TILDEIDENTCOLON; p = patt LEVEL "simple" ->
2739            <:patt< ~{$_:i$ = $p$} >>
2740       | i = V TILDEIDENT ->
2741            <:patt< ~{$_:i$} >>
2742       | "~"; "("; i = LIDENT; ")" ->
2743            <:patt< ~{$lid:i$} >>
2744       | "~"; "("; i = LIDENT; ":"; t = ctyp; ")" ->
2745            <:patt< ~{$lid:i$ : $t$} >>
2746       | i = V QUESTIONIDENTCOLON; j = LIDENT ->
2747            <:patt< ?{$_:i$ = ?{$lid:j$}} >>
2748       | i = V QUESTIONIDENTCOLON; "_" ->
2749            <:patt< ?{$_:i$} >>
2750       | i = V QUESTIONIDENTCOLON; "("; p = patt; "="; e = expr; ")" ->
2751           <:patt< ?{$_:i$ = ?{$p$ = $e$}} >>
2752       | i = V QUESTIONIDENTCOLON; "("; p = patt; ":"; t = ctyp; ")" ->
2753           <:patt< ?{$_:i$ = ?{$p$ : $t$}} >>
2754       | i = V QUESTIONIDENTCOLON; "("; p = patt; ":"; t = ctyp; "=";
2755         e = expr; ")" ->
2756           <:patt< ?{$_:i$ = ?{$p$ : $t$ = $e$}} >>
2757       | i = V QUESTIONIDENTCOLON; "("; p = patt; ")" ->
2758           <:patt< ?{$_:i$ = ?{$p$}} >>
2759       | i = V QUESTIONIDENT -> <:patt< ?{$_:i$} >>
2760       | "?"; "("; i = LIDENT; "="; e = expr; ")" ->
2761           <:patt< ?{$lid:i$ = $e$} >>
2762       | "?"; "("; i = LIDENT; ":"; t = ctyp; "="; e = expr; ")" ->
2763           <:patt< ?{$lid:i$ : $t$ = $e$} >>
2764       | "?"; "("; i = LIDENT; ")" ->
2765           <:patt< ?{$lid:i$} >>
2766       | "?"; "("; i = LIDENT; ":"; t = ctyp; ")" ->
2767           <:patt< ?{$lid:i$ : $t$} >> ] ]
2768   ;
2769   class_type:
2770     [ [ i = LIDENT; ":"; t = ctyp LEVEL "apply"; "->"; ct = SELF ->
2771           <:class_type< [ ~$i$: $t$ ] -> $ct$ >>
2772       | i = V QUESTIONIDENTCOLON; t = ctyp LEVEL "apply"; "->"; ct = SELF ->
2773           <:class_type< [ ?$_:i$: $t$ ] -> $ct$ >>
2774       | i = V QUESTIONIDENT; ":"; t = ctyp LEVEL "apply"; "->"; ct = SELF ->
2775           <:class_type< [ ?$_:i$: $t$ ] -> $ct$ >> ] ]
2776   ;
2777   class_fun_binding:
2778     [ [ p = labeled_patt; cfb = SELF -> <:class_expr< fun $p$ -> $cfb$ >> ] ]
2779   ;
2780   class_fun_def:
2781     [ [ p = labeled_patt; "->"; ce = class_expr ->
2782           <:class_expr< fun $p$ -> $ce$ >>
2783       | p = labeled_patt; cfd = SELF ->
2784           <:class_expr< fun $p$ -> $cfd$ >> ] ]
2785   ;
2786 END;
2787
2788 (* Main entry points *)
2789
2790 EXTEND
2791   GLOBAL: interf implem use_file top_phrase expr patt;
2792   interf:
2793     [ [ si = sig_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped)
2794       | "#"; n = LIDENT; dp = OPT expr; ";;" ->
2795           ([(<:sig_item< # $lid:n$ $opt:dp$ >>, loc)], None)
2796       | EOI -> ([], Some loc) ] ]
2797   ;
2798   sig_item_semi:
2799     [ [ si = sig_item; OPT ";;" -> (si, loc) ] ]
2800   ;
2801   implem:
2802     [ [ si = str_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped)
2803       | "#"; n = LIDENT; dp = OPT expr; ";;" ->
2804           ([(<:str_item< # $lid:n$ $opt:dp$ >>, loc)], None)
2805       | EOI -> ([], Some loc) ] ]
2806   ;
2807   str_item_semi:
2808     [ [ si = str_item; OPT ";;" -> (si, loc) ] ]
2809   ;
2810   top_phrase:
2811     [ [ ph = phrase; ";;" -> Some ph
2812       | EOI -> None ] ]
2813   ;
2814   use_file:
2815     [ [ si = str_item; OPT ";;"; (sil, stopped) = SELF ->
2816           ([si :: sil], stopped)
2817       | "#"; n = LIDENT; dp = OPT expr; ";;" ->
2818           ([<:str_item< # $lid:n$ $opt:dp$ >>], True)
2819       | EOI -> ([], False) ] ]
2820   ;
2821   phrase:
2822     [ [ sti = str_item -> sti
2823       | "#"; n = LIDENT; dp = OPT expr ->
2824           <:str_item< # $lid:n$ $opt:dp$ >> ] ]
2825   ;
2826 END;
2827
2828 Pcaml.add_option "-no_quot" (Arg.Set no_quotations)
2829   "Don't parse quotations, allowing to use, e.g. \"<:>\" as token";
2830
2831 (* ------------------------------------------------------------------------- *)
2832 (* Added by JRH ***                                                          *)
2833 (* ------------------------------------------------------------------------- *)
2834
2835 EXTEND
2836   expr: AFTER "<"
2837    [[ f = expr; "o"; g = expr -> <:expr< ((o $f$) $g$) >>
2838     | f = expr; "upto"; g = expr -> <:expr< ((upto $f$) $g$) >>
2839     | f = expr; "F_F"; g = expr -> <:expr< ((f_f_ $f$) $g$) >>
2840     | f = expr; "THENC"; g = expr -> <:expr< ((thenc_ $f$) $g$) >>
2841     | f = expr; "THEN"; g = expr -> <:expr< ((then_ $f$) $g$) >>
2842     | f = expr; "THENL"; g = expr -> <:expr< ((thenl_ $f$) $g$) >>
2843     | f = expr; "ORELSE"; g = expr -> <:expr< ((orelse_ $f$) $g$) >>
2844     | f = expr; "ORELSEC"; g = expr -> <:expr< ((orelsec_ $f$) $g$) >>
2845     | f = expr; "THEN_TCL"; g = expr -> <:expr< ((then_tcl_ $f$) $g$) >>
2846     | f = expr; "ORELSE_TCL"; g = expr -> <:expr< ((orelse_tcl_ $f$) $g$) >>
2847 ]];
2848 END;
2849
2850 EXTEND
2851   top_phrase:
2852    [ [ sti = str_item; ";;" ->
2853          match sti with
2854          [ <:str_item< $exp:e$ >> -> Some <:str_item< value it = $e$ >>
2855          | x -> Some x ] ] ]
2856   ;
2857 END;