Previous Contents Next
Chapter 27 The LablTk library: Tcl/Tk GUI interface

The labltk library provides access to the Tcl/Tk GUI from Objective Caml programs. This interface is generated in an automated way, and you should refer to Tcl/Tk books and man pages for detailed information on the behavior of the numerous functions.
Programs that use the labltk library must be linked as follows:
        ocamlc other options -I labltk-dir labltk.cma other files
        ocamlopt other options -I labltk-dir labltk.cmxa other files
labltk-dir is CAMLLIB/labltk. On Unix the default location is /usr/local/lib/caml/labltk.

  Unix:
The labltk library is available for any system with Tcl/Tk installed, starting from Tcl 7.5/Tk 4.1 up to Tcl/Tk 8.3. Beware that some beta versions may have compatibility problems.

If the library was not compiled correctly, try to run again the configure script with the option -tkdefs switches, where switches is a list of C-style inclusion paths leading to the right tcl.h and tk.h, for instance '-I/usr/local/include/tcl8.0 -I/usr/local/include/tk8.0'.

A script is installed, to make easier the use of the labltk library as toplevel.
labltk
This is a toplevel including the labltk library, and the path is already set as to allow the use of the various modules. It also includes code for the Unix and Str libraries. You can use it in place of ocaml.
  Windows:
The labltk library has been precompiled for use with Tcl/Tk 8.0. You must first have it installed on your system. It can be downloaded from
http://www.scriptics.com/products/tcltk/8.0.html. After installing it, you must put the dynamically loaded libraries tcl80.dll and tk80.dll (from the bin directory of the Tcl installation) in a directory included in you path.

The toplevel, including Unix and Str, is available as labltk. But you need to explicitly add the labltk library directory to your load path with the #directory directive.
The labltk library is composed of a large number of modules.
Bell                Imagebitmap         Place
Button              Imagephoto          Radiobutton
Canvas              Label               Scale
Checkbutton         Listbox             Scrollbar
Clipboard           Menu                Selection
Dialog              Menubutton          Text
Entry               Message             Tk
Focus               Option              Tkwait
Frame               Optionmenu          Toplevel
Grab                Pack                Winfo
Grid                Palette             Wm
Giving a detailed account of each of these module would be impractical here. We will just present some of the basic functions in the module Tk. Note that for most other modules information can be found in the Tcl man page of their name.

27.1 Module Tk: basic functions and types for LablTk


Initialization and termination
val openTk : ?display:string -> ?class:string -> unit -> toplevel widget
Initialize LablTk and open a toplevel window. display is described according to the X11 conventions. class is used for the X11 resource mechanism.
val mainLoop : unit -> unit
Start the main event loop
val closeTk : unit -> unit
Quit the main loop and close all open windows.
val destroy : 'a Widget.widget -> unit
Destroy an individual widget.
Application wide commands
val update : unit -> unit
Synchronize display with internal state.
val appname_get : unit -> string
val appname_set : string -> unit
Get or set the application name.
Dimensions
type units = [`Pix int|`Cm float|`In float|`Mm float|`Pt float]
val pixels : units -> int
Converts various on-screen units to pixels, respective to the default display. Available units are pixels, centimeters, inches, millimeters and points
Widget layout commands
type anchor = [`Center|`E|`N|`Ne|`Nw|`S|`Se|`Sw|`W]
type fillMode = [`Both|`None|`X|`Y]
type side = [`Bottom|`Left|`Right|`Top]
val pack :
  ?after:'a Widget.widget ->
  ?anchor:anchor ->
  ?before:'b Widget.widget ->
  ?expand:bool ->
  ?fill:fillMode ->
  ?inside:'c Widget.widget ->
  ?ipadx:int ->
  ?ipady:int ->
  ?padx:int ->
  ?pady:int ->
  ?side:side ->
  'd Widget.widget list -> unit
Pack a widget inside its parent, using the standard layout engine.
val grid :
  ?column:int ->
  ?columnspan:int ->
  ?inside:'a Widget.widget ->
  ?ipadx:int ->
  ?ipady:int ->
  ?padx:int ->
  ?pady:int ->
  ?row:int ->
  ?rowspan:int ->
  ?sticky:string -> 'b Widget.widget list -> unit
