val getvalue : string -> Stdlib.Obj.tval setvalue : string -> Stdlib.Obj.t -> unitval set_paths : unit -> unitval loop : Stdlib.Format.formatter -> unitval run_script : Stdlib.Format.formatter -> string -> string array -> bool
type 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 -> unittype directive_info = {section : string;doc : string;}
val add_directive : string -> directive_fun -> directive_info -> unitval directive_table : (string, directive_fun) Stdlib.Hashtbl.tval directive_info_table : (string, directive_info) Stdlib.Hashtbl.tval toplevel_env : Env.t Stdlib.refval initialize_toplevel_env : unit -> unitval print_exception_outcome : Stdlib.Format.formatter -> exn -> unitval execute_phrase : bool -> Stdlib.Format.formatter -> Parsetree.toplevel_phrase -> boolval preprocess_phrase : Stdlib.Format.formatter -> Parsetree.toplevel_phrase -> Parsetree.toplevel_phraseval use_file : Stdlib.Format.formatter -> string -> boolval use_silently : Stdlib.Format.formatter -> string -> boolval mod_use_file : Stdlib.Format.formatter -> string -> boolval eval_module_path : Env.t -> Path.t -> Stdlib.Obj.tval eval_value_path : Env.t -> Path.t -> Stdlib.Obj.tval eval_extension_path : Env.t -> Path.t -> Stdlib.Obj.tval eval_class_path : Env.t -> Path.t -> Stdlib.Obj.tval record_backtrace : unit -> unitval print_value : Env.t -> Stdlib.Obj.t -> Stdlib.Format.formatter -> Types.type_expr -> unitval print_untyped_exception : Stdlib.Format.formatter -> Stdlib.Obj.t -> unit
type ('a, 'b) gen_printer =| Zero of 'b| Succ of 'a -> ('a, 'b) gen_printer
val install_printer : Path.t -> Types.type_expr -> (Stdlib.Format.formatter -> Stdlib.Obj.t -> unit) -> unitval install_generic_printer : Path.t -> Path.t -> (int -> (int -> Stdlib.Obj.t -> Outcometree.out_value, Stdlib.Obj.t -> Outcometree.out_value) gen_printer) -> unitval install_generic_printer' : Path.t -> Path.t -> (Stdlib.Format.formatter -> Stdlib.Obj.t -> unit, Stdlib.Format.formatter -> Stdlib.Obj.t -> unit) gen_printer -> unitval remove_printer : Path.t -> unitval max_printer_depth : int Stdlib.refval max_printer_steps : int Stdlib.refval parse_toplevel_phrase : (Stdlib.Lexing.lexbuf -> Parsetree.toplevel_phrase) Stdlib.refval parse_use_file : (Stdlib.Lexing.lexbuf -> Parsetree.toplevel_phrase list) Stdlib.refval print_location : Stdlib.Format.formatter -> Location.t -> unitval print_error : Stdlib.Format.formatter -> Location.error -> unitval print_warning : Location.t -> Stdlib.Format.formatter -> Warnings.t -> unitval input_name : string Stdlib.refval print_out_value : (Stdlib.Format.formatter -> Outcometree.out_value -> unit) Stdlib.refval print_out_type : (Stdlib.Format.formatter -> Outcometree.out_type -> unit) Stdlib.refval print_out_class_type : (Stdlib.Format.formatter -> Outcometree.out_class_type -> unit) Stdlib.refval print_out_module_type : (Stdlib.Format.formatter -> Outcometree.out_module_type -> unit) Stdlib.refval print_out_type_extension : (Stdlib.Format.formatter -> Outcometree.out_type_extension -> unit) Stdlib.refval print_out_sig_item : (Stdlib.Format.formatter -> Outcometree.out_sig_item -> unit) Stdlib.refval print_out_signature : (Stdlib.Format.formatter -> Outcometree.out_sig_item list -> unit) Stdlib.refval print_out_phrase : (Stdlib.Format.formatter -> Outcometree.out_phrase -> unit) Stdlib.refval read_interactive_input : (string -> bytes -> int -> int * bool) Stdlib.refval toplevel_startup_hook : (unit -> unit) Stdlib.ref
type event += | Startup| After_setup
val add_hook : (event -> unit) -> unitval run_hooks : event -> unitval may_trace : bool Stdlib.refval override_sys_argv : string array -> unit