This file is indexed.

/usr/lib/ocaml/lablgtk2/gSourceView2.ml is in liblablgtksourceview2-ocaml-dev 2.18.3+dfsg-1build1.

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
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
(**************************************************************************)
(*                Lablgtk                                                 *)
(*                                                                        *)
(*    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         *)
(*    version 2, with the exception described in file COPYING which       *)
(*    comes with the library.                                             *)
(*                                                                        *)
(*    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                                          *)
(*                                                                        *)
(*                                                                        *)
(**************************************************************************)

open Gaux
open GtkSourceView2
open SourceView2Enums
open Gobject
open Gtk
open GtkBase
open GtkSourceView2_types
open OgtkSourceView2Props
open GObj

let get_bool = function `BOOL x -> x | _ -> assert false
let bool x = `BOOL x
let get_uint = function `INT x -> x | _ -> assert false
let uint x = `INT x
let get_int = function `INT x -> x | _ -> assert false
let int x = `INT x
let get_gobject = function `OBJECT x -> x | _ -> assert false
let gobject x = `OBJECT (Some x)

let map_opt f = function
    None -> None
  | Some x -> Some (f x)

(** {2 GtkSourceTag} *)

type source_tag_property = [
  | `BACKGROUND of Gdk.color
  | `BOLD of bool
  | `FOREGROUND of Gdk.color
  | `ITALIC of bool
  | `STRIKETHROUGH of bool
  | `UNDERLINE of bool
]

let text_tag_property_of_source_tag_property = function
  | `BACKGROUND p -> `BACKGROUND_GDK p
  | `BOLD p -> `WEIGHT (if p then `BOLD else `NORMAL)
  | `FOREGROUND p -> `FOREGROUND_GDK p
  | `ITALIC p -> `STYLE (if p then `ITALIC else `NORMAL)
  | `STRIKETHROUGH p -> `STRIKETHROUGH p
  | `UNDERLINE p -> `UNDERLINE (if p then `SINGLE else `NONE)

