~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to camlp4/Camlp4Parsers/Camlp4OCamlParser.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
21
21
 
22
22
module Id : Sig.Id = struct
23
23
  value name = "Camlp4OCamlParser";
24
 
  value version = "$Id: Camlp4OCamlParser.ml,v 1.3.2.19 2007/12/18 08:53:26 ertai Exp $";
 
24
  value version = Sys.ocaml_version;
25
25
end;
26
26
 
27
27
module Make (Syntax : Sig.Camlp4Syntax) = struct
175
175
  DELETE_RULE Gram module_type: SELF; SELF; dummy END;
176
176
  DELETE_RULE Gram module_type: SELF; "."; SELF END;
177
177
  DELETE_RULE Gram label_expr: label_longident; fun_binding END;
 
178
  DELETE_RULE Gram meth_list: meth_decl; opt_dot_dot END;
178
179
  DELETE_RULE Gram expr: "let"; opt_rec; binding; "in"; SELF END;
179
180
  DELETE_RULE Gram expr: "let"; "module"; a_UIDENT; module_binding0; "in"; SELF END;
180
181
  DELETE_RULE Gram expr: "fun"; "["; LIST0 match_case0 SEP "|"; "]" END;
183
184
  DELETE_RULE Gram expr: SELF; SELF END;
184
185
  DELETE_RULE Gram expr: "new"; class_longident END;
185
186
  DELETE_RULE Gram expr: "["; sem_expr_for_list; "::"; expr; "]" END;
186
 
  DELETE_RULE Gram expr: "{"; label_expr; "}" END;
187
 
  DELETE_RULE Gram expr: "{"; "("; SELF; ")"; "with"; label_expr; "}" END;
 
187
  DELETE_RULE Gram expr: "{"; label_expr_list; "}" END;
 
188
  DELETE_RULE Gram expr: "{"; "("; SELF; ")"; "with"; label_expr_list; "}" END;
188
189
  DELETE_RULE Gram expr: "("; SELF; ","; comma_expr; ")" END;
189
190
  DELETE_RULE Gram expr: SELF; ":="; SELF; dummy END;
190
191
  DELETE_RULE Gram expr: "~"; a_LIDENT; ":"; SELF END;
234
235
      comma_ctyp comma_expr comma_ipatt comma_patt comma_type_parameter
235
236
      constrain constructor_arg_list constructor_declaration
236
237
      constructor_declarations ctyp ctyp_quot cvalue_binding direction_flag
237
 
      dummy eq_expr expr expr_eoi expr_quot field_expr fun_binding
 
238
      dummy eq_expr expr expr_eoi expr_quot fun_binding
238
239
      fun_def ident ident_quot implem interf ipatt ipatt_tcon label
239
 
      label_declaration label_expr label_ipatt label_longident label_patt
240
 
      labeled_ipatt let_binding meth_list module_binding module_binding0
 
240
      label_declaration label_declaration_list label_expr label_expr_list
 
241
      label_longident label_patt_list meth_list
 
242
      labeled_ipatt let_binding module_binding module_binding0
241
243
      module_binding_quot module_declaration module_expr module_expr_quot
242
244
      module_longident module_longident_with_app module_rec_declaration
243
245
      module_type module_type_quot more_ctyp name_tags opt_as_lident
284
286
              <:str_item< let module $m$ = $mb$ in $e$ >>
285
287
      ] ]
286
288
    ;
 
289
    seq_expr:
 
290
      [ [ e1 = expr LEVEL "top"; ";"; e2 = SELF ->
 
291
            conc_seq e1 e2
 
292
        | e1 = expr LEVEL "top"; ";" -> e1
 
293
        | e1 = expr LEVEL "top" -> e1 ] ];
287
294
    expr: BEFORE "top"
288
 
      [ ";" RIGHTA
289
 
        [ e1 = SELF; ";"; e2 = SELF ->
290
 
            conc_seq e1 e2
291
 
        | e1 = SELF; ";" -> e1 ] ];
 
295
      [ ";" [ e = seq_expr -> e ] ];
292
296
    expr: LEVEL "top"
293
297
      [ [ "let"; r = opt_rec; bi = binding; "in";
294
298
          x = expr LEVEL ";" ->
306
310
      ] ];
307
311
    expr: BEFORE "||"
