]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/otherlibs/win32graph/events.c
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / otherlibs / win32graph / events.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 2004 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 6553 2004-07-13 12:25:21Z xleroy $ */
15
16 #include "mlvalues.h"
17 #include "alloc.h"
18 #include "libgraph.h"
19 #include <windows.h>
20
21 enum {
22   EVENT_BUTTON_DOWN = 1,
23   EVENT_BUTTON_UP = 2,
24   EVENT_KEY_PRESSED = 4,
25   EVENT_MOUSE_MOTION = 8
26 };
27
28 struct event_data {
29   short mouse_x, mouse_y;
30   unsigned char kind;
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 static int caml_gr_event_mask = EVENT_KEY_PRESSED;
40 static int last_button = 0;
41 static LPARAM last_pos = 0;
42
43 HANDLE caml_gr_queue_semaphore = NULL;
44 CRITICAL_SECTION caml_gr_queue_mutex;
45
46 void caml_gr_init_event_queue(void)
47 {
48   if (caml_gr_queue_semaphore == NULL) {
49     caml_gr_queue_semaphore = CreateSemaphore(NULL, 0, SIZE_QUEUE, NULL);
50     InitializeCriticalSection(&caml_gr_queue_mutex);
51   }
52 }
53
54 #define QueueIsEmpty (caml_gr_tail == caml_gr_head)
55
56 static void caml_gr_enqueue_event(int kind, LPARAM mouse_xy,
57                                   int button, int key)
58 {
59   struct event_data * ev;
60
61   if ((caml_gr_event_mask & kind) == 0) return;
62   EnterCriticalSection(&caml_gr_queue_mutex);
63   ev = &(caml_gr_queue[caml_gr_tail]);
64   ev->kind = kind;
65   ev->mouse_x = GET_X_LPARAM(mouse_xy);
66   ev->mouse_y = GET_Y_LPARAM(mouse_xy);
67   ev->button = (button != 0);
68   ev->key = key;
69   caml_gr_tail = (caml_gr_tail + 1) % SIZE_QUEUE;
70   /* If queue was full, it now appears empty;
71      drop oldest entry from queue. */
72   if (QueueIsEmpty) {
73     caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE;
74   } else {
75     /* One more event in queue */
76     ReleaseSemaphore(caml_gr_queue_semaphore, 1, NULL);
77   }
78   LeaveCriticalSection(&caml_gr_queue_mutex);
79 }
80
81 void caml_gr_handle_event(UINT msg, WPARAM wParam, LPARAM lParam)
82 {
83   switch (msg) {
84   case WM_LBUTTONDOWN:
85   case WM_RBUTTONDOWN:
86   case WM_MBUTTONDOWN:
87     last_button = 1;
88     last_pos = lParam;
89     caml_gr_enqueue_event(EVENT_BUTTON_DOWN, lParam, 1, 0);
90     break;
91
92   case WM_LBUTTONUP:
93   case WM_RBUTTONUP:
94   case WM_MBUTTONUP:
95     last_button = 0;
96     last_pos = lParam;
97     caml_gr_enqueue_event(EVENT_BUTTON_UP, lParam, 0, 0);
98     break;
99
100   case WM_CHAR:
101     caml_gr_enqueue_event(EVENT_KEY_PRESSED, last_pos, last_button, wParam);
102     break;
103
104   case WM_MOUSEMOVE:
105     last_pos = lParam;
106     caml_gr_enqueue_event(EVENT_MOUSE_MOTION, lParam, last_button, 0);
107     break;
108   }
109 }
110
111 static value caml_gr_wait_allocate_result(int mouse_x, int mouse_y,
112                                           int button,
113                                           int keypressed, int key)
114 {
115   value res = alloc_small(5, 0);
116   Field(res, 0) = Val_int(mouse_x);
117   Field(res, 1) = Val_int(grwindow.height - 1 - mouse_y);
118   Field(res, 2) = Val_bool(button);
119   Field(res, 3) = Val_bool(keypressed);
120   Field(res, 4) = Val_int(key & 0xFF);
121   return res;
122 }
123
124 static value caml_gr_wait_event_poll(void)
125 {
126   int key, keypressed, i;
127
128   /* Look inside event queue for pending KeyPress events */
129   EnterCriticalSection(&caml_gr_queue_mutex);
130   key = 0;
131   keypressed = 0;
132   for (i = caml_gr_head; i != caml_gr_tail; i = (i + 1) % SIZE_QUEUE) {
133     if (caml_gr_queue[i].kind == EVENT_KEY_PRESSED) {
134       keypressed = 1;
135       key = caml_gr_queue[i].key;
136       break;
137     }
138   }
139   LeaveCriticalSection(&caml_gr_queue_mutex);
140   /* Use global vars for mouse position and buttons */
141   return caml_gr_wait_allocate_result(GET_X_LPARAM(last_pos),
142                                       GET_Y_LPARAM(last_pos),
143                                       last_button,
144                                       keypressed, key);
145 }
146
147 static value caml_gr_wait_event_blocking(int mask)
148 {
149   struct event_data ev;
150
151   /* Increase the selected events if needed */
152   caml_gr_event_mask |= mask;
153   /* Pop events from queue until one matches */
154   do {
155     /* Wait for event queue to be non-empty */
156     WaitForSingleObject(caml_gr_queue_semaphore, INFINITE);
157     /* Pop oldest event in queue */
158     EnterCriticalSection(&caml_gr_queue_mutex);
159     ev = caml_gr_queue[caml_gr_head];
160     /* Queue should never be empty at this point, but just in case... */
161     if (QueueIsEmpty) {
162       ev.kind = 0;
163     } else {
164       caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE;
165     }
166     LeaveCriticalSection(&caml_gr_queue_mutex);
167     /* Check if it matches */
168   } while ((ev.kind & mask) == 0);
169   return caml_gr_wait_allocate_result(ev.mouse_x, ev.mouse_y, ev.button,
170                                       ev.kind == EVENT_KEY_PRESSED,
171                                       ev.key);
172 }
173
174 CAMLprim value caml_gr_wait_event(value eventlist) /* ML */
175 {
176   int mask, poll;
177
178   gr_check_open();
179   mask = 0;
180   poll = 0;
181   while (eventlist != Val_int(0)) {
182     switch (Int_val(Field(eventlist, 0))) {
183     case 0:                     /* Button_down */
184       mask |= EVENT_BUTTON_DOWN; break;
185     case 1:                     /* Button_up */
186       mask |= EVENT_BUTTON_UP; break;
187     case 2:                     /* Key_pressed */
188       mask |= EVENT_KEY_PRESSED; break;
189     case 3:                     /* Mouse_motion */
190       mask |= EVENT_MOUSE_MOTION; break;
191     case 4:                     /* Poll */
192       poll = 1; break;
193     }
194     eventlist = Field(eventlist, 1);
195   }
196   if (poll)
197     return caml_gr_wait_event_poll();
198   else
199     return caml_gr_wait_event_blocking(mask);
200 }