This file is indexed.

/usr/lib/ocaml/lambda-term/lTerm_widget.mli is in liblambda-term-ocaml-dev 1.9-4.

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
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
(*
 * lTerm_widget.mli
 * ----------------
 * Copyright : (c) 2011, Jeremie Dimino <jeremie@dimino.org>
 * Licence   : BSD3
 *
 * This file is a part of Lambda-Term.
 *)

(** Widgets for creating applications *)

(** {6 Base class} *)

(** The base class. The parameter is the initial resource class. The
    resource class is the first part of all resource keys used by the
    widget.

    For examples, buttons use the resources
    ["button.focused.foreground"], ["button.unfocused.bold"], ... so
    their resource class is ["button"].
*)
class t : string -> object
  method children : t list
    (** The children of the widget. *)

  method parent : t option
    (** The parent of the widget, if any. *)

  method set_parent : t option -> unit
    (** Sets the parent of the widget. This also affect
        {!queue_draw}. *)

  method can_focus : bool
    (** Whether the widget can receive the focus or not. *)

  method queue_draw : unit
    (** Enqueue a redraw operation. If the widget has a parent, this
        is the same as calling the {!queue_draw} method of the parent,
        otherwise this does nothing. *)

  method set_queue_draw : (unit -> unit) -> unit
    (** [set_queue_draw f] sets the function called when the
        {!queue_draw} method is invoked, for this widget and all its
        children. *)

  method draw : LTerm_draw.context -> t -> unit
    (** [draw ctx focused] draws the widget on the given
        context. [focused] is the focused widget. *)

  method cursor_position : LTerm_geom.coord option
    (** Method invoked when the widget has the focus, it returns the
        position of the cursor inside the widget if it should be
        displayed. *)

  method allocation : LTerm_geom.rect
    (** The zone occuped by the widget. *)

  method set_allocation : LTerm_geom.rect -> unit
    (** Sets the zone occuped by the widget. *)

  method send_event : LTerm_event.t -> unit
    (** Send an event to the widget. If the widget cannot process the
        event, it is sent to the parent and so on. *)

  method on_event : ?switch : LTerm_widget_callbacks.switch -> (LTerm_event.t -> bool) -> unit
    (** [on_event ?switch f] calls [f] each time an event is
        received. If [f] returns [true], the event is not passed to
        other callbacks. *)

  method size_request : LTerm_geom.size
    (** The size wanted by the widget. *)

  method resources : LTerm_resources.t
    (** The set of resources used by the widget. *)

  method set_resources : LTerm_resources.t -> unit
    (** Sets the resources of the widget and of all its children. *)

  method resource_class : string
    (** The resource class of the widget. *)

  method set_resource_class : string -> unit
    (** Sets the resource class of the widget. This can be used to set
        an alternative style for the widget. *)

  method update_resources : unit
    (** Method invoked when the resources or the resource class of the
        widget change. The default function does nothing. *)
end

(** {6 Labels} *)

(** A widget displaying a text. *)
class label : string -> object
  inherit t

  method text : string
    (** The text of  the label. *)

  method set_text : string -> unit
end

(** {6 Containers} *)

exception Out_of_range

(** Type of widgets displaying a list of widget. *)
class type box = object
  inherit t

  method add : ?position : int -> ?expand : bool -> #t -> unit
    (** [add ?position ?expand widget] adds a widget to the box. If
        [expand] is [true] (the default) then [widget] will occupy as
        much space as possible. If [position] is not specified then
        the widget is appended to the end of the widget list. It
        raises {!Out_of_range} if the given position is negative or
        exceed the number of widgets. *)

  method remove : #t -> unit
    (** [remove widget] remove a widget from the box. *)
end

(** A widget displaying a list of widgets, listed horizontally. *)
class hbox : box

(** A widget displaying a list of widgets, listed vertically. *)
class vbox : box

(** A widget displayiing another widget in a box. *)
class frame : object
  inherit t

  method set : #t -> unit
    (** Set the widget that is inside the frame. *)

  method empty : unit
    (** Remove the child of the frame. *)
end

(** A widget displaying a frame around child widget. Unlike {!frame}, the child
    widget is not expanded to take all available space; instead the child is
    centered and frame is drawn around it. This is a utility class for creation
    of modal dialogs and similar widgets. *)
class modal_frame : object
  inherit frame
end

(** {6 Lines} *)

(** A horizontal line. *)
class hline : t

(** A vertical line. *)
class vline : t

(** {6 Buttons} *)

(** Normal button. *)
class button : string -> object
  inherit t

  method label : string
    (** The text displayed on the button. *)

  method set_label : string -> unit

  method on_click : ?switch : LTerm_widget_callbacks.switch -> (unit -> unit) -> unit
    (** [on_click ?switch f] calls [f] when the button is clicked. *)
