Topeval
val getvalue : string -> Obj.t
val setvalue : string -> Obj.t -> unit
val execute_phrase :
bool ->
Format.formatter ->
Parsetree.toplevel_phrase ->
bool
val may_trace : bool ref
module EvalBase : Topcommon.EVAL_BASE
val eval_address : Env.address -> Obj.t
module Printer : sig ... end
val print_value :
Env.t ->
Printer.t ->
Format.formatter ->
Types.type_expr ->
unit
val print_untyped_exception : Format.formatter -> Printer.t -> unit
val print_exception_outcome : Format.formatter -> exn -> unit
val outval_of_value :
Env.t ->
Printer.t ->
Types.type_expr ->
Outcometree.out_value
type (!'a, !'b) gen_printer =
('a, 'b) Topcommon.MakeEvalPrinter(EvalBase).gen_printer =
| Zero of 'b
| Succ of 'a -> ('a, 'b) gen_printer
val install_printer :
Path.t ->
Types.type_expr ->
(Format.formatter -> Printer.t -> unit) ->
unit
val install_generic_printer :
Path.t ->
Path.t ->
(int ->
(int ->
Printer.t ->
Outcometree.out_value,
Printer.t ->
Outcometree.out_value)
gen_printer) ->
unit
val install_generic_printer' :
Path.t ->
Path.t ->
(Format.formatter ->
Printer.t ->
unit,
Format.formatter ->
Printer.t ->
unit)
gen_printer ->
unit
val remove_printer : Path.t -> unit
val load_file : bool -> Format.formatter -> string -> bool