Pack a widget inside its parent, using the grid layout engine.
type borderMode = [`Ignore|`Inside|`Outside]
val place :
  ?anchor:anchor ->
  ?bordermode:borderMode ->
  ?height:int ->
  ?inside:'a Widget.widget ->
  ?relheight:float ->
  ?relwidth:float ->
  ?relx:float ->
  ?rely:float ->
  ?width:int ->
  ?x:int -> ?y:int -> 'b Widget.widget -> unit
Pack a widget inside its parent, at absolute coordinates.
val raise_window :
  ?above:'a Widget.widget -> 'b Widget.widget -> unit
val lower_window :
  ?below:'a Widget.widget -> 'b Widget.widget -> unit
Raise or lower the window associated to a widget.
Event handling
type modifier =
  [ `Control | `Shift | `Lock
  | `Button1 | `Button2 | `Button3 | `Button4 | `Button5
  | `Double | `Triple
  | `Mod1 | `Mod2 | `Mod3 | `Mod4 | `Mod5 | `Meta | `Alt ]
type event =
  [ `ButtonPress | `ButtonPressDetail int
  | `ButtonRelease | `ButtonReleaseDetail int
  | `Circulate | `ColorMap | `Configure | `Destroy
  | `Enter | `Expose | `FocusIn | `FocusOut | `Gravity
  | `KeyPress | `KeyPressDetail string
  | `KeyRelease | `KeyReleaseDetail string
  | `Leave | `Map | `Motion | `Property
  | `Reparent | `Unmap | `Visibility
  | `Modified modifier list * event ]
An event can be either a basic X event, or modified by a key or mouse modifier.
type eventInfo =
  { mutable ev_Above: int;
    mutable ev_ButtonNumber: int;
    mutable ev_Count: int;
    mutable ev_Detail: string;
    mutable ev_Focus: bool;
    mutable ev_Height: int;
    mutable ev_KeyCode: int;
    mutable ev_Mode: string;
    mutable ev_OverrideRedirect: bool;
    mutable ev_Place: string;
    mutable ev_State: string;
    mutable ev_Time: int;
    mutable ev_Width: int;
    mutable ev_MouseX: int;
    mutable ev_MouseY: int;
    mutable ev_Char: string;
    mutable ev_BorderWidth: int;
    mutable ev_SendEvent: bool;
    mutable ev_KeySymString: string;
    mutable ev_KeySymInt: int;
    mutable ev_RootWindow: int;
    mutable ev_SubWindow: int;
    mutable ev_Type: int;
    mutable ev_Widget: Widget.any Widget.widget;
    mutable ev_RootX: int;
    mutable ev_RootY: int }
Event related information accessible in callbacks.
type eventField =
  [ `Above | `ButtonNumber | `Count | `Detail | `Focus | `Height
  | `KeyCode | `Mode | `OverrideRedirect | `Place | `State
  | `Time | `Width | `MouseX | `MouseY | `Char | `BorderWidth
  | `SendEvent | `KeySymString | `KeySymInt | `RootWindow
  | `SubWindow | `Type | `Widget | `RootX | `RootY ]
In order to access the above event information, one has to pass a list of required event fields to the bind function.
val bind :
  events:event list ->
  ?extend:bool ->
  ?breakable:bool ->
  ?fields:eventField list
  ?action:(eventInfo -> unit) ->
  'a Widget.widget -> unit
Bind a succession of events on a widget to an action. If extend is true then then binding is added after existing ones, otherwise it replaces them. breakable should be true when break is to be called inside the action. action is called with the fields required set in an eventInfo structure. Other fields should not be accessed. If action is omitted then existing bindings are removed.
val bind_class :
  events:event list ->
  ?extend:bool ->
  ?breakable:bool ->
  ?fields:eventField list
  ?action:(eventInfo -> unit) ->
  ?on:'a Widget.widget ->
  string -> unit
Same thing for all widgets of a given class. If a widget is given with label ~on:, the binding will be removed as soon as it is destroyed.
val bind_tag :
  events:event list ->
  ?extend:bool ->
  ?breakable:bool ->
  ?fields:eventField list
  ?action:(eventInfo -> unit) ->
  ?on:'a Widget.widget ->
  string -> unit
Same thing for all widgets having a given tag
val break : unit -> unit
Used inside a bound action, do not call other actions after this one. This is only possible if this action was bound with ~breakable:true.

Previous Contents Next