let color_of_string s =
  Gdk.Color.alloc ~colormap: (Gdk.Color.get_system_colormap())
    (`NAME s)

(** {2 GtkSourceStyleScheme} *)

class source_style_scheme (obj: GtkSourceView2_types.source_style_scheme obj) =
object(self)
  method as_source_style_scheme = obj
  method name = SourceStyleScheme.get_name obj
  method description = SourceStyleScheme.get_description obj
end


(** {2 GtkSourceStyleSchemeManager} *)

class source_style_scheme_manager
	(obj: GtkSourceView2_types.source_style_scheme_manager obj) =
  object(self)
    val obj = obj
    inherit source_style_scheme_manager_props

    method search_path =
      SourceStyleSchemeManager.get_search_path obj
    method set_search_path =
      SourceStyleSchemeManager.set_search_path obj
    method style_scheme_ids =
      SourceStyleSchemeManager.get_scheme_ids obj
    method style_scheme s =
      may_map (new source_style_scheme)
	(SourceStyleSchemeManager.get_scheme obj s)
  end

let source_style_scheme_manager ~default =
  let mgr =
    if default then SourceStyleSchemeManager.default ()
    else SourceStyleSchemeManager.new_ () in
  new source_style_scheme_manager mgr

(** {2 GtkSourceCompletionInfo} *)

class source_completion_info_signals
  (obj' : GtkSourceView2_types.source_completion_info obj) =
  object
    inherit GContainer.container_signals_impl obj'
    inherit source_completion_info_sigs
  end

class source_completion_info 
  (obj' : ([> GtkSourceView2_types.source_completion_info ] as 'a) obj) =
  object
    inherit GWindow.window obj'
    inherit source_completion_info_props
    method as_source_completion_info =
      (obj :> GtkSourceView2_types.source_completion_info obj)
    method widget =
      new GObj.widget (SourceCompletionInfo.get_widget obj)
    method set_widget (w : GObj.widget) =
      SourceCompletionInfo.set_widget obj w#as_widget
  end

(** {2 GtkSourceCompletionProposal} *)

class source_completion_proposal_signals
  (obj' : GtkSourceView2_types.source_completion_proposal obj) =
  object
    inherit ['a] gobject_signals (obj' : [> GtkSourceView2_types.source_completion_proposal ] obj)
    inherit source_completion_proposal_sigs
  end

class source_completion_proposal 
  (obj : GtkSourceView2_types.source_completion_proposal obj) =
  object
    val obj = obj
    method connect = new source_completion_proposal_signals obj
    method as_source_completion_proposal = obj
    inherit source_completion_proposal_props
  end

class source_completion_item
  (obj : GtkSourceView2_types.source_completion_proposal obj) =
  object
    inherit source_completion_proposal obj
    inherit source_completion_item_props
  end

let source_completion_item ?(label = "") ?(text = "") ?icon ?info () =
  new source_completion_item (SourceCompletionItem.new_ label text icon info)

let source_completion_item_with_markup ?(label = "") ?(text = "") ?icon ?info () =
  new source_completion_item (SourceCompletionItem.new_with_markup label text icon info)

let source_completion_item_from_stock ?(label = "") ?(text = "") ~stock ~info () =
  let stock = GtkStock.Item.lookup stock in
  let id = stock.GtkStock.stock_id in
  new source_completion_item (SourceCompletionItem.new_from_stock label text id info)

(** {2 GtkSourceCompletionProvider} *)

class source_completion_provider
  (obj' : GtkSourceView2_types.source_completion_provider obj) =
  object
    val obj = obj'
    method as_source_completion_provider = obj
    method icon = SourceCompletionProvider.get_icon obj
    method name = SourceCompletionProvider.get_name obj
    method populate (context : source_completion_context) =
      SourceCompletionProvider.populate obj context#as_source_completion_context
    method activation =
      SourceCompletionProvider.get_activation obj
    method matched (context : source_completion_context) =
      SourceCompletionProvider.match_ obj context#as_source_completion_context
    method info_widget (proposal : source_completion_proposal) =
      let widget = SourceCompletionProvider.get_info_widget obj proposal#as_source_completion_proposal in
      match widget with
      | None -> None
      | Some widget -> Some (new GObj.widget widget)
    method update_info (proposal : source_completion_proposal) (info : source_completion_info) =
      SourceCompletionProvider.update_info obj proposal#as_source_completion_proposal info#as_source_completion_info
    method start_iter (context : source_completion_context) (proposal : source_completion_proposal) =
      let iter = 
        SourceCompletionProvider.get_start_iter obj
          context#as_source_completion_context proposal#as_source_completion_proposal 
      in
      new GText.iter iter

    method activate_proposal (proposal : source_completion_proposal) (iter : GText.iter) =
      SourceCompletionProvider.activate_proposal obj proposal#as_source_completion_proposal iter#as_iter

    method interactive_delay =
      SourceCompletionProvider.get_interactive_delay obj 

    method priority =
      SourceCompletionProvider.get_priority obj 

  end

(** {2 GtkSourceCompletionContext} *)

and source_completion_context_signals
  (obj' : GtkSourceView2_types.source_completion_context obj) =
  object
    inherit ['a] gobject_signals (obj' : [> GtkSourceView2_types.source_completion_context ] obj)
    inherit source_completion_context_sigs
  end

and source_completion_context
  (obj' : GtkSourceView2_types.source_completion_context obj) =
  object
    val obj = obj'
    val iter_prop = {
      Gobject.name = "iter";
      conv = Gobject.Data.unsafe_pointer
    }
    inherit source_completion_context_props
    method as_source_completion_context = obj
    method activation = SourceCompletionContext.get_activation obj
    method add_proposals
      (provider : source_completion_provider) (proposals : source_completion_proposal list) b =
      let proposals = List.map (fun obj -> obj#as_source_completion_proposal) proposals in
      SourceCompletionContext.add_proposals obj
      provider#as_source_completion_provider proposals b
    method connect = new source_completion_context_signals obj'
    method iter =
      new GText.iter (Gobject.get iter_prop obj)

    method set_iter (iter : GText.iter) =
      Gobject.set iter_prop obj (iter#as_iter)
  end

class type custom_completion_provider =
  object
    method name : string
    method icon : GdkPixbuf.pixbuf option
    method populate : source_completion_context -> unit
    method matched : source_completion_context -> bool
    method activation : source_completion_activation_flags list
    method info_widget : source_completion_proposal -> GObj.widget option
    method update_info : source_completion_proposal -> source_completion_info -> unit
    method start_iter : source_completion_context -> source_completion_proposal -> GText.iter -> bool
    method activate_proposal : source_completion_proposal -> GText.iter -> bool
    method interactive_delay : int
    method priority : int
  end

let source_completion_provider (p : custom_completion_provider) : source_completion_provider =
  let of_context ctx = new source_completion_context ctx in
  let of_proposal prop = new source_completion_proposal prop in
  let of_info info = new source_completion_info info in
  let of_iter iter = new GText.iter iter in
  let as_opt_widget = function
  | None -> None
  | Some obj -> Some obj#as_widget
  in
  let completion_provider = {
    SourceCompletionProvider.provider_name = (fun () -> p#name);
    provider_icon = (fun () -> p#icon);
    provider_populate = (fun ctx -> p#populate (of_context ctx));
    provider_match = (fun ctx -> p#matched (of_context ctx));
    provider_activation = (fun () -> p#activation);
    provider_info_widget = (fun prop -> as_opt_widget (p#info_widget (of_proposal prop)));
    provider_update_info = (fun prop info -> p#update_info (of_proposal prop) (of_info info));
    provider_start_iter = (fun ctx prop iter -> p#start_iter (of_context ctx) (of_proposal prop) (of_iter iter));
    provider_activate_proposal = (fun prop iter -> p#activate_proposal (of_proposal prop) (of_iter iter));
    provider_interactive_delay = (fun () -> p#interactive_delay);
    provider_priority = (fun () -> p#priority);
  } in
  let obj = SourceCompletionProvider.new_ completion_provider in
  new source_completion_provider obj

(** {2 GtkSourceCompletion} *)

class source_completion_signals obj' =
object (self)
  inherit ['a] gobject_signals (obj' : [> GtkSourceView2_types.source_completion] obj)
  inherit source_completion_sigs
  method populate_context ~callback =
    let callback obj = callback (new source_completion_context obj) in
    self#connect SourceCompletion.S.populate_context ~callback
end

class source_completion
  (obj : GtkSourceView2_types.source_completion obj) =
  object
    val obj = obj
    inherit source_completion_props as super
    method as_source_completion = obj
    method connect = new source_completion_signals obj

    method create_context (iter : GText.iter) =
      let obj = SourceCompletion.create_context obj (iter#as_iter) in
      new source_completion_context obj

    method move_window (iter : GText.iter) =
      SourceCompletion.move_window obj (iter#as_iter)

    method show (prs : source_completion_provider list) (ctx : source_completion_context) =
      let prs = List.map (fun pr -> pr#as_source_completion_provider) prs in
      SourceCompletion.show obj prs ctx#as_source_completion_context

    method providers =
      let prs = SourceCompletion.get_providers obj in
      List.map (fun pr -> new source_completion_provider pr) prs

    method add_provider (pr : source_completion_provider) =
      SourceCompletion.add_provider obj (pr#as_source_completion_provider)

    method remove_provider (pr : source_completion_provider) =
      SourceCompletion.remove_provider obj (pr#as_source_completion_provider)

  end

(** {2 GtkSourceLanguage} *)

class source_language (obj: GtkSourceView2_types.source_language obj) =
object (self)
  method as_source_language = obj
  val obj = obj
  method misc = new gobject_ops obj

  method id = SourceLanguage.get_id obj
  method name = SourceLanguage.get_name obj
  method section = SourceLanguage.get_section obj
  method hidden = SourceLanguage.get_hidden obj

  method metadata s = SourceLanguage.metadata obj s
  method mime_types = SourceLanguage.mime_types obj
  method globs = SourceLanguage.globs obj
  method style_name s = SourceLanguage.style_name obj s
  method style_ids = SourceLanguage.style_ids obj
end

(** {2 GtkSourceLanguageManager} *)

class source_language_manager
  (obj: GtkSourceView2_types.source_language_manager obj) =
object (self)
  method get_oid = Gobject.get_oid obj
  method as_source_language_manager = obj

  method set_search_path p = SourceLanguageManager.set_search_path obj p
  method search_path = SourceLanguageManager.search_path obj
  method language_ids = SourceLanguageManager.language_ids obj

  method language id =
    may_map
      (new source_language)
      (SourceLanguageManager.language obj id )

  method guess_language ?filename ?content_type () =
    may_map
      (new source_language)
      (SourceLanguageManager.guess_language obj filename content_type)
end

let source_language_manager ~default =
  new source_language_manager
    (if default then SourceLanguageManager.default ()
     else SourceLanguageManager.create [])


(** {2 GtkSourceMark} *)

class source_mark  (obj: GtkSourceView2_types.source_mark obj) =
object (self)
  method coerce = (`MARK (GtkText.Mark.cast obj):GText.mark)
  method as_source_mark = obj
  val obj = obj
  inherit source_mark_props

  method next ?category () =
    may_map (fun m -> new source_mark m) (SourceMark.next obj category)
  method prev ?category () =
    may_map (fun m -> new source_mark m) (SourceMark.prev obj category)

