]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/toplevel/toploop.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / toplevel / toploop.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: toploop.mli 8705 2007-12-04 13:38:58Z doligez $ *)
14
15 open Format
16
17 (* Accessors for the table of toplevel value bindings.  These functions
18    must appear as first and second exported functions in this module.
19    (See module Translmod.) *)
20 val getvalue : string -> Obj.t
21 val setvalue : string -> Obj.t -> unit
22
23 (* Set the load paths, before running anything *)
24
25 val set_paths : unit -> unit
26
27 (* The interactive toplevel loop *)
28
29 val loop : formatter -> unit
30
31 (* Read and execute a script from the given file *)
32
33 val run_script : formatter -> string -> string array -> bool
34         (* true if successful, false if error *)
35
36 (* Interface with toplevel directives *)
37
38 type directive_fun =
39    | Directive_none of (unit -> unit)
40    | Directive_string of (string -> unit)
41    | Directive_int of (int -> unit)
42    | Directive_ident of (Longident.t -> unit)
43    | Directive_bool of (bool -> unit)
44
45 val directive_table : (string, directive_fun) Hashtbl.t
46         (* Table of known directives, with their execution function *)
47 val toplevel_env : Env.t ref
48         (* Typing environment for the toplevel *)
49 val initialize_toplevel_env : unit -> unit
50         (* Initialize the typing environment for the toplevel *)
51 val print_exception_outcome : formatter -> exn -> unit
52         (* Print an exception resulting from the evaluation of user code. *)
53 val execute_phrase : bool -> formatter -> Parsetree.toplevel_phrase -> bool
54         (* Execute the given toplevel phrase. Return [true] if the
55            phrase executed with no errors and [false] otherwise.
56            First bool says whether the values and types of the results
57            should be printed. Uncaught exceptions are always printed. *)
58 val use_file : formatter -> string -> bool
59 val use_silently : formatter -> string -> bool
60         (* Read and execute commands from a file.
61            [use_file] prints the types and values of the results.
62            [use_silently] does not print them. *)
63 val eval_path: Path.t -> Obj.t
64         (* Return the toplevel object referred to by the given path *)
65
66 (* Printing of values *)
67
68 val print_value: Env.t -> Obj.t -> formatter -> Types.type_expr -> unit
69 val print_untyped_exception: formatter -> Obj.t -> unit
70
71 val install_printer :
72   Path.t -> Types.type_expr -> (formatter -> Obj.t -> unit) -> unit
73 val remove_printer : Path.t -> unit
74
75 val max_printer_depth: int ref
76 val max_printer_steps: int ref
77
78 (* Hooks for external parsers and printers *)
79
80 val parse_toplevel_phrase : (Lexing.lexbuf -> Parsetree.toplevel_phrase) ref
81 val parse_use_file : (Lexing.lexbuf -> Parsetree.toplevel_phrase list) ref
82 val print_location : formatter -> Location.t -> unit
83 val print_error : formatter -> Location.t -> unit
84 val print_warning : Location.t -> formatter -> Warnings.t -> unit
85 val input_name : string ref
86
87 val print_out_value :
88   (formatter -> Outcometree.out_value -> unit) ref
89 val print_out_type :
90   (formatter -> Outcometree.out_type -> unit) ref
91 val print_out_class_type :
92   (formatter -> Outcometree.out_class_type -> unit) ref
93 val print_out_module_type :
94   (formatter -> Outcometree.out_module_type -> unit) ref
95 val print_out_sig_item :
96   (formatter -> Outcometree.out_sig_item -> unit) ref
97 val print_out_signature :
98   (formatter -> Outcometree.out_sig_item list -> unit) ref
99 val print_out_phrase :
100   (formatter -> Outcometree.out_phrase -> unit) ref
101
102 (* Hooks for external line editor *)
103
104 val read_interactive_input : (string -> string -> int -> int * bool) ref
105
106 (* Hooks for initialization *)
107
108 val toplevel_startup_hook : (unit -> unit) ref
109
110 (* Used by Trace module *)
111
112 val may_trace : bool ref