]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/otherlibs/graph/events.c
update
[l4.git] / l4 / pkg / ocaml / contrib / otherlibs / graph / events.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 1996 Institut National de Recherche en Informatique et   */
8 /*  en Automatique.  All rights reserved.  This file is distributed    */
9 /*  under the terms of the GNU Library General Public License, with    */
10 /*  the special exception on linking described in file ../../LICENSE.  */
11 /*                                                                     */
12 /***********************************************************************/
13
14 /* $Id: events.c 7019 2005-08-13 20:59:37Z doligez $ */
15
16 #include <signal.h>
17 #include "libgraph.h"
18 #include <alloc.h>
19 #include <signals.h>
20 #include <sys/types.h>
21 #include <sys/time.h>
22 #ifdef HAS_SYS_SELECT_H
23 #include <sys/select.h>
24 #endif
25 #include <string.h>
26 #include <unistd.h>
27
28 struct event_data {
29   short kind;
30   short mouse_x, mouse_y;
31   unsigned char button;
32   unsigned char key;
33 };
34
35 static struct event_data caml_gr_queue[SIZE_QUEUE];
36 static unsigned int caml_gr_head = 0;       /* position of next read */
37 static unsigned int caml_gr_tail = 0;       /* position of next write */
38
39 #define QueueIsEmpty (caml_gr_tail == caml_gr_head)
40
41 static void caml_gr_enqueue_event(int kind, int mouse_x, int mouse_y,
42                              int button, int key)
43 {
44   struct event_data * ev;
45
46   ev = &(caml_gr_queue[caml_gr_tail]);
47   ev->kind = kind;
48   ev->mouse_x = mouse_x;
49   ev->mouse_y = mouse_y;
50   ev->button = (button != 0);
51   ev->key = key;
52   caml_gr_tail = (caml_gr_tail + 1) % SIZE_QUEUE;
53   /* If queue was full, it now appears empty; drop oldest entry from queue. */
54   if (QueueIsEmpty) caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE;
55 }
56
57 #define BUTTON_STATE(state) \
58   ((state) & (Button1Mask|Button2Mask|Button3Mask|Button4Mask|Button5Mask))
59
60 void caml_gr_handle_event(XEvent * event)
61 {
62   switch (event->type) {
63
64   case Expose:
65     XCopyArea(caml_gr_display, caml_gr_bstore.win, caml_gr_window.win, caml_gr_window.gc,
66               event->xexpose.x, event->xexpose.y + caml_gr_bstore.h - caml_gr_window.h,
67               event->xexpose.width, event->xexpose.height,
68               event->xexpose.x, event->xexpose.y);
69     XFlush(caml_gr_display);
70     break;
71
72   case ConfigureNotify:
73     caml_gr_window.w = event->xconfigure.width;
74     caml_gr_window.h = event->xconfigure.height;
75     if (caml_gr_window.w > caml_gr_bstore.w || caml_gr_window.h > caml_gr_bstore.h) {
76
77       /* Allocate a new backing store large enough to accomodate
78          both the old backing store and the current window. */
79       struct canvas newbstore;
80       newbstore.w = max(caml_gr_window.w, caml_gr_bstore.w);
81       newbstore.h = max(caml_gr_window.h, caml_gr_bstore.h);
82       newbstore.win =
83         XCreatePixmap(caml_gr_display, caml_gr_window.win, newbstore.w, newbstore.h,
84                       XDefaultDepth(caml_gr_display, caml_gr_screen));
85       newbstore.gc = XCreateGC(caml_gr_display, newbstore.win, 0, NULL);
86       XSetBackground(caml_gr_display, newbstore.gc, caml_gr_white);
87       XSetForeground(caml_gr_display, newbstore.gc, caml_gr_white);
88       XFillRectangle(caml_gr_display, newbstore.win, newbstore.gc,
89                      0, 0, newbstore.w, newbstore.h);
90       XSetForeground(caml_gr_display, newbstore.gc, caml_gr_color);
91       if (caml_gr_font != NULL)
92         XSetFont(caml_gr_display, newbstore.gc, caml_gr_font->fid);
93
94       /* Copy the old backing store into the new one */
95       XCopyArea(caml_gr_display, caml_gr_bstore.win, newbstore.win, newbstore.gc,
96                 0, 0, caml_gr_bstore.w, caml_gr_bstore.h, 0, newbstore.h - caml_gr_bstore.h);
97
98       /* Free the old backing store */
99       XFreeGC(caml_gr_display, caml_gr_bstore.gc);
100       XFreePixmap(caml_gr_display, caml_gr_bstore.win);
101
102       /* Use the new backing store */
103       caml_gr_bstore = newbstore;
104       XFlush(caml_gr_display);
105     }
106     break;
107
108   case MappingNotify:
109     XRefreshKeyboardMapping(&(event->xmapping));
110     break;
111
112   case KeyPress:
113     { KeySym thekey;
114       char keytxt[256];
115       int nchars;
116       char * p;
117       nchars = XLookupString(&(event->xkey), keytxt, sizeof(keytxt),
118                              &thekey, 0);
119       for (p = keytxt; nchars > 0; p++, nchars--)
120         caml_gr_enqueue_event(event->type, event->xkey.x, event->xkey.y,
121                          BUTTON_STATE(event->xkey.state), *p);
122       break;
123     }
124
125   case ButtonPress:
126   case ButtonRelease:
127     caml_gr_enqueue_event(event->type, event->xbutton.x, event->xbutton.y,
128                      event->type == ButtonPress, 0);
129     break;
130
131   case MotionNotify:
132     caml_gr_enqueue_event(event->type, event->xmotion.x, event->xmotion.y,
133                      BUTTON_STATE(event->xmotion.state), 0);
134     break;
135   }
136 }
137
138 static value caml_gr_wait_allocate_result(int mouse_x, int mouse_y, int button,
139                                      int keypressed, int key)
140 {
141   value res = alloc_small(5, 0);
142   Field(res, 0) = Val_int(mouse_x);
143   Field(res, 1) = Val_int(mouse_y == -1 ? -1 : Wcvt(mouse_y));
144   Field(res, 2) = Val_bool(button);
145   Field(res, 3) = Val_bool(keypressed);
146   Field(res, 4) = Val_int(key & 0xFF);
147   return res;
148 }
149
150 static value caml_gr_wait_event_poll(void)
151 {
152   int mouse_x, mouse_y, button, key, keypressed;
153   Window rootwin, childwin;
154   int root_x, root_y, win_x, win_y;
155   unsigned int modifiers;
156   unsigned int i;
157
158   if (XQueryPointer(caml_gr_display, caml_gr_window.win,
159                     &rootwin, &childwin,
160                     &root_x, &root_y, &win_x, &win_y,
161                     &modifiers)) {
162     mouse_x = win_x;
163     mouse_y = win_y;
164   } else {
165     mouse_x = -1;
166     mouse_y = -1;
167   }
168   button = modifiers & (Button1Mask | Button2Mask | Button3Mask 
169                           | Button4Mask | Button5Mask);
170   /* Look inside event queue for pending KeyPress events */
171   key = 0;
172   keypressed = False;
173   for (i = caml_gr_head; i != caml_gr_tail; i = (i + 1) % SIZE_QUEUE) {
174     if (caml_gr_queue[i].kind == KeyPress) {
175       keypressed = True;
176       key = caml_gr_queue[i].key;
177       break;
178     }
179   }
180   return caml_gr_wait_allocate_result(mouse_x, mouse_y, button, keypressed, key);
181 }
182
183 static value caml_gr_wait_event_in_queue(long mask)
184 {
185   struct event_data * ev;
186   /* Pop events in queue until one matches mask. */
187   while (caml_gr_head != caml_gr_tail) {
188     ev = &(caml_gr_queue[caml_gr_head]);
189     caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE;
190     if ((ev->kind == KeyPress && (mask & KeyPressMask))
191         || (ev->kind == ButtonPress && (mask & ButtonPressMask))
192         || (ev->kind == ButtonRelease && (mask & ButtonReleaseMask))
193         || (ev->kind == MotionNotify && (mask & PointerMotionMask)))
194       return caml_gr_wait_allocate_result(ev->mouse_x, ev->mouse_y,
195                                      ev->button, ev->kind == KeyPress,
196                                      ev->key);
197   }
198   return Val_false;
199 }
200
201 static value caml_gr_wait_event_blocking(long mask)
202 {
203   XEvent event;
204   fd_set readfds;
205   value res;
206
207   /* First see if we have a matching event in the queue */
208   res = caml_gr_wait_event_in_queue(mask);
209   if (res != Val_false) return res;
210
211   /* Increase the selected events if required */
212   if ((mask & ~caml_gr_selected_events) != 0) {
213     caml_gr_selected_events |= mask;
214     XSelectInput(caml_gr_display, caml_gr_window.win, caml_gr_selected_events);
215   }
216
217   /* Replenish our event queue from that of X11 */
218   caml_gr_ignore_sigio = True;
219   while (1) {
220     if (XCheckMaskEvent(caml_gr_display, -1 /*all events*/, &event)) {
221       /* One event available: add it to our queue */
222       caml_gr_handle_event(&event);
223       /* See if we now have a matching event */
224       res = caml_gr_wait_event_in_queue(mask);
225       if (res != Val_false) break;
226     } else {
227       /* No event available: block on input socket until one is */
228       FD_ZERO(&readfds);
229       FD_SET(ConnectionNumber(caml_gr_display), &readfds);
230       enter_blocking_section();
231       select(FD_SETSIZE, &readfds, NULL, NULL, NULL);
232       leave_blocking_section();
233       caml_gr_check_open(); /* in case another thread closed the display */
234     }
235   }
236   caml_gr_ignore_sigio = False;
237
238   /* Return result */
239   return res;
240 }
241
242 value caml_gr_wait_event(value eventlist) /* ML */
243 {
244   int mask;
245   Bool poll;
246
247   caml_gr_check_open();
248   mask = 0;
249   poll = False;
250   while (eventlist != Val_int(0)) {
251     switch (Int_val(Field(eventlist, 0))) {
252     case 0:                     /* Button_down */
253       mask |= ButtonPressMask | OwnerGrabButtonMask; break;
254     case 1:                     /* Button_up */
255       mask |= ButtonReleaseMask | OwnerGrabButtonMask; break;
256     case 2:                     /* Key_pressed */
257       mask |= KeyPressMask; break;
258     case 3:                     /* Mouse_motion */
259       mask |= PointerMotionMask; break;
260     case 4:                     /* Poll */
261       poll = True; break;
262     }
263     eventlist = Field(eventlist, 1);
264   }
265   if (poll)
266     return caml_gr_wait_event_poll();
267   else
268     return caml_gr_wait_event_blocking(mask);
269 }