This file is indexed.

/usr/lib/ocaml/lablgtk2-extras/okey.mli is in liblablgtk-extras-ocaml-dev 1.5-1build3.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  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
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
(*********************************************************************************)
(*                Lablgtk-extras                                                 *)
(*                                                                               *)
(*    Copyright (C) 2011 Institut National de Recherche en Informatique          *)
(*    et en Automatique. All rights reserved.                                    *)
(*                                                                               *)
(*    This program is free software; you can redistribute it and/or modify       *)
(*    it under the terms of the GNU Library General Public License as            *)
(*    published by the Free Software Foundation; either version 2 of the         *)
(*    License, or any later version.                                             *)
(*                                                                               *)
(*    This program is distributed in the hope that it will be useful,            *)
(*    but WITHOUT ANY WARRANTY; without even the implied warranty of             *)
(*    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the              *)
(*    GNU Library General Public License for more details.                       *)
(*                                                                               *)
(*    You should have received a copy of the GNU Library General Public          *)
(*    License along with this program; if not, write to the Free Software        *)
(*    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA                   *)
(*    02111-1307  USA                                                            *)
(*                                                                               *)
(*    Contact: Maxence.Guesdon@inria.fr                                          *)
(*                                                                               *)
(*                                                                               *)
(*********************************************************************************)

(** Okey interface.
   Convenient functions to handle key press events in Lablgtk2 widgets.

   Once the lib is compiled and installed, you can use it by referencing
   it with the [Okey] module. You must add [okey.cmo] or [okey.cmx]
   on the commande line when you link.

   @cgname Okey
   @version 1.0
   @author Maxence Guesdon
*)

type modifier = Gdk.Tags.modifier

(** Set the default modifier list. The first default value is [[]].*)
val set_default_modifiers : modifier list -> unit

(** Set the default modifier mask. The first default value is
   [[`MOD2 ; `MOD3 ; `MOD4 ; `MOD5 ; `LOCK]].
   The mask defines the modifiers not taken into account
   when looking for the handler of a key press event.
*)
val set_default_mask : modifier list -> unit

(** {2 Setting handlers for simple key press events.} *)

(** [add widget key callback] associates the [callback] function to the event
   "key_press" with the given [key] for the given [widget].

   @param remove when true, the previous handlers for the given key and modifier
   list are not kept.
   @param cond this function is a guard: the [callback] function is not called
   if the [cond] function returns [false].
   The default [cond] function always returns [true].

   @param mods the list of modifiers. If not given, the default modifiers
   are used.
   You can set the default modifiers with function {!Okey.set_default_modifiers}.

   @param mask the list of modifiers which must not be taken
   into account to trigger the given handler. [mods]
   and [mask] must not have common modifiers. If not given, the default mask
   is used.
   You can set the default modifiers mask with function {!Okey.set_default_mask}.
*)
val add :
    < connect : < destroy : callback: (unit -> unit) -> GtkSignal.id; .. >;
      event : GObj.event_ops; get_oid : int; .. > ->
	?cond: (unit -> bool) ->
	  ?mods: modifier list ->
	    ?mask: modifier list ->
	      Gdk.keysym ->
		(unit -> unit) ->
		  unit

(** It calls {!Okey.add} for each given key.*)
val add_list :
    < connect : < destroy : callback: (unit -> unit) -> GtkSignal.id; .. >;
      event : GObj.event_ops; get_oid : int; .. > ->
	?cond: (unit -> bool) ->
	  ?mods: modifier list ->
	    ?mask: modifier list ->
	      Gdk.keysym list ->
		(unit -> unit) ->
		  unit

(** Like {!Okey.add} but the previous handlers for the
   given modifiers and key are not kept.*)
val set :
    < connect : < destroy : callback: (unit -> unit) -> GtkSignal.id; .. >;
      event : GObj.event_ops; get_oid : int; .. > ->
	?cond: (unit -> bool) ->
	  ?mods: modifier list ->
	    ?mask: modifier list ->
	      Gdk.keysym ->
		(unit -> unit) ->
		  unit

(** It calls {!Okey.set} for each given key.*)
val set_list :
    < connect : < destroy : callback: (unit -> unit) -> GtkSignal.id; .. >;
      event : GObj.event_ops; get_oid : int; .. > ->
	?cond: (unit -> bool) ->
	  ?mods: modifier list ->
	    ?mask: modifier list ->
	      Gdk.keysym list ->
		(unit -> unit) ->
		  unit

(** Remove the handlers associated to the given widget.
   This is automatically done when a widget is destroyed but
   you can do it yourself. *)
val remove_widget :
    < connect : < destroy : callback: (unit -> unit) -> GtkSignal.id; .. >;
      event : GObj.event_ops; get_oid : int; .. > ->
	unit ->
	  unit


(** {2 Setting handlers for combination of key press events, a la emacs} *)

type handler

type keyhit_spec

type keyhit_state = (modifier list * Gdk.keysym) list

(** The keys which are ignored when they are pressed alone. *)
val ignored_keys : Gdk.keysym list ref

type handler_tree_node =
    Handler of handler
  | Node of handler_tree list
and handler_tree = {
  mutable hst_spec : keyhit_spec;
  mutable hst_v : handler_tree_node;
}

val set_handler_trees :
    ?stop:(modifier list * Gdk.keysym) ->
      (unit -> handler_tree list) ->
        ?f_display_state: (after_handler: bool -> keyhit_state -> unit) ->
          < misc : GObj.misc_ops ; event : GObj.event_ops; ..> -> unit

val handler : ?cond:(unit -> bool) -> (unit -> unit) -> handler

val keyhit_spec :
  ?mods:modifier list -> ?mask:modifier list -> Gdk.keysym -> keyhit_spec

val handler_tree :
  ?mods:modifier list ->
  ?mask:modifier list ->
    Gdk.keysym -> handler_tree_node -> handler_tree

val reset_state : < misc : GObj.misc_ops ; ..> -> unit

val trees_of_list : (keyhit_state * (unit -> unit)) list -> handler_tree list