308
312
      [ ","
309
 
        [ e = SELF; ","; el = (*FIXME comma_expr*)LIST1 NEXT SEP "," ->
310
 
            <:expr< ( $e$, $Ast.exCom_of_list el$ ) >> ]
 
313
        [ e1 = SELF; ","; e2 = comma_expr ->
 
314
            <:expr< ( $e1$, $e2$ ) >> ]
311
315
      | ":=" NONA
312
316
        [ e1 = SELF; ":="; e2 = expr LEVEL "top" ->
313
317
            <:expr< $e1$.val := $e2$ >>
331
335
    expr: LEVEL "simple" (* LEFTA *)
332
336
      [ [ "false" -> <:expr< False >>
333
337
        | "true" -> <:expr< True >>
334
 
        | "{"; test_label_eq; lel = label_expr; "}" ->
 
338
        | "{"; test_label_eq; lel = label_expr_list; "}" ->
335
339
            <:expr< { $lel$ } >>
336
 
        | "{"; e = expr LEVEL "."; "with"; lel = label_expr; "}" ->
 
340
        | "{"; e = expr LEVEL "."; "with"; lel = label_expr_list; "}" ->
337
341
            <:expr< { ($e$) with $lel$ } >>
338
342
        | "new"; i = class_longident -> <:expr< new $i$ >>
339
343
      ] ]
372
376
                List.fold_left (fun p1 p2 -> <:patt< $p1$ $p2$ >>) p1
373
377
                                (Ast.list_of_patt p [])
374
378
            | _ -> <:patt< $p1$ $p2$ >> ]
 
379
        | "lazy"; p = SELF -> <:patt< lazy $p$ >>
375
380
        | `ANTIQUOT (""|"pat"|"anti" as n) s ->
376
381
            <:patt< $anti:mk_anti ~c:"patt" n s$ >>
377
382
        | p = patt_constr -> p ]
404
409
            mk_list <:patt< [] >>
405
410
        | "[|"; "|]" -> <:patt< [||] >>
406
411
        | "[|"; pl = sem_patt; "|]" -> <:patt< [| $pl$ |] >>
407
 
        | "{"; pl = label_patt; "}" -> <:patt< { $pl$ } >>
 
412
        | "{"; pl = label_patt_list; "}" -> <:patt< { $pl$ } >>
408
413
        | "("; ")" -> <:patt< () >>
409
414
        | "("; p = patt; ":"; t = ctyp; ")" -> <:patt< ($p$ : $t$) >>
410
415
        | "("; p = patt; ")" -> <:patt< $p$ >>
412
417
        | "`"; s = a_ident -> <:patt< ` $s$ >>
413
418
        | "#"; i = type_longident -> <:patt< # $i$ >> ] ]
414
419
    ;
415
 
    (* comma_expr:
416
 
      [ [ e1 = SELF; ","; e2 = SELF -> <:expr< $e1$, $e2$ >>
417
 
        | e = expr LEVEL ":=" -> e ] ]
418
 
    ;                                                           *)
 
420
    comma_expr:
 
421
      [ [ e1 = expr LEVEL ":="; ","; e2 = SELF -> <:expr< $e1$, $e2$ >>
 
422
        | e1 = expr LEVEL ":=" -> e1 ] ]
 
423
    ;
419
424
    (* comma_patt:
420
425
      [ [ p1 = SELF; ","; p2 = SELF -> <:patt< $p1$, $p2$ >>
421
426
        | p = patt LEVEL ".." -> p ] ]
507
512
            mk <:ctyp< $i$ $t$ >>
508
513
        | "("; t = SELF; ")" -> <:ctyp< $t$ >>
509
514
        | "#"; i = class_longident -> <:ctyp< # $i$ >>
510
 
        | "<"; ml = opt_meth_list; v = opt_dot_dot; ">" ->
511
 
            <:ctyp< < $ml$ $..:v$ > >>
 
515
        | "<"; t = opt_meth_list; ">" -> t
512
516
        | "["; OPT "|"; rfl = row_field; "]" ->
513
517
            <:ctyp< [ = $rfl$ ] >>
514
518
        | "["; ">"; "]" -> <:ctyp< [ > $<:ctyp<>>$ ] >>
520
524
            <:ctyp< [ < $rfl$ > $ntl$ ] >>
521
525
        ] ]
522
526
    ;
 
527
    meth_list:
 
528
      [ [ m = meth_decl -> (m, Ast.BFalse) ] ];
523
529
    comma_ctyp_app:
524
530
      [ [ t1 = ctyp; ","; t2 = SELF -> fun acc -> t2 <:ctyp< $acc$ $t1$ >>
525
531
        | t = ctyp -> fun acc -> <:ctyp< $acc$ $t$ >>
569
575
        | t = ctyp -> <:ctyp< $t$ >>
570
576
        | t = ctyp; "="; "private"; tk = type_kind ->
571
577
            <:ctyp< $t$ == private $tk$ >>
572
 
        | t1 = ctyp; "="; "{"; t2 = label_declaration; "}" ->
 
578
        | t1 = ctyp; "="; "{"; t2 = label_declaration_list; "}" ->
573
579
            <:ctyp< $t1$ == { $t2$ } >>
574
580
        | t1 = ctyp; "="; OPT "|"; t2 = constructor_declarations ->
575
581
            <:ctyp< $t1$ == [ $t2$ ] >>
576
 
        | "{"; t = label_declaration; "}" ->
 
582
        | "{"; t = label_declaration_list; "}" ->
577
583
            <:ctyp< { $t$ } >> ] ]
578
584
    ;
579
585
    module_expr: LEVEL "apply"
600
606
      [ [ "val" -> () ] ]
601
607
    ;
602
608
    label_declaration:
603
 
      [ LEFTA
604
 
        [ t1 = SELF; ";"; t2 = SELF -> <:ctyp< $t1$; $t2$ >>
605
 
        | `ANTIQUOT (""|"typ" as n) s ->
 
609
      [ [ `ANTIQUOT (""|"typ" as n) s ->
606
610
            <:ctyp< $anti:mk_anti ~c:"ctyp" n s$ >>
607
611
        | `QUOTATION x -> Quotation.expand _loc x Quotation.DynAst.ctyp_tag
608
612
        | s = a_LIDENT; ":"; t = poly_type ->  <:ctyp< $lid:s$ : $t$ >>