summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--camlp4/Camlp4/Struct/MetaAst.ml4
-rw-r--r--camlp4/Camlp4Bin.ml4
-rw-r--r--camlp4/Camlp4Printers/Auto.ml22
-rw-r--r--camlp4/Makefile.ml9
-rwxr-xr-xcamlp4/boot/camlp4bootbin1034298 -> 1062207 bytes
5 files changed, 31 insertions, 8 deletions
diff --git a/camlp4/Camlp4/Struct/MetaAst.ml b/camlp4/Camlp4/Struct/MetaAst.ml
index 77434e31a..586099257 100644
--- a/camlp4/Camlp4/Struct/MetaAst.ml
+++ b/camlp4/Camlp4/Struct/MetaAst.ml
@@ -202,7 +202,7 @@ module Make (MetaLoc : META_LOC) = struct
[ <:match_case@_loc<>> -> <:expr< Ast.McNil $meta_loc_expr _loc$ >>
| <:match_case@_loc< $a1$ | $a2$ >> -> <:expr< Ast.McOr $meta_loc_expr _loc$ $meta_a a1$ $meta_a a2$ >>
| <:match_case@_loc< $p$ when $e1$ -> $e2$ >> -> <:expr< Ast.McArr $meta_loc_expr _loc$ $meta_p p$ $meta_e e1$ $meta_e e2$ >>
- | Ast.McAnt _loc s -> <:expr< $anti:s$ >> ]
+ | <:match_case@_loc< $anti:s$ >> -> <:expr< $anti:s$ >> ]
and binding = fun
[ <:binding@_loc<>> -> <:expr< Ast.BiNil $meta_loc_expr _loc$ >>
@@ -508,7 +508,7 @@ module Make (MetaLoc : META_LOC) = struct
[ <:match_case@_loc<>> -> <:patt< Ast.McNil $meta_loc_patt _loc$ >>
| <:match_case@_loc< $a1$ | $a2$ >> -> <:patt< Ast.McOr $meta_loc_patt _loc$ $meta_a a1$ $meta_a a2$ >>
| <:match_case@_loc< $p$ when $e1$ -> $e2$ >> -> <:patt< Ast.McArr $meta_loc_patt _loc$ $meta_p p$ $meta_e e1$ $meta_e e2$ >>
- | Ast.McAnt _loc s -> <:patt< $anti:s$ >> ]
+ | <:match_case@_loc< $anti:s$ >> -> <:patt< $anti:s$ >> ]
and binding = fun
[ <:binding@_loc<>> -> <:patt< Ast.BiNil $meta_loc_patt _loc$ >>
diff --git a/camlp4/Camlp4Bin.ml b/camlp4/Camlp4Bin.ml
index 095cf0965..15246b529 100644
--- a/camlp4/Camlp4Bin.ml
+++ b/camlp4/Camlp4Bin.ml
@@ -84,8 +84,10 @@ value rewrite_and_load n x =
Camlp4.Printers.OCaml.enable ()
| ("Printers"|"", "pr_dump.cmo" | "p" | "DumpOCamlAst" | "Camlp4Printers/DumpOCamlAst.cmo") ->
Camlp4.Printers.DumpOCamlAst.enable ()
- | ("Printers"|"", "d" | "DumpCamlp4Ast" | "Camlp4Printers/DumpCamlp4Ast") ->
+ | ("Printers"|"", "d" | "DumpCamlp4Ast" | "Camlp4Printers/DumpCamlp4Ast.cmo") ->
Camlp4.Printers.DumpCamlp4Ast.enable ()
+ | ("Printers"|"", "a" | "Auto" | "Camlp4Printers/Auto.cmo") ->
+ load ["Camlp4Printers.Auto"]
| _ ->
let y = "Camlp4"^n^"/"^x^".cmo" in
real_load (try find_in_path y with [ Not_found -> x ]) ];
diff --git a/camlp4/Camlp4Printers/Auto.ml b/camlp4/Camlp4Printers/Auto.ml
new file mode 100644
index 000000000..8aa41c9af
--- /dev/null
+++ b/camlp4/Camlp4Printers/Auto.ml
@@ -0,0 +1,22 @@
+(****************************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* INRIA Rocquencourt *)
+(* *)
+(* Copyright 2006 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed under *)
+(* the terms of the GNU Library General Public License, with the special *)
+(* exception on linking described in LICENSE at the top of the Objective *)
+(* Caml source tree. *)
+(* *)
+(****************************************************************************)
+
+(* Authors:
+ * - Nicolas Pouillard: initial version
+ *)
+
+if (Unix.fstat Unix.stdout).Unix.st_kind = Unix.S_CHR then
+ Camlp4.Printers.OCaml.enable ()
+else
+ Camlp4.Printers.DumpOCamlAst.enable ();
diff --git a/camlp4/Makefile.ml b/camlp4/Makefile.ml
index 52d075b12..c17d6d9c4 100644
--- a/camlp4/Makefile.ml
+++ b/camlp4/Makefile.ml
@@ -254,6 +254,7 @@ let fi_tracer = ocaml_Module "Camlp4Filters/Tracer"
let camlp4_bin = ocaml_Module "Camlp4Bin"
let top_rprint = ocaml_Module "Camlp4Top/Rprint"
let top_camlp4_top = ocaml_Module "Camlp4Top/Camlp4Top"
+let camlp4Profiler = ocaml_IModule "Camlp4Profiler"
let byte_programs = ref []
let opt_programs = ref []
@@ -261,10 +262,7 @@ let byte_libraries = ref []
let opt_libraries = ref []
let special_modules =
- if Sys.file_exists "./boot/Profiler.cmo" then
- [ocaml_IModule "Camlp4Profiler"]
- else []
-
+ if Sys.file_exists "./boot/Profiler.cmo" then [camlp4Profiler] else []
let mk_camlp4_top_lib name modules =
byte_libraries += (name ^ ".cma");
@@ -406,7 +404,8 @@ let all =
mk_camlp4 "camlp4o" [pa_r; pa_o; pa_rp; pa_op; pr_a];
mk_camlp4 "camlp4of" [pa_r; pa_qb; pa_rq; pa_o; pa_rp; pa_op; pa_g; pa_macro; pr_a];
mk_camlp4_tool "mkcamlp4" [ocaml_Module ~o:(options_without_debug ()) "mkcamlp4"];
- mk_camlp4_tool "camlp4prof" [ocaml_Module ~o:(options_without_debug ()) "camlp4prof"];
+ mk_camlp4_tool "camlp4prof"
+ [camlp4Profiler; ocaml_Module ~o:(options_without_debug ()) "camlp4prof"];
mk_camlp4_top_lib "camlp4r" [pa_r; pa_rp; top_rprint];
mk_camlp4_top_lib "camlp4rf" [pa_r; pa_rp; pa_qb; pa_q; pa_g; pa_macro; top_rprint];
mk_camlp4_top_lib "camlp4o" [pa_r; pa_o; pa_rp; pa_op];
diff --git a/camlp4/boot/camlp4boot b/camlp4/boot/camlp4boot
index 0a5c173fb..ec6438fe7 100755
--- a/camlp4/boot/camlp4boot
+++ b/camlp4/boot/camlp4boot
Binary files differ