end

let source_mark ?category () =
  new source_mark (SourceMark.create ?category [])

(** {2 GtkSourceUndoManager} *)

class source_undo_manager_signals obj' =
object (self)
  inherit ['a] gobject_signals (obj' : [> GtkSourceView2_types.source_undo_manager] obj)
  inherit source_undo_manager_sigs
end

class source_undo_manager
  (obj : GtkSourceView2_types.source_undo_manager obj) =
  object
    val obj = obj
    inherit source_undo_manager_props
    method as_source_undo_manager = obj
    method connect = new source_undo_manager_signals obj
  end

class type custom_undo_manager =
  object
    method can_undo : bool
    method can_redo : bool
    method undo : unit -> unit
    method redo : unit -> unit
    method begin_not_undoable_action : unit -> unit
    method end_not_undoable_action : unit -> unit
    method can_undo_changed : unit -> unit
    method can_redo_changed : unit -> unit
  end

let source_undo_manager (manager : custom_undo_manager) : source_undo_manager =
  let undo_manager = {
    SourceUndoManager.can_undo = (fun () -> manager#can_undo);
    can_redo = (fun () -> manager#can_redo);
    undo = manager#undo;
    redo = manager#redo;
    begin_not_undoable_action = manager#begin_not_undoable_action;
    end_not_undoable_action = manager#end_not_undoable_action;
    can_undo_changed = manager#can_undo_changed;
    can_redo_changed = manager#can_redo_changed;
  } in
  let obj = SourceUndoManager.new_ undo_manager in
  new source_undo_manager obj

(** {2 GtkSourceBuffer} *)

class source_buffer_signals obj' =
object
  inherit ['a] gobject_signals (obj' : [> GtkSourceView2_types.source_buffer] obj)
  inherit GText.buffer_signals_skel
  inherit source_buffer_sigs
end

and source_buffer (_obj: GtkSourceView2_types.source_buffer obj) =
object (self)
  inherit GText.buffer_skel _obj as text_buffer
  val obj = _obj
  method private obj = _obj
  inherit source_buffer_props
  method as_source_buffer = obj
  method connect = new source_buffer_signals obj
  method misc = new gobject_ops obj
  method language = may_map (new source_language) (get SourceBuffer.P.language obj)
  method set_language (l:source_language option) =
    set SourceBuffer.P.language obj
      (may_map (fun l -> l#as_source_language) l)

  method style_scheme =
    may_map (new source_style_scheme) (get SourceBuffer.P.style_scheme obj)
  method set_style_scheme (s:source_style_scheme option) =
      match s with
        None -> ()
      | Some scheme -> set SourceBuffer.P.style_scheme obj
          (Some scheme#as_source_style_scheme)

  method undo () = SourceBuffer.undo obj
  method redo () = SourceBuffer.redo obj
  method begin_not_undoable_action () =
    SourceBuffer.begin_not_undoable_action obj
  method end_not_undoable_action () =
    SourceBuffer.end_not_undoable_action obj

  method create_source_mark ?name ?category (iter:GText.iter) =
    new source_mark(SourceBuffer.create_source_mark obj name category iter#as_iter)

  method source_marks_at_line ?category line =
    List.map
      (fun mark -> new source_mark mark)
      (SourceBuffer.get_source_marks_at_line obj line category)

  method source_marks_at_iter ?category (iter:GText.iter) =
    List.map
      (fun mark -> new source_mark mark)
      (SourceBuffer.get_source_marks_at_iter obj iter#as_iter category)

  method remove_source_marks ?category ~(start:GText.iter) ~(stop:GText.iter) () =
    SourceBuffer.remove_source_marks obj start#as_iter stop#as_iter category

  method forward_iter_to_source_mark ?category (iter:GText.iter) =
    SourceBuffer.forward_iter_to_source_mark obj iter#as_iter category

  method backward_iter_to_source_mark ?category (iter:GText.iter) =
    SourceBuffer.backward_iter_to_source_mark obj iter#as_iter category

  method iter_has_context_class (iter:GText.iter) context_class =
    SourceBuffer.iter_has_context_class obj iter#as_iter context_class

  method iter_forward_to_context_class_toggle (iter:GText.iter) context_class =
    SourceBuffer.iter_forward_to_context_class_toggle obj iter#as_iter context_class

  method iter_backward_to_context_class_toggle (iter:GText.iter) context_class =
    SourceBuffer.iter_backward_to_context_class_toggle obj iter#as_iter context_class

  method ensure_highlight ~(start:GText.iter) ~(stop:GText.iter) =
    SourceBuffer.ensure_highlight obj start#as_iter stop#as_iter

  method set_undo_manager (manager : source_undo_manager) =
    let manager = manager#as_source_undo_manager in
    Gobject.set SourceBuffer.P.undo_manager obj manager

  method undo_manager =
    let manager = Gobject.get SourceBuffer.P.undo_manager obj in
    new source_undo_manager manager

end

let source_buffer ?(language:source_language option)
  ?(style_scheme:source_style_scheme option)
  ?(tag_table : GText.tag_table option) ?text ?(undo_manager : source_undo_manager option)  =
  let language =
    match language with
    | None -> None
    | Some source_language -> Some (source_language#as_source_language)
  in
  let style_scheme =
    match style_scheme with
    | None -> None
    | Some schm -> Some (schm#as_source_style_scheme)
  in
  let undo_manager =
    match undo_manager with
    | None -> None
    | Some manager -> Some (manager#as_source_undo_manager)
  in
  SourceBuffer.make_params [] ?language ?style_scheme ?undo_manager
    ~cont:(fun pl () ->
      let buf =
	match tag_table with
	  None ->
	    new source_buffer (SourceBuffer.create pl)
	| Some tt ->
	    let obj = SourceBuffer.new_ tt#as_tag_table in
	    Gobject.set_params (Gobject.try_cast obj "GtkSourceBuffer") pl;
	    new source_buffer obj
      in
      (match text with
      | None -> ()
      | Some text -> buf#set_text text);
      buf)

(** {2 GtkSourceView} *)

class source_view_signals obj' =
object
  inherit widget_signals_impl (obj' : [> GtkSourceView2_types.source_view] obj)
  inherit GText.view_signals obj'
  inherit source_view_sigs
end

class source_view (obj': GtkSourceView2_types.source_view obj) =
object (self)
  inherit GText.view_skel obj'
  inherit source_view_props

  val source_buf =
    let buf_obj =
      Gobject.try_cast (GtkText.View.get_buffer obj') "GtkSourceBuffer"
    in
    new source_buffer buf_obj
  method source_buffer = source_buf
  method connect = new source_view_signals obj'

  method set_cursor_color = SourceView.set_cursor_color obj
  method set_cursor_color_by_name s = SourceView.set_cursor_color obj (color_of_string s)

  method draw_spaces = SourceView.get_draw_spaces obj
  method set_draw_spaces flags = SourceView.set_draw_spaces obj flags

  method completion = new source_completion (SourceView.get_completion obj)

end

let source_view ?source_buffer ?draw_spaces =
  SourceView.make_params [] ~cont:(
    GtkText.View.make_params ~cont:(
      GContainer.pack_container ~create:(fun pl ->
        let obj =
          match source_buffer with
          | Some buf ->
              SourceView.new_with_buffer
                (Gobject.try_cast buf#as_buffer "GtkSourceBuffer")
          | None -> SourceView.new_ ()
        in
        Gobject.set_params (Gobject.try_cast obj "GtkSourceView") pl;
	may (SourceView.set_draw_spaces obj) draw_spaces;
        new source_view obj)))

(** {2 Misc} *)

let iter_forward_search (iter:GText.iter) flags
    ~start ~stop ?limit str =
  let limit = map_opt (fun x -> x#as_iter) limit in
  match SourceViewMisc.iter_forward_search iter#as_iter str
      flags ~start: start#as_iter ~stop: stop#as_iter limit
  with
    None -> None
  | Some (it1,it2) -> Some (new GText.iter it1, new GText.iter it2)

let iter_backward_search (iter:GText.iter) flags
    ~start ~stop ?limit str =
  let limit = map_opt (fun x -> x#as_iter) limit in
  match SourceViewMisc.iter_backward_search iter#as_iter str
      flags ~start: start#as_iter ~stop: stop#as_iter limit
  with
    None -> None
  | Some (it1,it2) -> Some (new GText.iter it1, new GText.iter it2)