]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/otherlibs/labltk/support/protocol.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / otherlibs / labltk / support / protocol.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                 MLTk, Tcl/Tk interface of Objective Caml            *)
4 (*                                                                     *)
5 (*    Francois Rouaix, Francois Pessaux, Jun Furuse and Pierre Weis    *)
6 (*               projet Cristal, INRIA Rocquencourt                    *)
7 (*            Jacques Garrigue, Kyoto University RIMS                  *)
8 (*                                                                     *)
9 (*  Copyright 2002 Institut National de Recherche en Informatique et   *)
10 (*  en Automatique and Kyoto University.  All rights reserved.         *)
11 (*  This file is distributed under the terms of the GNU Library        *)
12 (*  General Public License, with the special exception on linking      *)
13 (*  described in file LICENSE found in the Objective Caml source tree. *)
14 (*                                                                     *)
15 (***********************************************************************)
16
17 (* $Id: protocol.mli 7283 2005-12-21 05:29:08Z garrigue $ *)
18
19 open Widget
20
21 (* Lower level interface *)
22 exception TkError of string
23       (* Raised by the communication functions *)
24
25 val debug : bool ref 
26       (* When set to true, displays approximation of intermediate Tcl code *)
27
28 type tkArgs =
29     TkToken of string
30   | TkTokenList of tkArgs list          (* to be expanded *)
31   | TkQuote of tkArgs                   (* mapped to Tcl list *)
32
33
34 (* Misc *)
35 external splitlist : string -> string list
36         = "camltk_splitlist"
37
38 val add_destroy_hook : (any widget -> unit) -> unit
39
40
41 (* Opening, closing, and mainloop *)
42 val default_display : unit -> string
43
44 val opentk : unit -> toplevel widget
45     (* The basic initialization function. *)
46
47 val keywords : (string * Arg.spec * string) list
48     (* Command line parsing specification for Arg.parse, which contains
49        the standard Tcl/Tk command line options such as "-display" and "-name".
50        Add [keywords] to a [Arg.parse] call, then call [opentk].
51        Then [opentk] can make use of these command line options 
52        to initiate applications. *)
53
54 val opentk_with_args : string list -> toplevel widget
55     (* [opentk_with_args] is a lower level interface to initiate Tcl/Tk 
56        applications.  [opentk_with_args argv] initializes Tcl/Tk with
57        the command line options given by [argv] *)
58
59 val openTk : ?display:string -> ?clas:string -> unit -> toplevel widget
60     (* [openTk ~display:display ~clas:clas ()] is equivalent to
61        [opentk_with_args ["-display"; display; "-name"; clas]] *)
62
63 (* Legacy opentk functions *)
64 val openTkClass: string -> toplevel widget
65     (* [openTkClass class] is equivalent to [opentk ["-name"; class]] *)
66 val openTkDisplayClass: string -> string -> toplevel widget
67     (* [openTkDisplayClass disp class] is equivalent to 
68        [opentk ["-display"; disp; "-name"; class]] *)
69
70 val closeTk : unit -> unit
71 val finalizeTk : unit -> unit 
72     (* Finalize tcl/tk before exiting. This function will be automatically 
73        called when you call [Pervasives.exit ()] *)
74
75 val mainLoop : unit -> unit
76     (* Start the event loop *)
77
78 type event_flag =
79   DONT_WAIT | X_EVENTS | FILE_EVENTS | TIMER_EVENTS | IDLE_EVENTS | ALL_EVENTS
80 val do_one_event : event_flag list -> bool
81     (* Process a single event *)
82 val do_pending : unit -> unit
83     (* Process all pending events, without waiting.
84        This lets you use Tk from the toplevel, for instance. *)
85
86
87 (* Direct evaluation of tcl code *)
88 val tkEval : tkArgs array -> string
89
90 val tkCommand : tkArgs array -> unit
91
92 (* Returning a value from a Tcl callback *)
93 val tkreturn: string -> unit
94
95
96 (* Callbacks: this is private *)
97
98 type cbid
99
100 type callback_buffer = string list
101       (* Buffer for reading callback arguments *)
102
103 val callback_naming_table : (cbid, callback_buffer -> unit) Hashtbl.t
104 val callback_memo_table : (any widget, cbid) Hashtbl.t
105       (* Exported for debug purposes only. Don't use them unless you
106          know what you are doing *)
107 val new_function_id : unit -> cbid
108 val string_of_cbid : cbid -> string
109 val register_callback : 'a widget -> callback:(callback_buffer -> unit) -> string
110       (* Callback support *)
111 val clear_callback : cbid -> unit
112       (* Remove a given callback from the table *)
113 val remove_callbacks : 'a widget -> unit
114       (* Clean up callbacks associated to widget. Must be used only when
115          the Destroy event is bind by the user and masks the default
116          Destroy event binding *)
117
118 val cTKtoCAMLwidget : string -> any widget
119 val cCAMLtoTKwidget : 'a widget -> tkArgs
120
121 val register : string -> callback:(callback_buffer -> unit) -> unit
122
123 (*-*)
124 val prerr_cbid : cbid -> unit