diff options
-rw-r--r-- | camlp4/CHANGES | 3 | ||||
-rw-r--r-- | camlp4/camlp4/argl.ml | 8 | ||||
-rw-r--r-- | camlp4/camlp4/pcaml.ml | 3 | ||||
-rw-r--r-- | camlp4/camlp4/pcaml.mli | 5 | ||||
-rw-r--r-- | camlp4/etc/pa_lisp.ml | 3 | ||||
-rw-r--r-- | camlp4/etc/pa_lispr.ml | 3 | ||||
-rw-r--r-- | camlp4/etc/pa_o.ml | 3 | ||||
-rw-r--r-- | camlp4/etc/pa_olabl.ml | 3 | ||||
-rw-r--r-- | camlp4/etc/pa_sml.ml | 3 | ||||
-rw-r--r-- | camlp4/meta/pa_r.ml | 3 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/argl.ml | 10 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/pcaml.ml | 11 | ||||
-rw-r--r-- | camlp4/ocaml_src/camlp4/pcaml.mli | 5 | ||||
-rw-r--r-- | camlp4/ocaml_src/meta/pa_r.ml | 3 |
14 files changed, 56 insertions, 10 deletions
diff --git a/camlp4/CHANGES b/camlp4/CHANGES index afa93a8eb..1cb8d1a5a 100644 --- a/camlp4/CHANGES +++ b/camlp4/CHANGES @@ -1,6 +1,9 @@ Camlp4 Version 3.04 ------------------- +- [07 Dec 01] Added Pcaml.parse_interf and Pcaml.parse_implem, hooks to + specify the parsers tof use, i.e. now can use other parsing technics + than the Camlp4 grammar system. - [27 Nov 01] Fixed functions Token.eval_char and Token.eval_string which returned bad values, resulting lexing of backslash sequences incompatible with OCaml (e.g. "\1" returned "\001" (one character) but OCaml returns diff --git a/camlp4/camlp4/argl.ml b/camlp4/camlp4/argl.ml index 902ea5b11..28382374c 100644 --- a/camlp4/camlp4/argl.ml +++ b/camlp4/camlp4/argl.ml @@ -106,7 +106,7 @@ value process pa pr getdir = let phr = try loop () where rec loop () = - let (pl, stopped_at_directive) = Grammar.Entry.parse pa cs in + let (pl, stopped_at_directive) = pa cs in if stopped_at_directive then do { match getdir (List.rev pl) with [ Some x -> @@ -142,8 +142,10 @@ value gimd = | _ -> None ] ; -value process_intf () = process Pcaml.interf Pcaml.print_interf.val gind; -value process_impl () = process Pcaml.implem Pcaml.print_implem.val gimd; +value process_intf () = + process Pcaml.parse_interf.val Pcaml.print_interf.val gind; +value process_impl () = + process Pcaml.parse_implem.val Pcaml.print_implem.val gimd; type file_kind = [ Intf diff --git a/camlp4/camlp4/pcaml.ml b/camlp4/camlp4/pcaml.ml index 99e528e08..35237e23d 100644 --- a/camlp4/camlp4/pcaml.ml +++ b/camlp4/camlp4/pcaml.ml @@ -39,6 +39,9 @@ value class_str_item = Grammar.Entry.create gram "class_str_item"; value class_type = Grammar.Entry.create gram "class_type"; value class_expr = Grammar.Entry.create gram "class_expr"; +value parse_interf = ref (Grammar.Entry.parse interf); +value parse_implem = ref (Grammar.Entry.parse implem); + value rec skip_to_eol cs = match Stream.peek cs with [ Some '\n' -> () diff --git a/camlp4/camlp4/pcaml.mli b/camlp4/camlp4/pcaml.mli index a33463a1a..6fe681fab 100644 --- a/camlp4/camlp4/pcaml.mli +++ b/camlp4/camlp4/pcaml.mli @@ -19,6 +19,11 @@ (* Parsers *) +value parse_interf : + ref (Stream.t char -> (list (MLast.sig_item * MLast.loc) * bool)); +value parse_implem : + ref (Stream.t char -> (list (MLast.str_item * MLast.loc) * bool)); + value gram : Grammar.g; value interf : Grammar.Entry.e (list (MLast.sig_item * MLast.loc) * bool); value implem : Grammar.Entry.e (list (MLast.str_item * MLast.loc) * bool); diff --git a/camlp4/etc/pa_lisp.ml b/camlp4/etc/pa_lisp.ml index 98867b085..9c15424e1 100644 --- a/camlp4/etc/pa_lisp.ml +++ b/camlp4/etc/pa_lisp.ml @@ -629,6 +629,9 @@ (Grammar.Unsafe.clear_entry class_sig_item) (Grammar.Unsafe.clear_entry class_str_item)) +(:= Pcaml.parse_interf.val (Grammar.Entry.parse interf)) +(:= Pcaml.parse_implem.val (Grammar.Entry.parse implem)) + (value sexpr (Grammar.Entry.create gram "sexpr")) (value atom (Grammar.Entry.create gram "atom")) diff --git a/camlp4/etc/pa_lispr.ml b/camlp4/etc/pa_lispr.ml index 6c85ff3d0..c8fb5110d 100644 --- a/camlp4/etc/pa_lispr.ml +++ b/camlp4/etc/pa_lispr.ml @@ -610,6 +610,9 @@ do { Grammar.Unsafe.clear_entry class_str_item }; +Pcaml.parse_interf.val := Grammar.Entry.parse interf; +Pcaml.parse_implem.val := Grammar.Entry.parse implem; + value sexpr = Grammar.Entry.create gram "sexpr"; value atom = Grammar.Entry.create gram "atom"; diff --git a/camlp4/etc/pa_o.ml b/camlp4/etc/pa_o.ml index 2f20414ec..1a46fec8e 100644 --- a/camlp4/etc/pa_o.ml +++ b/camlp4/etc/pa_o.ml @@ -40,6 +40,9 @@ do { Grammar.Unsafe.clear_entry class_str_item }; +Pcaml.parse_interf.val := Grammar.Entry.parse interf; +Pcaml.parse_implem.val := Grammar.Entry.parse implem; + value o2b = fun [ Some _ -> True diff --git a/camlp4/etc/pa_olabl.ml b/camlp4/etc/pa_olabl.ml index 0b4ff1cf9..590b97d4b 100644 --- a/camlp4/etc/pa_olabl.ml +++ b/camlp4/etc/pa_olabl.ml @@ -608,6 +608,9 @@ do { Grammar.Unsafe.clear_entry class_str_item }; +Pcaml.parse_interf.val := Grammar.Entry.parse interf; +Pcaml.parse_implem.val := Grammar.Entry.parse implem; + value o2b = fun [ Some _ -> True diff --git a/camlp4/etc/pa_sml.ml b/camlp4/etc/pa_sml.ml index be2d42e0c..a7f2214cc 100644 --- a/camlp4/etc/pa_sml.ml +++ b/camlp4/etc/pa_sml.ml @@ -33,6 +33,9 @@ do { Grammar.Unsafe.clear_entry let_binding; }; +Pcaml.parse_interf.val := Grammar.Entry.parse interf; +Pcaml.parse_implem.val := Grammar.Entry.parse implem; + value not_impl loc s = raise_with_loc loc (Stream.Error ("not implemented feature [" ^ s ^ "]")) ; diff --git a/camlp4/meta/pa_r.ml b/camlp4/meta/pa_r.ml index 5f5e43af9..b978748a5 100644 --- a/camlp4/meta/pa_r.ml +++ b/camlp4/meta/pa_r.ml @@ -60,6 +60,9 @@ do { Grammar.Unsafe.clear_entry class_str_item }; +Pcaml.parse_interf.val := Grammar.Entry.parse interf; +Pcaml.parse_implem.val := Grammar.Entry.parse implem; + value o2b = fun [ Some _ -> True diff --git a/camlp4/ocaml_src/camlp4/argl.ml b/camlp4/ocaml_src/camlp4/argl.ml index 0b1993021..331038f25 100644 --- a/camlp4/ocaml_src/camlp4/argl.ml +++ b/camlp4/ocaml_src/camlp4/argl.ml @@ -116,7 +116,7 @@ let process pa pr getdir = let phr = try let rec loop () = - let (pl, stopped_at_directive) = Grammar.Entry.parse pa cs in + let (pl, stopped_at_directive) = pa cs in if stopped_at_directive then begin begin match getdir (List.rev pl) with @@ -154,8 +154,12 @@ let gimd = | _ -> None ;; -let process_intf () = process Pcaml.interf !(Pcaml.print_interf) gind;; -let process_impl () = process Pcaml.implem !(Pcaml.print_implem) gimd;; +let process_intf () = + process !(Pcaml.parse_interf) !(Pcaml.print_interf) gind +;; +let process_impl () = + process !(Pcaml.parse_implem) !(Pcaml.print_implem) gimd +;; type file_kind = Intf | Impl;; let file_kind = ref Intf;; diff --git a/camlp4/ocaml_src/camlp4/pcaml.ml b/camlp4/ocaml_src/camlp4/pcaml.ml index 84777cbbb..79c4ed656 100644 --- a/camlp4/ocaml_src/camlp4/pcaml.ml +++ b/camlp4/ocaml_src/camlp4/pcaml.ml @@ -41,6 +41,9 @@ let class_str_item = Grammar.Entry.create gram "class_str_item";; let class_type = Grammar.Entry.create gram "class_type";; let class_expr = Grammar.Entry.create gram "class_expr";; +let parse_interf = ref (Grammar.Entry.parse interf);; +let parse_implem = ref (Grammar.Entry.parse implem);; + let rec skip_to_eol cs = match Stream.peek cs with Some '\n' -> () @@ -333,22 +336,22 @@ and kont = pretty Stream.t let pr_str_item = {pr_fun = - (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11510, 11516))); + (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11621, 11627))); pr_levels = []} ;; let pr_sig_item = {pr_fun = - (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11565, 11571))); + (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11676, 11682))); pr_levels = []} ;; let pr_expr = {pr_fun = - (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11616, 11622))); + (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11727, 11733))); pr_levels = []} ;; let pr_patt = {pr_fun = - (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11667, 11673))); + (fun _ -> raise (Match_failure ("camlp4/pcaml.ml", 11778, 11784))); pr_levels = []} ;; let pr_expr_fun_args = ref Extfun.empty;; diff --git a/camlp4/ocaml_src/camlp4/pcaml.mli b/camlp4/ocaml_src/camlp4/pcaml.mli index 58e7f06d6..ca46f9dc3 100644 --- a/camlp4/ocaml_src/camlp4/pcaml.mli +++ b/camlp4/ocaml_src/camlp4/pcaml.mli @@ -19,6 +19,11 @@ (* Parsers *) +val parse_interf : + (char Stream.t -> (MLast.sig_item * MLast.loc) list * bool) ref;; +val parse_implem : + (char Stream.t -> (MLast.str_item * MLast.loc) list * bool) ref;; + val gram : Grammar.g;; val interf : ((MLast.sig_item * MLast.loc) list * bool) Grammar.Entry.e;; val implem : ((MLast.str_item * MLast.loc) list * bool) Grammar.Entry.e;; diff --git a/camlp4/ocaml_src/meta/pa_r.ml b/camlp4/ocaml_src/meta/pa_r.ml index 126a956d4..46c51ee33 100644 --- a/camlp4/ocaml_src/meta/pa_r.ml +++ b/camlp4/ocaml_src/meta/pa_r.ml @@ -56,6 +56,9 @@ Grammar.Unsafe.clear_entry class_expr; Grammar.Unsafe.clear_entry class_sig_item; Grammar.Unsafe.clear_entry class_str_item;; +Pcaml.parse_interf := Grammar.Entry.parse interf;; +Pcaml.parse_implem := Grammar.Entry.parse implem;; + let o2b = function Some _ -> true |