end

(** Checkbutton. A button that can be in active or inactive state. *)
class checkbutton : string -> bool -> object
  inherit t

  method label : string
    (** The text displayed on the checkbutton. *)

  method state : bool
    (** The state of checkbutton; [true] means checked and [false] means unchecked. *)

  method set_label : string -> unit

  method on_click : ?switch : LTerm_widget_callbacks.switch -> (unit -> unit) -> unit
  (** [on_click ?switch f] calls [f] when the button state is changed. *)
end

class type ['a] radio = object
  method on : unit
  method off : unit
  method id : 'a
end

(** Radio group.

 Radio group governs the set of {!radio} objects. At each given moment of time only one
 of the objects in the "on" state and the rest are in the "off" state. *)
class ['a] radiogroup : object

  method on_state_change : ?switch : LTerm_widget_callbacks.switch -> ('a option -> unit) -> unit
  (** [on_state_change ?switch f] calls [f] when the state of the group is changed. *)

  method state : 'a option
  (** The state of the group. Contains [Some id] with the id of "on" object
   in the group or None if no objects were added to the group yet. *)

  method register_object : 'a radio -> unit
  (** Adds radio object to the group *)

  method switch_to : 'a -> unit
  (** [switch_to id] switches radio group to the state [Some id], calls {!radio.on}
  method of the object with the given id and {!radio.off} method of all other objects
  added to the group. *)

end

(** Radiobutton. The button which implements {!radio} object contract, so can be
 added to {!radiogroup}. *)
class ['a] radiobutton : 'a radiogroup -> string -> 'a -> object
  inherit t

  method state : bool
  (** The state of the button; [true] if button is "on" and [false] if the button
   is "off". *)

  method on : unit
  (** Switches the button state to "on". Affects only how the button is drawn,
   does not change the state of the group the button is added to.
   Use {!radiogroup.switch_to} instead. *)

  method off : unit
  (** Switches the button state to "off". Affects only how the button is drawn,
   does not change the state of the group the button is added to.
   Use {!radiogroup.switch_to} instead. *)

  method label : string
  (** The text displayed on the radiobutton. *)

  method set_label : string -> unit

  method id : 'a
  (** The id of the button. *)

  method on_click : ?switch:LTerm_widget_callbacks.switch -> (unit -> unit) -> unit
  (** [on_click ?switch f] calls [f] when the button is clicked. You probably want
   to use {!radiogroup.on_state_change} instead. *)

end

(** {6 Running in a terminal} *)

val run : LTerm.t -> ?save_state : bool -> ?load_resources : bool -> ?resources_file : string -> #t -> 'a Lwt.t -> 'a Lwt.t
  (** [run term ?save_state widget w] runs on the given terminal using
      [widget] as main widget. It returns when [w] terminates. If
      [save_state] is [true] (the default) then the state of the
      terminal is saved and restored when [w] terminates.

      If [load_resources] is [true] (the default) then
      [resources_file] (which default to ".lambda-termrc" in the home
      directory) is loaded and the result is set to [w]. *)

val run_modal : LTerm.t -> ?save_state : bool -> ?load_resources : bool -> ?resources_file : string -> t Lwt_react.event -> unit Lwt_react.event -> #t -> 'a Lwt.t -> 'a Lwt.t
  (** This function works in the same way as {!run} but also takes two
   {!Lwt_react.event} parameters. The first one should contain
   {!LTerm_widget.t} widget and makes it new topmost layer in UI. The second
   message removes the topmost level from UI. All layers are redrawn, from
   bottom to up, but only the topmost layer gets keyboard events delivered to
   it. This allows to implement things like modal dialogs.
   *)

val prepare_simple_run : unit -> (#t -> 'a Lwt.t) * (#t -> unit -> unit) * (?step:React.step -> unit -> unit) * ('a -> unit)
  (** [prepare_simple_run ()] returns a tuple [(do_run, push_layer, pop_layer,
     exit)] -- functions useful for creating simple UI.

     [do_run w] where w is a widget runs the given widget in a terminal over
     stdout, loading resources from [.lambda-termrc], saving state and
     restoring it on exit from ui.
     Example: [do_run my_frame]

     [push_layer w] where w is a widget is a callback to add w as a new modal
     layer to UI.
     Example: [button#on_click (push_layer my_modal_dialog)].

     [pop_layer] is a callback to destroy the topmost modal layer.
     Example: [cancel_button#on_click pop_layer].

     [exit] is a callback to exit the UI.
     Example: [exit_button#on_click exit]
*)