summaryrefslogtreecommitdiffstats
path: root/toplevel
diff options
context:
space:
mode:
authorDaniel de Rauglaudre <daniel.de_rauglaudre@inria.fr>2001-08-04 10:08:19 +0000
committerDaniel de Rauglaudre <daniel.de_rauglaudre@inria.fr>2001-08-04 10:08:19 +0000
commit3b5da7725e93872dcf596dc308c29be3be032f01 (patch)
treee90a159f0fa455ab2ee68e43e4baeace7c329c08 /toplevel
parenta5a1caa494f825523b779ef21b8418803ae970ed (diff)
Personalisation de l'affichage des valeurs et des types dans le toplevel.
Ajouté module Outcometree et des hooks dans le toplevel: print_out_value et print_out_type. (j'ai oublié de mettre un message log dans le 1er commit) git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3612 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'toplevel')
-rw-r--r--toplevel/genprintval.ml14
-rw-r--r--toplevel/toploop.ml1
-rw-r--r--toplevel/toploop.mli1
3 files changed, 4 insertions, 12 deletions
diff --git a/toplevel/genprintval.ml b/toplevel/genprintval.ml
index 842c44d47..384de0130 100644
--- a/toplevel/genprintval.ml
+++ b/toplevel/genprintval.ml
@@ -137,16 +137,6 @@ module Make(O : OBJ)(EVP : EVALPATH with type value = O.t) = struct
(* Print a constructor or label, giving it the same prefix as the type
it comes from. Attempt to omit the prefix if the type comes from
a module that has been opened. *)
- let ident_pervasive = Ident.create_persistent "Pervasives"
- let rec tree_of_type_path = function
- | Pident id ->
- Oide_ident (Ident.name id)
- | Pdot(Pident id, s, pos) when Ident.same id ident_pervasive ->
- Oide_ident s
- | Pdot(p, s, pos) ->
- Oide_dot (tree_of_type_path p, s)
- | Papply(p1, p2) ->
- Oide_apply (tree_of_type_path p1, tree_of_type_path p2)
let tree_of_qualified lookup_fun env ty_path name =
match ty_path with
@@ -159,9 +149,9 @@ module Make(O : OBJ)(EVP : EVALPATH with type value = O.t) = struct
| _ -> false
with Not_found -> false
then Oide_ident name
- else Oide_dot (tree_of_type_path p, name)
+ else Oide_dot (Printtyp.tree_of_path p, name)
| Papply(p1, p2) ->
- tree_of_type_path ty_path
+ Printtyp.tree_of_path ty_path
let tree_of_constr =
tree_of_qualified
diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml
index bc236bf3a..c907683eb 100644
--- a/toplevel/toploop.ml
+++ b/toplevel/toploop.ml
@@ -78,6 +78,7 @@ let max_printer_depth = ref 100
let max_printer_steps = ref 300
let print_out_value = ref Printer.print_outval
+let print_out_type = Printtyp.outcome_type_hook
let print_untyped_exception ppf obj =
!print_out_value ppf (Printer.outval_of_untyped_exception obj)
diff --git a/toplevel/toploop.mli b/toplevel/toploop.mli
index 1e06f29fd..c7d58d844 100644
--- a/toplevel/toploop.mli
+++ b/toplevel/toploop.mli
@@ -78,6 +78,7 @@ val print_warning : Location.t -> formatter -> Warnings.t -> unit
val input_name : string ref
val print_out_value : (formatter -> Outcometree.out_value -> unit) ref
+val print_out_type : (formatter -> Outcometree.out_type -> unit) ref
(* Used by Trace module *)