summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/support/protocol.mli
blob: 636ef3e2729d21c6cc33e27850ec691dcb798a0f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
(*************************************************************************)
(*                                                                       *)
(*                Objective Caml LablTk library                          *)
(*                                                                       *)
(*         Francois Rouaix, Francois Pessaux and Jun Furuse              *)
(*               projet Cristal, INRIA Rocquencourt                      *)
(*            Jacques Garrigue, Kyoto University RIMS                    *)
(*                                                                       *)
(*   Copyright 1999 Institut National de Recherche en Informatique et    *)
(*   en Automatique and Kyoto University.  All rights reserved.          *)
(*   This file is distributed under the terms of the GNU Library         *)
(*   General Public License.                                             *)
(*                                                                       *)
(*************************************************************************)

(* $Id$ *)

open Widget

(* Lower level interface *)
exception TkError of string
      (* Raised by the communication functions *)

val debug : bool ref 
      (* When set to true, displays approximation of intermediate Tcl code *)

type tkArgs =
    TkToken of string
  | TkTokenList of tkArgs list          (* to be expanded *)
  | TkQuote of tkArgs                   (* mapped to Tcl list *)


(* Misc *)
external splitlist : string -> string list
        = "camltk_splitlist"

val add_destroy_hook : (any widget -> unit) -> unit


(* Opening, closing, and mainloop *)
val   openTk : ?display:string -> ?clas:string -> unit -> toplevel widget
val   closeTk : unit -> unit
val   mainLoop : unit -> unit


(* Direct evaluation of tcl code *)
val   tkEval : tkArgs array -> string

val   tkCommand : tkArgs array -> unit

(* Returning a value from a Tcl callback *)
val   tkreturn: string -> unit


(* Callbacks: this is private *)

type cbid

type callback_buffer = string list
      (* Buffer for reading callback arguments *)

val callback_naming_table : (cbid, callback_buffer -> unit) Hashtbl.t
val callback_memo_table : (any widget, cbid) Hashtbl.t
      (* Exported for debug purposes only. Don't use them unless you
         know what you are doing *)
val new_function_id : unit -> cbid
val string_of_cbid : cbid -> string
val register_callback : 'a widget -> callback:(callback_buffer -> unit) -> string
      (* Callback support *)
val clear_callback : cbid -> unit
      (* Remove a given callback from the table *)
val remove_callbacks : 'a widget -> unit
      (* Clean up callbacks associated to widget. Must be used only when
         the Destroy event is bind by the user and masks the default
         Destroy event binding *)

val cTKtoCAMLwidget : string -> any widget
val cCAMLtoTKwidget : 'a widget -> tkArgs

val register : string -> callback:(callback_buffer -> unit) -> unit

(*-*)
val prerr_cbid : cbid -> unit