~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to otherlibs/labltk/frx/frx_req.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
16
16
open Camltk
17
17
 
18
18
(*
19
 
 * Some standard requesters (in Amiga techspeak) or dialog boxes (in Apple 
 
19
 * Some standard requesters (in Amiga techspeak) or dialog boxes (in Apple
20
20
 * jargon).
21
21
*)
22
22
 
23
 
let version = "$Id: frx_req.ml 5029 2002-07-23 14:12:03Z doligez $"
 
23
let version = "$Id: frx_req.ml 9547 2010-01-22 12:48:24Z doligez $"
24
24
 
25
25
(*
26
 
 * Simple requester 
 
26
 * Simple requester
27
27
 *  an entry field, unrestricted, with emacs-like bindings
28
28
 * Note: grabs focus, thus always unique at one given moment, and we
29
29
 *  shouldn't have to worry about toplevel widget name.
51
51
  let f = Frame.create t [] in
52
52
  let bok = Button.create f [Text "Ok"; Command activate] in
53
53
  let bcancel = Button.create f
54
 
            [Text "Cancel"; 
 
54
            [Text "Cancel";
55
55
             Command (fun () -> notaction(); Grab.release t; destroy t)] in
56
56
 
57
57
    bind e [[], KeyPressDetail "Escape"]
76
76
    Entry.create t [Relief Sunken; TextVariable memory; TextWidth len] in
77
77
 
78
78
  let waiting = Textvariable.create_temporary t in
79
 
  
 
79
 
80
80
  let activate _ =
81
81
     Grab.release t;                    (* because of wm *)
82
82
     destroy t;                         (* so action can call open_simple *)
86
86
 
87
87
  let f = Frame.create t [] in
88
88
  let bok = Button.create f [Text "Ok"; Command activate] in
89
 
  let bcancel = 
 
89
  let bcancel =
90
90
     Button.create f
91
 
        [Text "Cancel"; 
92
 
         Command (fun () -> 
 
91
        [Text "Cancel";
 
92
         Command (fun () ->
93
93
                   Grab.release t; destroy t; Textvariable.set waiting "0")] in
94
94
 
95
95
    bind e [[], KeyPressDetail "Escape"]
118
118
  Wm.title_set t title;
119
119
 
120
120
  let tit = Label.create t [Text title] in
121
 
  let fls = Frame.create t [Relief Sunken; BorderWidth (Pixels 2)] in 
 
121
  let fls = Frame.create t [Relief Sunken; BorderWidth (Pixels 2)] in
122
122
  let lb = Listbox.create fls [SelectMode Extended] in
123
123
  let sb = Scrollbar.create fls [] in
124
124
    Frx_listbox.scroll_link sb lb;
135
135
 
136
136
  bind lb [[Double], ButtonPressDetail 1] (BindSetBreakable ([], activate));
137
137
 
138
 
  Frx_listbox.add_completion lb activate; 
 
138
  Frx_listbox.add_completion lb activate;
139
139
 
140
140
  let f = Frame.create t [] in
141
141
  let bok = Button.create f [Text "Ok"; Command activate] in
142
 
  let bcancel = Button.create f 
143
 
            [Text "Cancel"; 
 
142
  let bcancel = Button.create f
 
143
            [Text "Cancel";
144
144
             Command (fun () -> notaction(); Grab.release t; destroy t)] in
145
145
 
146
146
    pack [bok; bcancel] [Side Side_Left; Fill Fill_X; Expand true];
167
167
  and fp,ep = Frx_entry.new_label_entry t "Password" (fun s -> ())
168
168
  in
169
169
  let fb = Frame.create t [] in
170
 
   let bok = Button.create fb 
171
 
              [Text "Ok"; Command (fun _ -> 
 
170
   let bok = Button.create fb
 
171
              [Text "Ok"; Command (fun _ ->
172
172
                                    username := Entry.get eu;
173
173
                                    password := Entry.get ep;
174
174
                                    Grab.release t; (* because of wm *)
183
183
    bind eu [[], KeyPressDetail "Return"]
184
184
      (BindSetBreakable ([], (fun _ -> Focus.set ep; break())));
185
185
    bind ep [[], KeyPressDetail "Return"]
186
 
      (BindSetBreakable ([], (fun _ -> Button.flash bok; 
187
 
                                       Button.invoke bok; 
 
186
      (BindSetBreakable ([], (fun _ -> Button.flash bok;
 
187
                                       Button.invoke bok;
188
188
                                       break())));
189
189
 
190
190
    pack [bok] [Side Side_Left; Expand true];