Toploopval getvalue : string -> Obj.tval setvalue : string -> Obj.t -> unitval loop : Format.formatter -> unitval run_script : Format.formatter -> string -> string array -> booltype directive_fun = | | Directive_none of unit -> unit | 
| | Directive_string of string -> unit | 
| | Directive_int of int -> unit | 
| | Directive_ident of Longident.t -> unit | 
| | Directive_bool of bool -> unit | 
val add_directive : string -> directive_fun -> directive_info -> unitval directive_table : (string, directive_fun) Hashtbl.tval directive_info_table : (string, directive_info) Hashtbl.tval print_exception_outcome : Format.formatter -> exn -> unitval execute_phrase : bool -> Format.formatter -> Parsetree.toplevel_phrase -> boolval preprocess_phrase : Format.formatter -> Parsetree.toplevel_phrase -> Parsetree.toplevel_phraseval use_file : Format.formatter -> string -> boolval use_output : Format.formatter -> string -> boolval use_silently : Format.formatter -> string -> boolval mod_use_file : Format.formatter -> string -> boolval print_value : Env.t -> Obj.t -> Format.formatter -> Types.type_expr -> unitval print_untyped_exception : Format.formatter -> Obj.t -> unitval install_printer : Path.t -> Types.type_expr -> (Format.formatter -> Obj.t -> unit) -> unitval install_generic_printer : Path.t -> Path.t -> (int -> (int -> Obj.t -> Outcometree.out_value, Obj.t -> Outcometree.out_value) gen_printer) -> unitval install_generic_printer' : Path.t -> Path.t -> (Format.formatter -> Obj.t -> unit, Format.formatter -> Obj.t -> unit) gen_printer -> unitval remove_printer : Path.t -> unitval max_printer_depth : int refval max_printer_steps : int refval parse_toplevel_phrase : (Lexing.lexbuf -> Parsetree.toplevel_phrase) refval parse_use_file : (Lexing.lexbuf -> Parsetree.toplevel_phrase list) refval print_location : Format.formatter -> Location.t -> unitval print_error : Format.formatter -> Location.error -> unitval print_warning : Location.t -> Format.formatter -> Warnings.t -> unitval input_name : string refval print_out_value : (Format.formatter -> Outcometree.out_value -> unit) refval print_out_type : (Format.formatter -> Outcometree.out_type -> unit) refval print_out_class_type : (Format.formatter -> Outcometree.out_class_type -> unit) refval print_out_module_type : (Format.formatter -> Outcometree.out_module_type -> unit) refval print_out_type_extension : (Format.formatter -> Outcometree.out_type_extension -> unit) refval print_out_sig_item : (Format.formatter -> Outcometree.out_sig_item -> unit) refval print_out_signature : (Format.formatter -> Outcometree.out_sig_item list -> unit) refval print_out_phrase : (Format.formatter -> Outcometree.out_phrase -> unit) refval read_interactive_input : (string -> bytes -> int -> int * bool) refval toplevel_startup_hook : (unit -> unit) refval add_hook : (event -> unit) -> unitval run_hooks : event -> unitval may_trace : bool ref