camlp4: remove the buggy/unfinished Camlp4Tracer filter.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9055 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
db5e084aa2
commit
2446372311
|
@ -90,7 +90,6 @@ value rewrite_and_load n x =
|
|||
| ("Filters"|"", "meta" | "camlp4metagenerator.cmo") -> load ["Camlp4MetaGenerator"]
|
||||
| ("Filters"|"", "trash" | "camlp4trashremover.cmo") -> load ["Camlp4TrashRemover"]
|
||||
| ("Filters"|"", "striploc" | "camlp4locationstripper.cmo") -> load ["Camlp4LocationStripper"]
|
||||
| ("Filters"|"", "tracer" | "camlp4tracer.cmo") -> load ["Camlp4Tracer"]
|
||||
| ("Printers"|"", "pr_r.cmo" | "r" | "ocamlr" | "camlp4ocamlrevisedprinter.cmo") ->
|
||||
Register.enable_ocamlr_printer ()
|
||||
| ("Printers"|"", "pr_o.cmo" | "o" | "ocaml" | "camlp4ocamlprinter.cmo") ->
|
||||
|
|
|
@ -1,58 +0,0 @@
|
|||
(* camlp4r *)
|
||||
(****************************************************************************)
|
||||
(* *)
|
||||
(* 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
|
||||
*)
|
||||
|
||||
|
||||
open Camlp4;
|
||||
|
||||
module Id = struct
|
||||
value name = "Camlp4Tracer";
|
||||
value version = "$Id$";
|
||||
end;
|
||||
|
||||
module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
|
||||
open AstFilters;
|
||||
open Ast;
|
||||
|
||||
value add_debug_expr e =
|
||||
(* let _loc = Loc.make_absolute (MLast.loc_of_expr e) in *)
|
||||
let _loc = Ast.loc_of_expr e in
|
||||
let msg = "camlp4-debug: tracer: %s at " ^ Loc.to_string _loc ^ "@." in
|
||||
<:expr< do { if Debug.mode "tracer" then
|
||||
Format.eprintf $`str:msg$ (Printexc.to_string exc)
|
||||
else ();
|
||||
$e$ } >>;
|
||||
|
||||
value rec map_match_case =
|
||||
fun
|
||||
[ <:match_case@_loc< $m1$ | $m2$ >> ->
|
||||
<:match_case< $map_match_case m1$ | $map_match_case m2$ >>
|
||||
| <:match_case@_loc< $p$ when $w$ -> $e$ >> ->
|
||||
<:match_case@_loc< $p$ when $w$ -> $add_debug_expr e$ >>
|
||||
| m -> m ]
|
||||
|
||||
and map_expr =
|
||||
fun
|
||||
[ <:expr@_loc< fun [ $m$ ] >> -> <:expr< fun [ $map_match_case m$ ] >>
|
||||
| x -> x ];
|
||||
|
||||
register_str_item_filter (Ast.map_expr map_expr)#str_item;
|
||||
|
||||
end;
|
||||
|
||||
let module M = Camlp4.Register.AstFilter Id Make in ();
|
|
@ -14013,8 +14013,6 @@ module B =
|
|||
load [ "Camlp4TrashRemover" ]
|
||||
| (("Filters" | ""), ("striploc" | "camlp4locationstripper.cmo"))
|
||||
-> load [ "Camlp4LocationStripper" ]
|
||||
| (("Filters" | ""), ("tracer" | "camlp4tracer.cmo")) ->
|
||||
load [ "Camlp4Tracer" ]
|
||||
| (("Printers" | ""),
|
||||
("pr_r.cmo" | "r" | "ocamlr" | "camlp4ocamlrevisedprinter.cmo"))
|
||||
-> Register.enable_ocamlr_printer ()
|
||||
|
|
|
@ -30,7 +30,6 @@ Camlp4Filters/Camlp4LocationStripper
|
|||
Camlp4Filters/Camlp4MapGenerator
|
||||
Camlp4Filters/Camlp4MetaGenerator
|
||||
Camlp4Filters/Camlp4Profiler
|
||||
Camlp4Filters/Camlp4Tracer
|
||||
Camlp4Filters/Camlp4TrashRemover
|
||||
|
||||
Camlp4Top
|
||||
|
|
|
@ -721,7 +721,6 @@ let pr_r = pr "Camlp4OCamlRevisedPrinter"
|
|||
let pr_o = pr "Camlp4OCamlPrinter"
|
||||
let pr_a = pr "Camlp4AutoPrinter"
|
||||
let fi_exc = fi "Camlp4ExceptionTracer"
|
||||
let fi_tracer = fi "Camlp4Tracer"
|
||||
let fi_meta = fi "MetaGenerator"
|
||||
let camlp4_bin = p4 "Camlp4Bin"
|
||||
let top_rprint = top "Rprint"
|
||||
|
|
Loading…
Reference in New Issue