toplevel: be explicit about what path are used for

From: Pierre Chambart <pierre.chambart@ocamlpro.com>

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15635 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Gabriel Scherer 2014-12-06 17:11:11 +00:00
parent 5f58cc7d3f
commit f0cee36d3a
2 changed files with 8 additions and 5 deletions

View File

@ -159,15 +159,16 @@ module Make(O : OBJ)(EVP : EVALPATH with type valu = O.t) = struct
let printer obj = Oval_printer (fun ppf -> print_val ppf obj) in
printers := (path, Simple (ty, printer)) :: !printers
let install_generic_printer path ty_path fn =
printers := (path, Generic (ty_path, fn)) :: !printers
let install_generic_printer function_path constr_path fn =
printers := (function_path, Generic (constr_path, fn)) :: !printers
let install_generic_printer' path ty_path fn =
let install_generic_printer' function_path ty_path fn =
let rec build gp depth =
match gp with
| Zero fn ->
let out_printer obj =
let printer ppf = try fn ppf obj with _ -> exn_printer ppf path in
let printer ppf =
try fn ppf obj with _ -> exn_printer ppf function_path in
Oval_printer printer in
Zero out_printer
| Succ fn ->
@ -176,7 +177,7 @@ module Make(O : OBJ)(EVP : EVALPATH with type valu = O.t) = struct
!Oprint.out_value ppf (fn_arg (depth+1) o) in
build (fn print_arg) depth in
Succ print_val in
printers := (path, Generic (ty_path, build fn)) :: !printers
printers := (function_path, Generic (ty_path, build fn)) :: !printers
let remove_printer path =
let rec remove = function

View File

@ -52,6 +52,8 @@ module type S =
(formatter -> t -> unit,
formatter -> t -> unit) gen_printer ->
unit
(** [install_generic_printer' function_path constructor_path printer]
function_path is used to remove the printer. *)
val remove_printer : Path.t -> unit
val outval_of_untyped_exception : t -> Outcometree.out_value
val outval_of_value :