Topevalval getvalue : string -> Obj.tval setvalue : string -> Obj.t -> unitval execute_phrase :
bool ->
Format.formatter ->
Parsetree.toplevel_phrase ->
boolval may_trace : bool refmodule EvalBase : Topcommon.EVAL_BASEval eval_address : Env.address -> Obj.tmodule Printer : sig ... endval print_value :
Env.t ->
Printer.t ->
Format.formatter ->
Types.type_expr ->
unitval print_untyped_exception : Format.formatter -> Printer.t -> unitval print_exception_outcome : Format.formatter -> exn -> unitval outval_of_value :
Env.t ->
Printer.t ->
Types.type_expr ->
Outcometree.out_valuetype (!'a, !'b) gen_printer =
('a, 'b) Topcommon.MakeEvalPrinter(EvalBase).gen_printer =
| Zero of 'b| Succ of 'a -> ('a, 'b) gen_printerval install_printer :
Path.t ->
Types.type_expr ->
(Format.formatter -> Printer.t -> unit) ->
unitval install_generic_printer :
Path.t ->
Path.t ->
(int ->
(int ->
Printer.t ->
Outcometree.out_value,
Printer.t ->
Outcometree.out_value)
gen_printer) ->
unitval install_generic_printer' :
Path.t ->
Path.t ->
(Format.formatter ->
Printer.t ->
unit,
Format.formatter ->
Printer.t ->
unit)
gen_printer ->
unitval remove_printer : Path.t -> unitval load_file : bool -> Format.formatter -> string -> bool