diff options
author | Daniel de Rauglaudre <daniel.de_rauglaudre@inria.fr> | 2002-01-26 12:44:30 +0000 |
---|---|---|
committer | Daniel de Rauglaudre <daniel.de_rauglaudre@inria.fr> | 2002-01-26 12:44:30 +0000 |
commit | 80718ed845abf34ef3f96e7ee6d6e7e8d69d3af7 (patch) | |
tree | ced3128ca6985b358d565d429cf4432030381a08 /camlp4 | |
parent | 055eb887acabb62019d4612c6cee836cd135117f (diff) |
-
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4319 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4')
-rw-r--r-- | camlp4/meta/pa_r.ml | 71 | ||||
-rw-r--r-- | camlp4/meta/q_MLast.ml | 108 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/pa_r.ml | 326 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/q_MLast.ml | 654 |
4 files changed, 592 insertions, 567 deletions
diff --git a/camlp4/meta/pa_r.ml b/camlp4/meta/pa_r.ml index 903de0f7b..feab2fa0b 100644 --- a/camlp4/meta/pa_r.ml +++ b/camlp4/meta/pa_r.ml @@ -186,43 +186,6 @@ Pcaml.add_option "-no_warn_seq" (Arg.Clear not_yet_warned) " No warning when using old syntax for sequences."; EXTEND - GLOBAL: interf implem use_file top_phrase; - interf: - [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> - ([(<:sig_item< # $n$ $opt:dp$ >>, loc)], True) - | si = sig_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped) - | EOI -> ([], False) ] ] - ; - sig_item_semi: - [ [ si = sig_item; ";" -> (si, loc) ] ] - ; - implem: - [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> - ([(<:str_item< # $n$ $opt:dp$ >>, loc)], True) - | si = str_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped) - | EOI -> ([], False) ] ] - ; - str_item_semi: - [ [ si = str_item; ";" -> (si, loc) ] ] - ; - top_phrase: - [ [ ph = phrase -> Some ph - | EOI -> None ] ] - ; - use_file: - [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> - ([ <:str_item< # $n$ $opt:dp$ >>], True) - | si = str_item; ";"; (sil, stopped) = SELF -> ([si :: sil], stopped) - | EOI -> ([], False) ] ] - ; - phrase: - [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> - <:str_item< # $n$ $opt:dp$ >> - | sti = str_item; ";" -> sti ] ] - ; -END; - -EXTEND GLOBAL: sig_item str_item ctyp patt expr module_type module_expr class_type class_expr class_sig_item class_str_item let_binding ipatt; module_expr: @@ -883,6 +846,40 @@ EXTEND END; EXTEND + GLOBAL: interf implem use_file top_phrase expr patt; + interf: + [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> + ([(<:sig_item< # $n$ $opt:dp$ >>, loc)], True) + | si = sig_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped) + | EOI -> ([], False) ] ] + ; + sig_item_semi: + [ [ si = sig_item; ";" -> (si, loc) ] ] + ; + implem: + [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> + ([(<:str_item< # $n$ $opt:dp$ >>, loc)], True) + | si = str_item_semi; (sil, stopped) = SELF -> ([si :: sil], stopped) + | EOI -> ([], False) ] ] + ; + str_item_semi: + [ [ si = str_item; ";" -> (si, loc) ] ] + ; + top_phrase: + [ [ ph = phrase -> Some ph + | EOI -> None ] ] + ; + use_file: + [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> + ([ <:str_item< # $n$ $opt:dp$ >>], True) + | si = str_item; ";"; (sil, stopped) = SELF -> ([si :: sil], stopped) + | EOI -> ([], False) ] ] + ; + phrase: + [ [ "#"; n = LIDENT; dp = OPT expr; ";" -> + <:str_item< # $n$ $opt:dp$ >> + | sti = str_item; ";" -> sti ] ] + ; expr: LEVEL "simple" [ [ x = LOCATE -> let x = diff --git a/camlp4/meta/q_MLast.ml b/camlp4/meta/q_MLast.ml index a7ef19429..d9916b3f1 100644 --- a/camlp4/meta/q_MLast.ml +++ b/camlp4/meta/q_MLast.ml @@ -57,6 +57,17 @@ value class_str_item = Grammar.Entry.create gram "class structure item"; value ipatt = Grammar.Entry.create gram "ipatt"; value let_binding = Grammar.Entry.create gram "let_binding"; +value a_list = Grammar.Entry.create gram "a_list"; +value a_opt = Grammar.Entry.create gram "a_opt"; +value a_UIDENT = Grammar.Entry.create gram "a_UIDENT"; +value a_LIDENT = Grammar.Entry.create gram "a_LIDENT"; +value a_INT = Grammar.Entry.create gram "a_INT"; +value a_FLOAT = Grammar.Entry.create gram "a_FLOAT"; +value a_STRING = Grammar.Entry.create gram "a_STRING"; +value a_CHAR = Grammar.Entry.create gram "a_CHAR"; +value a_TILDEIDENT = Grammar.Entry.create gram "a_TILDEIDENT"; +value a_QUESTIONIDENT = Grammar.Entry.create gram "a_QUESTIONIDENT"; + value o2b = fun [ Qast.Option (Some _) -> Qast.Bool True @@ -1067,7 +1078,54 @@ EXTEND warning_sequence: [ [ -> warning_seq () ] ] ; - (* Antiquotations *) + (* Antiquotations for local entries *) + sequence: + [ [ a = ANTIQUOT "list" -> antiquot "list" loc a ] ] + ; + expr_ident: + [ [ a = ANTIQUOT -> antiquot "" loc a ] ] + ; + patt_label_ident: LEVEL "simple" + [ [ a = ANTIQUOT -> antiquot "" loc a ] ] + ; + when_expr_opt: + [ [ a = ANTIQUOT "when" -> antiquot "when" loc a ] ] + ; + mod_ident: + [ [ a = ANTIQUOT -> antiquot "" loc a ] ] + ; + as_lident_opt: + [ [ a = ANTIQUOT "as" -> antiquot "as" loc a ] ] + ; + meth_list: + [ [ a = a_list -> Qast.Tuple [a; Qast.Bool False] + | a = a_list; b = ANTIQUOT -> Qast.Tuple [a; antiquot "" loc b] ] ] + ; + clty_longident: + [ [ a = a_list -> a ] ] + ; + class_longident: + [ [ a = a_list -> a ] ] + ; + rec_flag: + [ [ a = ANTIQUOT "rec" -> antiquot "rec" loc a ] ] + ; + direction_flag: + [ [ a = ANTIQUOT "to" -> antiquot "to" loc a ] ] + ; + mutable_flag: + [ [ a = ANTIQUOT "mut" -> antiquot "mut" loc a ] ] + ; + virtual_flag: + [ [ a = ANTIQUOT "virt" -> antiquot "virt" loc a ] ] + ; + amp_flag: + [ [ a = ANTIQUOT "opt" -> antiquot "opt" loc a ] ] + ; +END; + +EXTEND + GLOBAL: str_item sig_item; str_item: [ [ "#"; n = a_LIDENT; dp = dir_param -> Qast.Node "StDir" [Qast.Loc; n; dp] ] ] @@ -1081,6 +1139,11 @@ EXTEND | e = expr -> Qast.Option (Some e) | -> Qast.Option None ] ] ; +END; + +(* Antiquotations *) + +EXTEND module_expr: LEVEL "simple" [ [ a = ANTIQUOT "mexp" -> antiquot "mexp" loc a | a = ANTIQUOT -> antiquot "" loc a ] ] @@ -1104,12 +1167,6 @@ EXTEND Qast.Node "ExAnt" [Qast.Loc; antiquot "anti" loc a] | "("; el = a_list; ")" -> Qast.Node "ExTup" [Qast.Loc; el] ] ] ; - sequence: - [ [ a = ANTIQUOT "list" -> antiquot "list" loc a ] ] - ; - expr_ident: - [ [ a = ANTIQUOT -> antiquot "" loc a ] ] - ; patt: LEVEL "simple" [ [ a = ANTIQUOT "pat" -> antiquot "pat" loc a | a = ANTIQUOT -> antiquot "" loc a @@ -1117,12 +1174,6 @@ EXTEND Qast.Node "PaAnt" [Qast.Loc; antiquot "anti" loc a] | "("; pl = a_list; ")" -> Qast.Node "PaTup" [Qast.Loc; pl] ] ] ; - patt_label_ident: LEVEL "simple" - [ [ a = ANTIQUOT -> antiquot "" loc a ] ] - ; - when_expr_opt: - [ [ a = ANTIQUOT "when" -> antiquot "when" loc a ] ] - ; ipatt: [ [ a = ANTIQUOT "pat" -> antiquot "pat" loc a | a = ANTIQUOT -> antiquot "" loc a @@ -1135,9 +1186,6 @@ EXTEND | a = ANTIQUOT -> antiquot "" loc a | "("; tl = a_list; ")" -> Qast.Node "TyTup" [Qast.Loc; tl] ] ] ; - mod_ident: - [ [ a = ANTIQUOT -> antiquot "" loc a ] ] - ; class_expr: LEVEL "simple" [ [ a = ANTIQUOT -> antiquot "" loc a ] ] ; @@ -1150,22 +1198,9 @@ EXTEND class_type: [ [ a = ANTIQUOT -> antiquot "" loc a ] ] ; - as_lident_opt: - [ [ a = ANTIQUOT "as" -> antiquot "as" loc a ] ] - ; - meth_list: - [ [ a = a_list -> Qast.Tuple [a; Qast.Bool False] - | a = a_list; b = ANTIQUOT -> Qast.Tuple [a; antiquot "" loc b] ] ] - ; expr: LEVEL "simple" [ [ "{<"; fel = a_list; ">}" -> Qast.Node "ExOvr" [Qast.Loc; fel] ] ] ; - clty_longident: - [ [ a = a_list -> a ] ] - ; - class_longident: - [ [ a = a_list -> a ] ] - ; patt: LEVEL "simple" [ [ "#"; a = a_list -> Qast.Node "PaTyp" [Qast.Loc; a] ] ] ; @@ -1213,21 +1248,6 @@ EXTEND [ [ "?"; a = ANTIQUOT -> antiquot "" loc a | s = QUESTIONIDENT -> Qast.Str s ] ] ; - rec_flag: - [ [ a = ANTIQUOT "rec" -> antiquot "rec" loc a ] ] - ; - direction_flag: - [ [ a = ANTIQUOT "to" -> antiquot "to" loc a ] ] - ; - mutable_flag: - [ [ a = ANTIQUOT "mut" -> antiquot "mut" loc a ] ] - ; - virtual_flag: - [ [ a = ANTIQUOT "virt" -> antiquot "virt" loc a ] ] - ; - amp_flag: - [ [ a = ANTIQUOT "opt" -> antiquot "opt" loc a ] ] - ; END; value loc = (0, 0); diff --git a/camlp4/ocaml_src/meta/pa_r.ml b/camlp4/ocaml_src/meta/pa_r.ml index c80749eef..510724c8d 100644 --- a/camlp4/ocaml_src/meta/pa_r.ml +++ b/camlp4/ocaml_src/meta/pa_r.ml @@ -189,111 +189,6 @@ Pcaml.add_option "-no_warn_seq" (Arg.Clear not_yet_warned) " No warning when using old syntax for sequences.";; Grammar.extend - (let _ = (interf : 'interf Grammar.Entry.e) - and _ = (implem : 'implem Grammar.Entry.e) - and _ = (use_file : 'use_file Grammar.Entry.e) - and _ = (top_phrase : 'top_phrase Grammar.Entry.e) in - let grammar_entry_create s = - Grammar.Entry.create (Grammar.of_entry interf) s - in - let sig_item_semi : 'sig_item_semi Grammar.Entry.e = - 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" in - [Grammar.Entry.obj (interf : 'interf Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("EOI", "")], - Gramext.action (fun _ (loc : int * int) -> ([], false : 'interf)); - [Gramext.Snterm - (Grammar.Entry.obj (sig_item_semi : 'sig_item_semi Grammar.Entry.e)); - Gramext.Sself], - Gramext.action - (fun (sil, stopped : 'interf) (si : 'sig_item_semi) - (loc : int * int) -> - (si :: sil, stopped : 'interf)); - [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); - Gramext.Sopt - (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> - ([MLast.SgDir (loc, n, dp), loc], true : 'interf))]]; - Grammar.Entry.obj (sig_item_semi : 'sig_item_semi Grammar.Entry.e), None, - [None, None, - [[Gramext.Snterm - (Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e)); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (si : 'sig_item) (loc : int * int) -> - (si, loc : 'sig_item_semi))]]; - Grammar.Entry.obj (implem : 'implem Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("EOI", "")], - Gramext.action (fun _ (loc : int * int) -> ([], false : 'implem)); - [Gramext.Snterm - (Grammar.Entry.obj (str_item_semi : 'str_item_semi Grammar.Entry.e)); - Gramext.Sself], - Gramext.action - (fun (sil, stopped : 'implem) (si : 'str_item_semi) - (loc : int * int) -> - (si :: sil, stopped : 'implem)); - [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); - Gramext.Sopt - (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> - ([MLast.StDir (loc, n, dp), loc], true : 'implem))]]; - Grammar.Entry.obj (str_item_semi : 'str_item_semi Grammar.Entry.e), None, - [None, None, - [[Gramext.Snterm - (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (si : 'str_item) (loc : int * int) -> - (si, loc : 'str_item_semi))]]; - Grammar.Entry.obj (top_phrase : 'top_phrase Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("EOI", "")], - Gramext.action (fun _ (loc : int * int) -> (None : 'top_phrase)); - [Gramext.Snterm (Grammar.Entry.obj (phrase : 'phrase Grammar.Entry.e))], - Gramext.action - (fun (ph : 'phrase) (loc : int * int) -> (Some ph : 'top_phrase))]]; - Grammar.Entry.obj (use_file : 'use_file Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("EOI", "")], - Gramext.action (fun _ (loc : int * int) -> ([], false : 'use_file)); - [Gramext.Snterm - (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); - Gramext.Stoken ("", ";"); Gramext.Sself], - Gramext.action - (fun (sil, stopped : 'use_file) _ (si : 'str_item) - (loc : int * int) -> - (si :: sil, stopped : 'use_file)); - [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); - Gramext.Sopt - (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> - ([MLast.StDir (loc, n, dp)], true : 'use_file))]]; - Grammar.Entry.obj (phrase : 'phrase Grammar.Entry.e), None, - [None, None, - [[Gramext.Snterm - (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (sti : 'str_item) (loc : int * int) -> (sti : 'phrase)); - [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); - Gramext.Sopt - (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); - Gramext.Stoken ("", ";")], - Gramext.action - (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> - (MLast.StDir (loc, n, dp) : '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) @@ -2649,61 +2544,166 @@ Grammar.extend (fun (loc : int * int) -> (warning_seq () : 'warning_sequence))]]]);; Grammar.extend - [Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("QUOTATION", "")], - Gramext.action - (fun (x : string) (loc : int * int) -> - (let x = - try - let i = String.index x ':' in - String.sub x 0 i, - String.sub x (i + 1) (String.length x - i - 1) - with - Not_found -> "", x - in - Pcaml.handle_expr_quotation loc x : - 'expr)); - [Gramext.Stoken ("LOCATE", "")], - Gramext.action - (fun (x : string) (loc : int * int) -> - (let x = - try - let i = String.index x ':' in - int_of_string (String.sub x 0 i), - String.sub x (i + 1) (String.length x - i - 1) - with - Not_found | Failure _ -> 0, x - in - Pcaml.handle_expr_locate loc x : - 'expr))]]; - Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("QUOTATION", "")], - Gramext.action - (fun (x : string) (loc : int * int) -> - (let x = - try - let i = String.index x ':' in - String.sub x 0 i, - String.sub x (i + 1) (String.length x - i - 1) - with - Not_found -> "", x - in - Pcaml.handle_patt_quotation loc x : - 'patt)); - [Gramext.Stoken ("LOCATE", "")], - Gramext.action - (fun (x : string) (loc : int * int) -> - (let x = - try - let i = String.index x ':' in - int_of_string (String.sub x 0 i), - String.sub x (i + 1) (String.length x - i - 1) - with - Not_found | Failure _ -> 0, x - in - Pcaml.handle_patt_locate loc x : - 'patt))]]];; + (let _ = (interf : 'interf Grammar.Entry.e) + and _ = (implem : 'implem Grammar.Entry.e) + and _ = (use_file : 'use_file Grammar.Entry.e) + and _ = (top_phrase : 'top_phrase Grammar.Entry.e) + and _ = (expr : 'expr Grammar.Entry.e) + and _ = (patt : 'patt Grammar.Entry.e) in + let grammar_entry_create s = + Grammar.Entry.create (Grammar.of_entry interf) s + in + let sig_item_semi : 'sig_item_semi Grammar.Entry.e = + 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" in + [Grammar.Entry.obj (interf : 'interf Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("EOI", "")], + Gramext.action (fun _ (loc : int * int) -> ([], false : 'interf)); + [Gramext.Snterm + (Grammar.Entry.obj (sig_item_semi : 'sig_item_semi Grammar.Entry.e)); + Gramext.Sself], + Gramext.action + (fun (sil, stopped : 'interf) (si : 'sig_item_semi) + (loc : int * int) -> + (si :: sil, stopped : 'interf)); + [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); + Gramext.Sopt + (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> + ([MLast.SgDir (loc, n, dp), loc], true : 'interf))]]; + Grammar.Entry.obj (sig_item_semi : 'sig_item_semi Grammar.Entry.e), None, + [None, None, + [[Gramext.Snterm + (Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e)); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (si : 'sig_item) (loc : int * int) -> + (si, loc : 'sig_item_semi))]]; + Grammar.Entry.obj (implem : 'implem Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("EOI", "")], + Gramext.action (fun _ (loc : int * int) -> ([], false : 'implem)); + [Gramext.Snterm + (Grammar.Entry.obj (str_item_semi : 'str_item_semi Grammar.Entry.e)); + Gramext.Sself], + Gramext.action + (fun (sil, stopped : 'implem) (si : 'str_item_semi) + (loc : int * int) -> + (si :: sil, stopped : 'implem)); + [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); + Gramext.Sopt + (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> + ([MLast.StDir (loc, n, dp), loc], true : 'implem))]]; + Grammar.Entry.obj (str_item_semi : 'str_item_semi Grammar.Entry.e), None, + [None, None, + [[Gramext.Snterm + (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (si : 'str_item) (loc : int * int) -> + (si, loc : 'str_item_semi))]]; + Grammar.Entry.obj (top_phrase : 'top_phrase Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("EOI", "")], + Gramext.action (fun _ (loc : int * int) -> (None : 'top_phrase)); + [Gramext.Snterm (Grammar.Entry.obj (phrase : 'phrase Grammar.Entry.e))], + Gramext.action + (fun (ph : 'phrase) (loc : int * int) -> (Some ph : 'top_phrase))]]; + Grammar.Entry.obj (use_file : 'use_file Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("EOI", "")], + Gramext.action (fun _ (loc : int * int) -> ([], false : 'use_file)); + [Gramext.Snterm + (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); + Gramext.Stoken ("", ";"); Gramext.Sself], + Gramext.action + (fun (sil, stopped : 'use_file) _ (si : 'str_item) + (loc : int * int) -> + (si :: sil, stopped : 'use_file)); + [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); + Gramext.Sopt + (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> + ([MLast.StDir (loc, n, dp)], true : 'use_file))]]; + Grammar.Entry.obj (phrase : 'phrase Grammar.Entry.e), None, + [None, None, + [[Gramext.Snterm + (Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e)); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (sti : 'str_item) (loc : int * int) -> (sti : 'phrase)); + [Gramext.Stoken ("", "#"); Gramext.Stoken ("LIDENT", ""); + Gramext.Sopt + (Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))); + Gramext.Stoken ("", ";")], + Gramext.action + (fun _ (dp : 'expr option) (n : string) _ (loc : int * int) -> + (MLast.StDir (loc, n, dp) : 'phrase))]]; + Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("QUOTATION", "")], + Gramext.action + (fun (x : string) (loc : int * int) -> + (let x = + try + let i = String.index x ':' in + String.sub x 0 i, + String.sub x (i + 1) (String.length x - i - 1) + with + Not_found -> "", x + in + Pcaml.handle_expr_quotation loc x : + 'expr)); + [Gramext.Stoken ("LOCATE", "")], + Gramext.action + (fun (x : string) (loc : int * int) -> + (let x = + try + let i = String.index x ':' in + int_of_string (String.sub x 0 i), + String.sub x (i + 1) (String.length x - i - 1) + with + Not_found | Failure _ -> 0, x + in + Pcaml.handle_expr_locate loc x : + 'expr))]]; + Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("QUOTATION", "")], + Gramext.action + (fun (x : string) (loc : int * int) -> + (let x = + try + let i = String.index x ':' in + String.sub x 0 i, + String.sub x (i + 1) (String.length x - i - 1) + with + Not_found -> "", x + in + Pcaml.handle_patt_quotation loc x : + 'patt)); + [Gramext.Stoken ("LOCATE", "")], + Gramext.action + (fun (x : string) (loc : int * int) -> + (let x = + try + let i = String.index x ':' in + int_of_string (String.sub x 0 i), + String.sub x (i + 1) (String.length x - i - 1) + with + Not_found | Failure _ -> 0, x + in + Pcaml.handle_patt_locate loc x : + 'patt))]]]);; diff --git a/camlp4/ocaml_src/meta/q_MLast.ml b/camlp4/ocaml_src/meta/q_MLast.ml index 9f970d568..6fb4cfe61 100644 --- a/camlp4/ocaml_src/meta/q_MLast.ml +++ b/camlp4/ocaml_src/meta/q_MLast.ml @@ -57,6 +57,17 @@ let class_str_item = Grammar.Entry.create gram "class structure item";; let ipatt = Grammar.Entry.create gram "ipatt";; let let_binding = Grammar.Entry.create gram "let_binding";; +let a_list = Grammar.Entry.create gram "a_list";; +let a_opt = Grammar.Entry.create gram "a_opt";; +let a_UIDENT = Grammar.Entry.create gram "a_UIDENT";; +let a_LIDENT = Grammar.Entry.create gram "a_LIDENT";; +let a_INT = Grammar.Entry.create gram "a_INT";; +let a_FLOAT = Grammar.Entry.create gram "a_FLOAT";; +let a_STRING = Grammar.Entry.create gram "a_STRING";; +let a_CHAR = Grammar.Entry.create gram "a_CHAR";; +let a_TILDEIDENT = Grammar.Entry.create gram "a_TILDEIDENT";; +let a_QUESTIONIDENT = Grammar.Entry.create gram "a_QUESTIONIDENT";; + let o2b = function Qast.Option (Some _) -> Qast.Bool true @@ -285,8 +296,6 @@ Grammar.extend and name_tag : 'name_tag Grammar.Entry.e = grammar_entry_create "name_tag" and warning_sequence : 'warning_sequence Grammar.Entry.e = grammar_entry_create "warning_sequence" - and dir_param : 'dir_param Grammar.Entry.e = - grammar_entry_create "dir_param" and sequence : 'sequence Grammar.Entry.e = grammar_entry_create "sequence" and expr_ident : 'expr_ident Grammar.Entry.e = grammar_entry_create "expr_ident" @@ -304,18 +313,6 @@ Grammar.extend grammar_entry_create "clty_longident" and class_longident : 'class_longident Grammar.Entry.e = grammar_entry_create "class_longident" - and a_list : 'a_list Grammar.Entry.e = grammar_entry_create "a_list" - and a_opt : 'a_opt Grammar.Entry.e = grammar_entry_create "a_opt" - and a_UIDENT : 'a_UIDENT Grammar.Entry.e = grammar_entry_create "a_UIDENT" - and a_LIDENT : 'a_LIDENT Grammar.Entry.e = grammar_entry_create "a_LIDENT" - and a_INT : 'a_INT Grammar.Entry.e = grammar_entry_create "a_INT" - and a_FLOAT : 'a_FLOAT Grammar.Entry.e = grammar_entry_create "a_FLOAT" - and a_STRING : 'a_STRING Grammar.Entry.e = grammar_entry_create "a_STRING" - and a_CHAR : 'a_CHAR Grammar.Entry.e = grammar_entry_create "a_CHAR" - and a_TILDEIDENT : 'a_TILDEIDENT Grammar.Entry.e = - grammar_entry_create "a_TILDEIDENT" - and a_QUESTIONIDENT : 'a_QUESTIONIDENT Grammar.Entry.e = - grammar_entry_create "a_QUESTIONIDENT" and rec_flag : 'rec_flag Grammar.Entry.e = grammar_entry_create "rec_flag" and direction_flag : 'direction_flag Grammar.Entry.e = grammar_entry_create "direction_flag" @@ -497,7 +494,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 6683, 6699)) + _ -> raise (Match_failure ("q_MLast.ml", 7234, 7250)) in Qast.Node ("StExc", [Qast.Loc; c; tl; b]) : 'str_item)); @@ -728,7 +725,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 8896, 8912)) + _ -> raise (Match_failure ("q_MLast.ml", 9447, 9463)) in Qast.Node ("SgExc", [Qast.Loc; c; tl]) : 'sig_item)); @@ -2522,7 +2519,7 @@ Grammar.extend Qast.Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 29488, 29504)) + _ -> raise (Match_failure ("q_MLast.ml", 30039, 30055)) in Qast.Node ("CrVal", [Qast.Loc; lab; mf; e]) : 'class_str_item)); @@ -2917,7 +2914,7 @@ Grammar.extend Qast.Tuple [xx1; xx2] -> xx1, xx2 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 34055, 34071)) + _ -> raise (Match_failure ("q_MLast.ml", 34606, 34622)) in Qast.Node ("TyObj", [Qast.Loc; ml; v]) : 'ctyp)); @@ -2952,7 +2949,7 @@ Grammar.extend Qast.Tuple [xx1; xx2] -> xx1, xx2 | _ -> match () with - _ -> raise (Match_failure ("q_MLast.ml", 34402, 34418)) + _ -> raise (Match_failure ("q_MLast.ml", 34953, 34969)) in Qast.Tuple [Qast.Cons (f, ml); v] : 'meth_list))]]; @@ -3529,103 +3526,6 @@ Grammar.extend [[], Gramext.action (fun (loc : int * int) -> (warning_seq () : 'warning_sequence))]]; - Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("", "#"); - Gramext.Snterm - (Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e)); - Gramext.Snterm - (Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e))], - Gramext.action - (fun (dp : 'dir_param) (n : 'a_LIDENT) _ (loc : int * int) -> - (Qast.Node ("StDir", [Qast.Loc; n; dp]) : 'str_item))]]; - Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("", "#"); - Gramext.Snterm - (Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e)); - Gramext.Snterm - (Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e))], - Gramext.action - (fun (dp : 'dir_param) (n : 'a_LIDENT) _ (loc : int * int) -> - (Qast.Node ("SgDir", [Qast.Loc; n; dp]) : 'sig_item))]]; - Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e), None, - [None, None, - [[], - Gramext.action - (fun (loc : int * int) -> (Qast.Option None : 'dir_param)); - [Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))], - Gramext.action - (fun (e : 'expr) (loc : int * int) -> - (Qast.Option (Some e) : 'dir_param)); - [Gramext.Stoken ("ANTIQUOT", "opt")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "opt" loc a : 'dir_param))]]; - Grammar.Entry.obj (module_expr : 'module_expr Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'module_expr)); - [Gramext.Stoken ("ANTIQUOT", "mexp")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "mexp" loc a : 'module_expr))]]; - Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e), - Some (Gramext.Level "top"), - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'str_item)); - [Gramext.Stoken ("ANTIQUOT", "stri")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "stri" loc a : 'str_item))]]; - Grammar.Entry.obj (module_type : 'module_type Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'module_type)); - [Gramext.Stoken ("ANTIQUOT", "mtyp")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "mtyp" loc a : 'module_type))]]; - Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e), - Some (Gramext.Level "top"), - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'sig_item)); - [Gramext.Stoken ("ANTIQUOT", "sigi")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "sigi" loc a : 'sig_item))]]; - Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("", "("); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); - Gramext.Stoken ("", ")")], - Gramext.action - (fun _ (el : 'a_list) _ (loc : int * int) -> - (Qast.Node ("ExTup", [Qast.Loc; el]) : 'expr)); - [Gramext.Stoken ("ANTIQUOT", "anti")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (Qast.Node ("ExAnt", [Qast.Loc; antiquot "anti" loc a]) : 'expr)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'expr)); - [Gramext.Stoken ("ANTIQUOT", "exp")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "exp" loc a : 'expr))]]; Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("ANTIQUOT", "list")], @@ -3638,26 +3538,6 @@ Grammar.extend Gramext.action (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'expr_ident))]]; - Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("", "("); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); - Gramext.Stoken ("", ")")], - Gramext.action - (fun _ (pl : 'a_list) _ (loc : int * int) -> - (Qast.Node ("PaTup", [Qast.Loc; pl]) : 'patt)); - [Gramext.Stoken ("ANTIQUOT", "anti")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (Qast.Node ("PaAnt", [Qast.Loc; antiquot "anti" loc a]) : 'patt)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'patt)); - [Gramext.Stoken ("ANTIQUOT", "pat")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "pat" loc a : 'patt))]]; Grammar.Entry.obj (patt_label_ident : 'patt_label_ident Grammar.Entry.e), Some (Gramext.Level "simple"), [None, None, @@ -3671,74 +3551,12 @@ Grammar.extend Gramext.action (fun (a : string) (loc : int * int) -> (antiquot "when" loc a : 'when_expr_opt))]]; - Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("", "("); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); - Gramext.Stoken ("", ")")], - Gramext.action - (fun _ (pl : 'a_list) _ (loc : int * int) -> - (Qast.Node ("PaTup", [Qast.Loc; pl]) : 'ipatt)); - [Gramext.Stoken ("ANTIQUOT", "anti")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (Qast.Node ("PaAnt", [Qast.Loc; antiquot "anti" loc a]) : 'ipatt)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'ipatt)); - [Gramext.Stoken ("ANTIQUOT", "pat")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "pat" loc a : 'ipatt))]]; - Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("", "("); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); - Gramext.Stoken ("", ")")], - Gramext.action - (fun _ (tl : 'a_list) _ (loc : int * int) -> - (Qast.Node ("TyTup", [Qast.Loc; tl]) : 'ctyp)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'ctyp)); - [Gramext.Stoken ("ANTIQUOT", "typ")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "typ" loc a : 'ctyp))]]; Grammar.Entry.obj (mod_ident : 'mod_ident Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("ANTIQUOT", "")], Gramext.action (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'mod_ident))]]; - Grammar.Entry.obj (class_expr : 'class_expr Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'class_expr))]]; - Grammar.Entry.obj (class_str_item : 'class_str_item Grammar.Entry.e), - None, - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'class_str_item))]]; - Grammar.Entry.obj (class_sig_item : 'class_sig_item Grammar.Entry.e), - None, - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'class_sig_item))]]; - Grammar.Entry.obj (class_type : 'class_type Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'class_type))]]; Grammar.Entry.obj (as_lident_opt : 'as_lident_opt Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("ANTIQUOT", "as")], @@ -3756,15 +3574,6 @@ Grammar.extend Gramext.action (fun (a : 'a_list) (loc : int * int) -> (Qast.Tuple [a; Qast.Bool false] : 'meth_list))]]; - Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("", "{<"); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); - Gramext.Stoken ("", ">}")], - Gramext.action - (fun _ (fel : 'a_list) _ (loc : int * int) -> - (Qast.Node ("ExOvr", [Qast.Loc; fel]) : 'expr))]]; Grammar.Entry.obj (clty_longident : 'clty_longident Grammar.Entry.e), None, [None, None, @@ -3777,122 +3586,6 @@ Grammar.extend [[Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e))], Gramext.action (fun (a : 'a_list) (loc : int * int) -> (a : 'class_longident))]]; - Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), - Some (Gramext.Level "simple"), - [None, None, - [[Gramext.Stoken ("", "#"); - Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e))], - Gramext.action - (fun (a : 'a_list) _ (loc : int * int) -> - (Qast.Node ("PaTyp", [Qast.Loc; a]) : 'patt))]]; - Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "list")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "list" loc a : 'a_list))]]; - Grammar.Entry.obj (a_opt : 'a_opt Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("ANTIQUOT", "opt")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "opt" loc a : 'a_opt))]]; - Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("UIDENT", "")], - Gramext.action - (fun (i : string) (loc : int * int) -> (Qast.Str i : 'a_UIDENT)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'a_UIDENT)); - [Gramext.Stoken ("ANTIQUOT", "uid")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "uid" loc a : 'a_UIDENT))]]; - Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("LIDENT", "")], - Gramext.action - (fun (i : string) (loc : int * int) -> (Qast.Str i : 'a_LIDENT)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'a_LIDENT)); - [Gramext.Stoken ("ANTIQUOT", "lid")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "lid" loc a : 'a_LIDENT))]]; - Grammar.Entry.obj (a_INT : 'a_INT Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("INT", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_INT)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_INT)); - [Gramext.Stoken ("ANTIQUOT", "int")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "int" loc a : 'a_INT))]]; - Grammar.Entry.obj (a_FLOAT : 'a_FLOAT Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("FLOAT", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_FLOAT)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'a_FLOAT)); - [Gramext.Stoken ("ANTIQUOT", "flo")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "flo" loc a : 'a_FLOAT))]]; - Grammar.Entry.obj (a_STRING : 'a_STRING Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("STRING", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_STRING)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "" loc a : 'a_STRING)); - [Gramext.Stoken ("ANTIQUOT", "str")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "str" loc a : 'a_STRING))]]; - Grammar.Entry.obj (a_CHAR : 'a_CHAR Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("CHAR", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_CHAR)); - [Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_CHAR)); - [Gramext.Stoken ("ANTIQUOT", "chr")], - Gramext.action - (fun (a : string) (loc : int * int) -> - (antiquot "chr" loc a : 'a_CHAR))]]; - Grammar.Entry.obj (a_TILDEIDENT : 'a_TILDEIDENT Grammar.Entry.e), None, - [None, None, - [[Gramext.Stoken ("TILDEIDENT", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_TILDEIDENT)); - [Gramext.Stoken ("", "~"); Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) _ (loc : int * int) -> - (antiquot "" loc a : 'a_TILDEIDENT))]]; - Grammar.Entry.obj (a_QUESTIONIDENT : 'a_QUESTIONIDENT Grammar.Entry.e), - None, - [None, None, - [[Gramext.Stoken ("QUESTIONIDENT", "")], - Gramext.action - (fun (s : string) (loc : int * int) -> - (Qast.Str s : 'a_QUESTIONIDENT)); - [Gramext.Stoken ("", "?"); Gramext.Stoken ("ANTIQUOT", "")], - Gramext.action - (fun (a : string) _ (loc : int * int) -> - (antiquot "" loc a : 'a_QUESTIONIDENT))]]; Grammar.Entry.obj (rec_flag : 'rec_flag Grammar.Entry.e), None, [None, None, [[Gramext.Stoken ("ANTIQUOT", "rec")], @@ -3925,6 +3618,321 @@ Grammar.extend (fun (a : string) (loc : int * int) -> (antiquot "opt" loc a : 'amp_flag))]]]);; +Grammar.extend + (let _ = (str_item : 'str_item Grammar.Entry.e) + and _ = (sig_item : 'sig_item Grammar.Entry.e) in + let grammar_entry_create s = + Grammar.Entry.create (Grammar.of_entry str_item) s + in + let dir_param : 'dir_param Grammar.Entry.e = + grammar_entry_create "dir_param" + in + [Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("", "#"); + Gramext.Snterm + (Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e)); + Gramext.Snterm + (Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e))], + Gramext.action + (fun (dp : 'dir_param) (n : 'a_LIDENT) _ (loc : int * int) -> + (Qast.Node ("StDir", [Qast.Loc; n; dp]) : 'str_item))]]; + Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("", "#"); + Gramext.Snterm + (Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e)); + Gramext.Snterm + (Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e))], + Gramext.action + (fun (dp : 'dir_param) (n : 'a_LIDENT) _ (loc : int * int) -> + (Qast.Node ("SgDir", [Qast.Loc; n; dp]) : 'sig_item))]]; + Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e), None, + [None, None, + [[], + Gramext.action + (fun (loc : int * int) -> (Qast.Option None : 'dir_param)); + [Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))], + Gramext.action + (fun (e : 'expr) (loc : int * int) -> + (Qast.Option (Some e) : 'dir_param)); + [Gramext.Stoken ("ANTIQUOT", "opt")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "opt" loc a : 'dir_param))]]]);; + +(* Antiquotations *) + +Grammar.extend + [Grammar.Entry.obj (module_expr : 'module_expr Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'module_expr)); + [Gramext.Stoken ("ANTIQUOT", "mexp")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "mexp" loc a : 'module_expr))]]; + Grammar.Entry.obj (str_item : 'str_item Grammar.Entry.e), + Some (Gramext.Level "top"), + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'str_item)); + [Gramext.Stoken ("ANTIQUOT", "stri")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "stri" loc a : 'str_item))]]; + Grammar.Entry.obj (module_type : 'module_type Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'module_type)); + [Gramext.Stoken ("ANTIQUOT", "mtyp")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "mtyp" loc a : 'module_type))]]; + Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e), + Some (Gramext.Level "top"), + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'sig_item)); + [Gramext.Stoken ("ANTIQUOT", "sigi")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "sigi" loc a : 'sig_item))]]; + Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("", "("); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); + Gramext.Stoken ("", ")")], + Gramext.action + (fun _ (el : 'a_list) _ (loc : int * int) -> + (Qast.Node ("ExTup", [Qast.Loc; el]) : 'expr)); + [Gramext.Stoken ("ANTIQUOT", "anti")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (Qast.Node ("ExAnt", [Qast.Loc; antiquot "anti" loc a]) : 'expr)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'expr)); + [Gramext.Stoken ("ANTIQUOT", "exp")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "exp" loc a : 'expr))]]; + Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("", "("); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); + Gramext.Stoken ("", ")")], + Gramext.action + (fun _ (pl : 'a_list) _ (loc : int * int) -> + (Qast.Node ("PaTup", [Qast.Loc; pl]) : 'patt)); + [Gramext.Stoken ("ANTIQUOT", "anti")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (Qast.Node ("PaAnt", [Qast.Loc; antiquot "anti" loc a]) : 'patt)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'patt)); + [Gramext.Stoken ("ANTIQUOT", "pat")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "pat" loc a : 'patt))]]; + Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("", "("); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); + Gramext.Stoken ("", ")")], + Gramext.action + (fun _ (pl : 'a_list) _ (loc : int * int) -> + (Qast.Node ("PaTup", [Qast.Loc; pl]) : 'ipatt)); + [Gramext.Stoken ("ANTIQUOT", "anti")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (Qast.Node ("PaAnt", [Qast.Loc; antiquot "anti" loc a]) : 'ipatt)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'ipatt)); + [Gramext.Stoken ("ANTIQUOT", "pat")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "pat" loc a : 'ipatt))]]; + Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("", "("); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); + Gramext.Stoken ("", ")")], + Gramext.action + (fun _ (tl : 'a_list) _ (loc : int * int) -> + (Qast.Node ("TyTup", [Qast.Loc; tl]) : 'ctyp)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'ctyp)); + [Gramext.Stoken ("ANTIQUOT", "typ")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "typ" loc a : 'ctyp))]]; + Grammar.Entry.obj (class_expr : 'class_expr Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'class_expr))]]; + Grammar.Entry.obj (class_str_item : 'class_str_item Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'class_str_item))]]; + Grammar.Entry.obj (class_sig_item : 'class_sig_item Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'class_sig_item))]]; + Grammar.Entry.obj (class_type : 'class_type Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'class_type))]]; + Grammar.Entry.obj (expr : 'expr Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("", "{<"); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e)); + Gramext.Stoken ("", ">}")], + Gramext.action + (fun _ (fel : 'a_list) _ (loc : int * int) -> + (Qast.Node ("ExOvr", [Qast.Loc; fel]) : 'expr))]]; + Grammar.Entry.obj (patt : 'patt Grammar.Entry.e), + Some (Gramext.Level "simple"), + [None, None, + [[Gramext.Stoken ("", "#"); + Gramext.Snterm (Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e))], + Gramext.action + (fun (a : 'a_list) _ (loc : int * int) -> + (Qast.Node ("PaTyp", [Qast.Loc; a]) : 'patt))]]; + Grammar.Entry.obj (a_list : 'a_list Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "list")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "list" loc a : 'a_list))]]; + Grammar.Entry.obj (a_opt : 'a_opt Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("ANTIQUOT", "opt")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "opt" loc a : 'a_opt))]]; + Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("UIDENT", "")], + Gramext.action + (fun (i : string) (loc : int * int) -> (Qast.Str i : 'a_UIDENT)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'a_UIDENT)); + [Gramext.Stoken ("ANTIQUOT", "uid")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "uid" loc a : 'a_UIDENT))]]; + Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("LIDENT", "")], + Gramext.action + (fun (i : string) (loc : int * int) -> (Qast.Str i : 'a_LIDENT)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'a_LIDENT)); + [Gramext.Stoken ("ANTIQUOT", "lid")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "lid" loc a : 'a_LIDENT))]]; + Grammar.Entry.obj (a_INT : 'a_INT Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("INT", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_INT)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_INT)); + [Gramext.Stoken ("ANTIQUOT", "int")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "int" loc a : 'a_INT))]]; + Grammar.Entry.obj (a_FLOAT : 'a_FLOAT Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("FLOAT", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_FLOAT)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_FLOAT)); + [Gramext.Stoken ("ANTIQUOT", "flo")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "flo" loc a : 'a_FLOAT))]]; + Grammar.Entry.obj (a_STRING : 'a_STRING Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("STRING", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_STRING)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "" loc a : 'a_STRING)); + [Gramext.Stoken ("ANTIQUOT", "str")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "str" loc a : 'a_STRING))]]; + Grammar.Entry.obj (a_CHAR : 'a_CHAR Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("CHAR", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_CHAR)); + [Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) (loc : int * int) -> (antiquot "" loc a : 'a_CHAR)); + [Gramext.Stoken ("ANTIQUOT", "chr")], + Gramext.action + (fun (a : string) (loc : int * int) -> + (antiquot "chr" loc a : 'a_CHAR))]]; + Grammar.Entry.obj (a_TILDEIDENT : 'a_TILDEIDENT Grammar.Entry.e), None, + [None, None, + [[Gramext.Stoken ("TILDEIDENT", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> (Qast.Str s : 'a_TILDEIDENT)); + [Gramext.Stoken ("", "~"); Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) _ (loc : int * int) -> + (antiquot "" loc a : 'a_TILDEIDENT))]]; + Grammar.Entry.obj (a_QUESTIONIDENT : 'a_QUESTIONIDENT Grammar.Entry.e), + None, + [None, None, + [[Gramext.Stoken ("QUESTIONIDENT", "")], + Gramext.action + (fun (s : string) (loc : int * int) -> + (Qast.Str s : 'a_QUESTIONIDENT)); + [Gramext.Stoken ("", "?"); Gramext.Stoken ("ANTIQUOT", "")], + Gramext.action + (fun (a : string) _ (loc : int * int) -> + (antiquot "" loc a : 'a_QUESTIONIDENT))]]];; + let loc = 0, 0;; let rec expr_of_ast = |