diff options
-rw-r--r-- | camlp4/meta/pa_r.ml | 9 | ||||
-rw-r--r-- | camlp4/meta/q_MLast.ml | 13 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/pa_r.ml | 107 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/q_MLast.ml | 17 |
4 files changed, 65 insertions, 81 deletions
diff --git a/camlp4/meta/pa_r.ml b/camlp4/meta/pa_r.ml index b051daa5e..a8142928f 100644 --- a/camlp4/meta/pa_r.ml +++ b/camlp4/meta/pa_r.ml @@ -133,9 +133,7 @@ value direction_flag = Grammar.Entry.create gram "direction_flag"; value mod_ident = Grammar.Entry.create gram "mod_ident"; EXTEND - GLOBAL: interf implem top_phrase use_file sig_item str_item ctyp patt expr - module_type module_expr let_binding type_parameter fun_binding ipatt - direction_flag mod_ident; + GLOBAL: interf implem use_file top_phrase; interf: [ [ si = sig_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped) | "#"; n = LIDENT; dp = OPT expr; ";" -> @@ -169,6 +167,11 @@ EXTEND | "#"; n = LIDENT; dp = OPT expr; ";" -> <:str_item< # $n$ $opt:dp$ >> ] ] ; +END; + +EXTEND + GLOBAL: sig_item str_item ctyp patt expr module_type module_expr + let_binding type_parameter fun_binding ipatt direction_flag mod_ident; module_expr: [ [ "functor"; "("; i = UIDENT; ":"; t = module_type; ")"; "->"; me = SELF -> diff --git a/camlp4/meta/q_MLast.ml b/camlp4/meta/q_MLast.ml index aea04eadb..1c2a5af0c 100644 --- a/camlp4/meta/q_MLast.ml +++ b/camlp4/meta/q_MLast.ml @@ -35,7 +35,6 @@ value str_item = Grammar.Entry.create gram "structure item"; value ctyp = Grammar.Entry.create gram "type"; value patt = Grammar.Entry.create gram "pattern"; value expr = Grammar.Entry.create gram "expression"; -value directive = Grammar.Entry.create gram "directive"; value module_type = Grammar.Entry.create gram "module type"; value module_expr = Grammar.Entry.create gram "module expression"; @@ -107,7 +106,7 @@ value warning_seq () = ; EXTEND - GLOBAL: sig_item str_item ctyp patt expr directive module_type module_expr + GLOBAL: sig_item str_item ctyp patt expr module_type module_expr class_type class_expr class_sig_item class_str_item; module_expr: [ [ "functor"; "("; i = anti_UIDENT; ":"; t = module_type; ")"; "->"; @@ -973,16 +972,6 @@ do { Quotation.add "module_expr" (apply_entry module_expr_eoi) }; -let directive_eoi = Grammar.Entry.create gram "directive" in -do { - EXTEND - directive_eoi: - [ [ x = directive; EOI -> x ] ] - ; - END; - Quotation.add "directive" (apply_entry directive_eoi) -}; - let class_type_eoi = Grammar.Entry.create gram "class_type" in do { EXTEND diff --git a/camlp4/ocaml_src/meta/pa_r.ml b/camlp4/ocaml_src/meta/pa_r.ml index b8e054087..52f80c3b6 100644 --- a/camlp4/ocaml_src/meta/pa_r.ml +++ b/camlp4/ocaml_src/meta/pa_r.ml @@ -131,21 +131,8 @@ let mod_ident = Grammar.Entry.create gram "mod_ident";; Grammar.extend (let _ = (interf : 'interf Grammar.Entry.e) and _ = (implem : 'implem Grammar.Entry.e) - and _ = (top_phrase : 'top_phrase Grammar.Entry.e) and _ = (use_file : 'use_file Grammar.Entry.e) - and _ = (sig_item : 'sig_item Grammar.Entry.e) - and _ = (str_item : 'str_item Grammar.Entry.e) - and _ = (ctyp : 'ctyp Grammar.Entry.e) - and _ = (patt : 'patt Grammar.Entry.e) - and _ = (expr : 'expr Grammar.Entry.e) - and _ = (module_type : 'module_type Grammar.Entry.e) - and _ = (module_expr : 'module_expr Grammar.Entry.e) - and _ = (let_binding : 'let_binding Grammar.Entry.e) - and _ = (type_parameter : 'type_parameter Grammar.Entry.e) - and _ = (fun_binding : 'fun_binding Grammar.Entry.e) - and _ = (ipatt : 'ipatt Grammar.Entry.e) - and _ = (direction_flag : 'direction_flag Grammar.Entry.e) - and _ = (mod_ident : 'mod_ident Grammar.Entry.e) in + and _ = (top_phrase : 'top_phrase Grammar.Entry.e) in let grammar_entry_create s = Grammar.Entry.create (Grammar.of_entry interf) s in @@ -153,41 +140,7 @@ Grammar.extend grammar_entry_create "sig_item_semi" and str_item_semi : 'str_item_semi Grammar.Entry.e = grammar_entry_create "str_item_semi" - and phrase : 'phrase Grammar.Entry.e = grammar_entry_create "phrase" - and rebind_exn : 'rebind_exn Grammar.Entry.e = - grammar_entry_create "rebind_exn" - and module_binding : 'module_binding Grammar.Entry.e = - grammar_entry_create "module_binding" - and module_declaration : 'module_declaration Grammar.Entry.e = - grammar_entry_create "module_declaration" - and with_constr : 'with_constr Grammar.Entry.e = - grammar_entry_create "with_constr" - and dummy : 'dummy Grammar.Entry.e = grammar_entry_create "dummy" - and sequence : 'sequence Grammar.Entry.e = grammar_entry_create "sequence" - and match_case : 'match_case Grammar.Entry.e = - grammar_entry_create "match_case" - and label_expr : 'label_expr Grammar.Entry.e = - grammar_entry_create "label_expr" - and expr_ident : 'expr_ident Grammar.Entry.e = - grammar_entry_create "expr_ident" - and fun_def : 'fun_def Grammar.Entry.e = grammar_entry_create "fun_def" - and label_patt : 'label_patt Grammar.Entry.e = - grammar_entry_create "label_patt" - and patt_label_ident : 'patt_label_ident Grammar.Entry.e = - grammar_entry_create "patt_label_ident" - and label_ipatt : 'label_ipatt Grammar.Entry.e = - grammar_entry_create "label_ipatt" - and type_declaration : 'type_declaration Grammar.Entry.e = - grammar_entry_create "type_declaration" - and type_patt : 'type_patt Grammar.Entry.e = - grammar_entry_create "type_patt" - and constrain : 'constrain Grammar.Entry.e = - grammar_entry_create "constrain" - and constructor_declaration : 'constructor_declaration Grammar.Entry.e = - grammar_entry_create "constructor_declaration" - and label_declaration : 'label_declaration Grammar.Entry.e = - grammar_entry_create "label_declaration" - and ident : 'ident Grammar.Entry.e = grammar_entry_create "ident" in + and phrase : 'phrase Grammar.Entry.e = grammar_entry_create "phrase" in [Grammar.Entry.obj (interf : 'interf Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("EOI", "")], @@ -278,8 +231,60 @@ Grammar.extend (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); Gramext.Stoken ("", ";")], Gramext.action - (fun _ (sti : 'str_item) (loc : int * int) -> (sti : 'phrase))]]; - Grammar.Entry.obj (module_expr : 'module_expr Grammar.Entry.e), None, + (fun _ (sti : 'str_item) (loc : int * int) -> (sti : 'phrase))]]]);; + +Grammar.extend + (let _ = (sig_item : 'sig_item Grammar.Entry.e) + and _ = (str_item : 'str_item Grammar.Entry.e) + and _ = (ctyp : 'ctyp Grammar.Entry.e) + and _ = (patt : 'patt Grammar.Entry.e) + and _ = (expr : 'expr Grammar.Entry.e) + and _ = (module_type : 'module_type Grammar.Entry.e) + and _ = (module_expr : 'module_expr Grammar.Entry.e) + and _ = (let_binding : 'let_binding Grammar.Entry.e) + and _ = (type_parameter : 'type_parameter Grammar.Entry.e) + and _ = (fun_binding : 'fun_binding Grammar.Entry.e) + and _ = (ipatt : 'ipatt Grammar.Entry.e) + and _ = (direction_flag : 'direction_flag Grammar.Entry.e) + and _ = (mod_ident : 'mod_ident Grammar.Entry.e) in + let grammar_entry_create s = + Grammar.Entry.create (Grammar.of_entry sig_item) s + in + let rebind_exn : 'rebind_exn Grammar.Entry.e = + grammar_entry_create "rebind_exn" + and module_binding : 'module_binding Grammar.Entry.e = + grammar_entry_create "module_binding" + and module_declaration : 'module_declaration Grammar.Entry.e = + grammar_entry_create "module_declaration" + and with_constr : 'with_constr Grammar.Entry.e = + grammar_entry_create "with_constr" + and dummy : 'dummy Grammar.Entry.e = grammar_entry_create "dummy" + and sequence : 'sequence Grammar.Entry.e = grammar_entry_create "sequence" + and match_case : 'match_case Grammar.Entry.e = + grammar_entry_create "match_case" + and label_expr : 'label_expr Grammar.Entry.e = + grammar_entry_create "label_expr" + and expr_ident : 'expr_ident Grammar.Entry.e = + grammar_entry_create "expr_ident" + and fun_def : 'fun_def Grammar.Entry.e = grammar_entry_create "fun_def" + and label_patt : 'label_patt Grammar.Entry.e = + grammar_entry_create "label_patt" + and patt_label_ident : 'patt_label_ident Grammar.Entry.e = + grammar_entry_create "patt_label_ident" + and label_ipatt : 'label_ipatt Grammar.Entry.e = + grammar_entry_create "label_ipatt" + and type_declaration : 'type_declaration Grammar.Entry.e = + grammar_entry_create "type_declaration" + and type_patt : 'type_patt Grammar.Entry.e = + grammar_entry_create "type_patt" + and constrain : 'constrain Grammar.Entry.e = + grammar_entry_create "constrain" + and constructor_declaration : 'constructor_declaration Grammar.Entry.e = + grammar_entry_create "constructor_declaration" + and label_declaration : 'label_declaration Grammar.Entry.e = + grammar_entry_create "label_declaration" + and ident : 'ident Grammar.Entry.e = grammar_entry_create "ident" in + [Grammar.Entry.obj (module_expr : 'module_expr Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("", "struct"); Gramext.Slist0 diff --git a/camlp4/ocaml_src/meta/q_MLast.ml b/camlp4/ocaml_src/meta/q_MLast.ml index e3e4798e0..cebf0540d 100644 --- a/camlp4/ocaml_src/meta/q_MLast.ml +++ b/camlp4/ocaml_src/meta/q_MLast.ml @@ -35,7 +35,6 @@ let str_item = Grammar.Entry.create gram "structure item";; let ctyp = Grammar.Entry.create gram "type";; let patt = Grammar.Entry.create gram "pattern";; let expr = Grammar.Entry.create gram "expression";; -let directive = Grammar.Entry.create gram "directive";; let module_type = Grammar.Entry.create gram "module type";; let module_expr = Grammar.Entry.create gram "module expression";; @@ -118,7 +117,6 @@ Grammar.extend and _ = (ctyp : 'ctyp Grammar.Entry.e) and _ = (patt : 'patt Grammar.Entry.e) and _ = (expr : 'expr Grammar.Entry.e) - and _ = (directive : 'directive Grammar.Entry.e) and _ = (module_type : 'module_type Grammar.Entry.e) and _ = (module_expr : 'module_expr Grammar.Entry.e) and _ = (class_type : 'class_type Grammar.Entry.e) @@ -420,7 +418,7 @@ Grammar.extend Tuple [x1; x2; x3] -> x1, x2, x3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 4588, 4604)) + _ -> raise (Match_failure ("q_MLast.ml", 4521, 4537)) in Node ("StExc", [Loc; c; tl; b]) : 'str_item)); @@ -664,7 +662,7 @@ Grammar.extend Tuple [Loc; c; tl] -> Node ("SgExc", [Loc; c; tl]) | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 6805, 6821)) : + _ -> raise (Match_failure ("q_MLast.ml", 6738, 6754)) : 'sig_item)); [Gramext.Stoken ("", "#"); Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e)); @@ -3380,17 +3378,6 @@ Grammar.extend (x : 'module_expr_eoi))]]]; Quotation.add "module_expr" (apply_entry module_expr_eoi);; -let directive_eoi = Grammar.Entry.create gram "directive" in -Grammar.extend - [Grammar.Entry.obj (directive_eoi : 'directive_eoi Grammar.Entry.e), None, - [None, None, - [[Gramext.Snterm - (Grammar.Entry.obj (directive : 'directive Grammar.Entry.e)); - Gramext.Stoken ("EOI", "")], - Gramext.action - (fun _ (x : 'directive) (loc : int * int) -> (x : 'directive_eoi))]]]; -Quotation.add "directive" (apply_entry directive_eoi);; - let class_type_eoi = Grammar.Entry.create gram "class_type" in Grammar.extend [Grammar.Entry.obj (class_type_eoi : 'class_type_eoi Grammar.Entry.e), None, |