chiark / gitweb /
Clearing stack allocated memory
[clg] / glib / gcallback.lisp
1 ;; Common Lisp bindings for GTK+ v2.x
2 ;; Copyright 2000 Espen S. Johnsen <espen@users.sf.net>
3 ;;
4 ;; Permission is hereby granted, free of charge, to any person obtaining
5 ;; a copy of this software and associated documentation files (the
6 ;; "Software"), to deal in the Software without restriction, including
7 ;; without limitation the rights to use, copy, modify, merge, publish,
8 ;; distribute, sublicense, and/or sell copies of the Software, and to
9 ;; permit persons to whom the Software is furnished to do so, subject to
10 ;; the following conditions:
11 ;;
12 ;; The above copyright notice and this permission notice shall be
13 ;; included in all copies or substantial portions of the Software.
14 ;;
15 ;; THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
16 ;; EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
17 ;; MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
18 ;; IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
19 ;; CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
20 ;; TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
21 ;; SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
22
23 ;; $Id: gcallback.lisp,v 1.31 2006-02-19 19:53:52 espen Exp $
24
25 (in-package "GLIB")
26
27 (use-prefix "g")
28
29
30 ;;;; Callback invokation
31
32 (deftype gclosure () 'pointer)
33 (register-type 'gclosure '|g_closure_get_type|)
34
35 (defun register-callback-function (function)
36   (check-type function (or null symbol function))
37   (register-user-data function))
38
39 ;; Callback marshal for regular signal handlers
40 (define-callback closure-marshal nil
41     ((gclosure gclosure) (return-value gvalue) (n-params unsigned-int) 
42      (param-values pointer) (invocation-hint pointer) 
43      (callback-id unsigned-int))
44   (declare (ignore gclosure invocation-hint))
45   (callback-trampoline callback-id n-params param-values return-value))
46
47 ;; Callback function for emission hooks
48 (define-callback signal-emission-hook nil
49     ((invocation-hint pointer) (n-params unsigned-int) (param-values pointer)
50      (callback-id unsigned-int))
51   (callback-trampoline callback-id n-params param-values))
52
53 (defun callback-trampoline (callback-id n-params param-values &optional
54                             (return-value (make-pointer 0)))
55   (let* ((return-type (unless (null-pointer-p return-value)
56                         (gvalue-type return-value)))
57          (args (loop
58                 for n from 0 below n-params
59                 for offset from 0 by +gvalue-size+
60                 collect (gvalue-get (sap+ param-values offset) t))))
61     (unwind-protect
62         (let ((result (apply #'invoke-callback callback-id return-type args)))
63           (when return-type
64             (gvalue-set return-value result)))
65       (loop 
66        for arg in args
67        when (typep arg 'proxy)
68        do (invalidate-instance arg)))))
69
70
71 (defun invoke-callback (callback-id return-type &rest args)
72   (restart-case
73       (apply (find-user-data callback-id) args)
74     (continue nil :report "Return from callback function"
75               (when return-type
76                 (format *query-io* "Enter return value of type ~S: " return-type)
77                 (force-output *query-io*)
78                 (eval (read *query-io*))))
79     (re-invoke nil :report "Re-invoke callback function"
80                (apply #'invoke-callback callback-id return-type args))))
81
82
83 ;;;; Timeouts and idle functions
84
85 (defconstant +priority-high+ -100)
86 (defconstant +priority-default+ 0)
87 (defconstant +priority-high-idle+ 100)
88 (defconstant +priority-default-idle+ 200)
89 (defconstant +priority-low+ 300)
90
91 (defbinding source-remove () boolean
92   (tag unsigned-int))
93
94 (define-callback source-callback-marshal nil ((callback-id unsigned-int))
95   (callback-trampoline callback-id 0 nil))
96
97 (defbinding (timeout-add "g_timeout_add_full")
98     (interval function &optional (priority +priority-default+)) unsigned-int 
99   (priority int)
100   (interval unsigned-int)
101   (source-callback-marshal callback)
102   ((register-callback-function function) unsigned-long)
103   (user-data-destroy-callback callback))
104
105 (defun timeout-remove (timeout)
106   (source-remove timeout))
107
108 (defbinding (idle-add "g_idle_add_full")
109     (function &optional (priority +priority-default-idle+)) unsigned-int 
110   (priority int)
111   (source-callback-marshal callback)
112   ((register-callback-function function) unsigned-long)
113   (user-data-destroy-callback callback))
114
115 (defun idle-remove (idle)
116   (source-remove idle))
117
118
119 ;;;; Signal information querying
120
121 (defbinding signal-lookup (name type) unsigned-int
122   ((signal-name-to-string name) string)
123   ((find-type-number type t) type-number))
124
125 (defbinding signal-name () (copy-of string)
126   (signal-id unsigned-int))
127
128 (defbinding signal-list-ids (type) (vector unsigned-int n-ids)
129   ((find-type-number type t) type-number)
130   (n-ids unsigned-int :out))
131
132 (defun signal-list-names (type)
133   (map 'list #'signal-name (signal-list-ids type)))
134
135 (defun ensure-signal-id-from-type (signal-id type)
136   (etypecase signal-id
137     (integer (if (signal-name signal-id)
138                  signal-id
139                (error "Invalid signal id: ~D" signal-id)))
140     ((or symbol string) 
141      (let ((numeric-id (signal-lookup signal-id type)))
142        (if (zerop numeric-id)
143            (error "Invalid signal name for ~S: ~D" type signal-id)
144          numeric-id)))))
145
146 (defun ensure-signal-id (signal-id instance)
147   (ensure-signal-id-from-type signal-id (type-of instance)))
148   
149 (eval-when (:compile-toplevel :load-toplevel :execute)
150   (deftype signal-flags () 
151     '(flags :run-first :run-last :run-cleanup :no-recurse 
152             :detailed :action :no-hooks))
153
154   (defclass signal-query (struct)
155     ((id :allocation :alien :type unsigned-int)
156      (name :allocation :alien :type (copy-of string))
157      (type :allocation :alien :type type-number)
158      (flags :allocation :alien :type signal-flags)
159      (return-type :allocation :alien :type type-number)
160      (n-params :allocation :alien :type unsigned-int)
161      (param-types :allocation :alien :type pointer))
162     (:metaclass struct-class)))
163
164 (defbinding signal-query 
165     (signal-id &optional (signal-query (make-instance 'signal-query))) nil
166   (signal-id unsigned-int)
167   (signal-query signal-query :return))
168
169 (defun signal-param-types (info)
170   (with-slots (n-params param-types) info
171    (map-c-vector 'list 
172     #'(lambda (type-number) 
173         (type-from-number type-number))
174     param-types 'type-number n-params)))
175
176
177 (defun describe-signal (signal-id &optional type)
178   (let ((info (signal-query (ensure-signal-id-from-type signal-id type))))
179     (with-slots (id name type flags return-type n-params) info
180       (format t "The signal with id ~D is named '~A' and may be emitted on instances of type ~S~%~%" id name (type-from-number type t))
181       (format t "Signal handlers should return ~A and take ~A~%"
182        (cond
183         ((= return-type (find-type-number "void")) "no values")
184         ((not (type-from-number return-type)) "values of unknown type")
185         ((format nil "values of type ~S" (type-from-number return-type))))
186        (if (zerop n-params)
187            "no arguments"
188          (format nil "arguments with the following types: ~A"
189           (signal-param-types info)))))))
190
191
192 ;;;; Signal connecting and controlling
193
194 (defvar *overridden-signals* (make-hash-table :test 'equalp))
195
196 (defbinding %signal-override-class-closure () nil
197   (signal-id unsigned-int)
198   (type-number type-number)
199   (callback-closure pointer))
200
201
202 (defun signal-override-class-closure (name type function)
203   (let* ((signal-id (ensure-signal-id-from-type name type))
204          (type-number (find-type-number type t))
205          (callback-id (gethash (cons type-number signal-id) *overridden-signals*)))
206     (if callback-id
207         (update-user-data callback-id function)
208       (multiple-value-bind (callback-closure callback-id)
209           (make-callback-closure function)
210         (%signal-override-class-closure signal-id type-number callback-closure)
211         (setf 
212          (gethash (cons type-number signal-id) *overridden-signals*)
213          callback-id)))))
214
215
216 (defbinding %signal-chain-from-overridden () nil
217   (args pointer)
218   (return-value (or null gvalue)))
219
220
221 (defun %call-next-handler (n-params types args return-type)
222   (let ((params (allocate-memory (* n-params +gvalue-size+))))
223     (loop 
224      for arg in args
225      for type in types
226      for offset from 0 by +gvalue-size+
227      do (gvalue-init (sap+ params offset) type arg))
228
229     (unwind-protect
230         (if return-type
231             (with-gvalue (return-value return-type)
232               (%signal-chain-from-overridden params return-value))
233           (%signal-chain-from-overridden params nil))
234       (progn
235         (loop
236          repeat n-params
237          for offset from 0 by +gvalue-size+
238          do (gvalue-unset (sap+ params offset)))
239         (deallocate-memory params)))))
240
241
242 (defmacro define-signal-handler (name ((object class) &rest args) &body body)
243   (let* ((info (signal-query (ensure-signal-id-from-type name class)))
244          (types (cons class (signal-param-types info)))
245          (n-params (1+ (slot-value info 'n-params)))
246          (return-type (type-from-number (slot-value info 'return-type)))
247          (vars (loop
248                 for arg in args
249                 until (eq arg '&rest)
250                 collect arg))
251          (rest (cadr (member '&rest args)))
252          (next (make-symbol "ARGS"))
253          (default (make-symbol "DEFAULT")))
254
255     `(progn
256        (signal-override-class-closure ',name ',class 
257         #'(lambda (,object ,@args)
258             (let ((,default (list* ,object ,@vars ,rest)))
259               (flet ((call-next-handler (&rest ,next)
260                        (%call-next-handler 
261                         ,n-params ',types (or ,next ,default) ',return-type))))
262               ,@body)))
263        ',name)))
264
265
266 (defbinding %signal-stop-emission () nil
267   (instance ginstance)
268   (signal-id unsigned-int)
269   (detail quark))
270
271 (defvar *signal-stop-emission* nil)
272 (declaim (special *signal-stop-emission*))
273
274 (defun signal-stop-emission ()
275   (if *signal-stop-emission*
276       (funcall *signal-stop-emission*)
277     (error "Not inside a signal handler")))
278
279
280 (defbinding signal-add-emission-hook (type signal function &key (detail 0))
281     unsigned-int
282   ((ensure-signal-id-from-type signal type) unsigned-int)
283   (detail quark)
284   (signal-emission-hook callback)
285   ((register-callback-function function) unsigned-int)
286   (user-data-destroy-callback callback))
287
288 (defbinding signal-remove-emission-hook (type signal hook-id) nil
289   ((ensure-signal-id-from-type signal type) unsigned-int)
290   (hook-id unsigned-int))
291
292
293 (defbinding (signal-has-handler-pending-p "g_signal_has_handler_pending")
294     (instance signal-id &key detail blocked) boolean
295   (instance ginstance)
296   ((ensure-signal-id signal-id instance) unsigned-int)
297   ((or detail 0) quark)
298   (blocked boolean))
299     
300 (defbinding %signal-connect-closure-by-id () unsigned-int
301   (instance ginstance)
302   (signal-id unsigned-int)
303   (detail quark)
304   (closure pointer)
305   (after boolean))
306
307 (defbinding signal-handler-block () nil
308   (instance ginstance)
309   (handler-id unsigned-int))
310
311 (defbinding signal-handler-unblock () nil
312   (instance ginstance)
313   (handler-id unsigned-int))
314
315 (defbinding signal-handler-disconnect () nil
316   (instance ginstance)
317   (handler-id unsigned-int))
318
319 (defbinding signal-handler-is-connected-p () boolean
320   (instance ginstance)
321   (handler-id unsigned-int))
322
323 (defbinding (callback-closure-new "clg_callback_closure_new") () gclosure
324   (callback-id unsigned-int) 
325   (callback callback)
326   (destroy-notify callback))
327
328 (defun make-callback-closure (function)
329   (let ((callback-id (register-callback-function function)))
330     (values
331      (callback-closure-new callback-id closure-marshal user-data-destroy-callback)
332      callback-id)))
333
334 (defgeneric compute-signal-function (gobject signal function object))
335
336 (defmethod compute-signal-function ((gobject gobject) signal function object)
337   (declare (ignore signal))
338   (cond
339    ((or (eq object t) (eq object gobject)) function)
340    ((not object)
341     #'(lambda (&rest args) (apply function (rest args))))
342    (t
343     #'(lambda (&rest args) (apply function object (rest args))))))
344
345
346 (defgeneric compute-signal-id (gobject signal))
347
348 (defmethod compute-signal-id ((gobject gobject) signal)
349   (ensure-signal-id signal gobject))
350
351
352 (defgeneric signal-connect (gobject signal function &key detail after object remove))
353
354 (defmethod signal-connect :around ((gobject gobject) signal function &rest args)
355   (declare (ignore gobject signal args))
356   (when function
357     (call-next-method)))
358
359
360 (defmethod signal-connect ((gobject gobject) signal function
361                            &key detail after object remove)
362 "Connects a callback function to a signal for a particular object. If
363 :OBJECT is T, the object connected to is passed as the first argument
364 to the callback function, or if :OBJECT is any other non NIL value, it
365 is passed as the first argument instead. If :AFTER is non NIL, the
366 handler will be called after the default handler for the signal. If
367 :REMOVE is non NIL, the handler will be removed after beeing invoked
368 once."
369 (let* ((signal-id (compute-signal-id gobject signal))
370        (detail-quark (if detail (quark-intern detail) 0))
371        (signal-stop-emission
372         #'(lambda ()
373             (%signal-stop-emission gobject signal-id detail-quark)))
374        (callback (compute-signal-function gobject signal function object))
375        (wrapper #'(lambda (&rest args)
376                     (let ((*signal-stop-emission* signal-stop-emission))
377                       (apply callback args)))))
378       (multiple-value-bind (closure-id callback-id)
379           (make-callback-closure wrapper)
380         (let ((handler-id (%signal-connect-closure-by-id 
381                            gobject signal-id detail-quark closure-id after)))
382           (when remove
383             (update-user-data callback-id
384              #'(lambda (&rest args)
385                  (unwind-protect
386                      (let ((*signal-stop-emission* signal-stop-emission))
387                        (apply callback args))
388                    (signal-handler-disconnect gobject handler-id)))))
389           handler-id))))
390
391
392 ;;;; Signal emission
393
394 (defbinding %signal-emitv () nil
395   (gvalues pointer)
396   (signal-id unsigned-int)
397   (detail quark)
398   (return-value gvalue))
399
400 (defvar *signal-emit-functions* (make-hash-table))
401
402 (defun create-signal-emit-function (signal-id)
403   (let ((info (signal-query signal-id)))
404     (let* ((type (type-from-number (slot-value info 'type)))
405            (param-types (cons type (signal-param-types info)))
406            (return-type (type-from-number (slot-value info 'return-type)))
407            (n-params (1+ (slot-value info 'n-params)))
408            (params (allocate-memory (* n-params +gvalue-size+))))
409       #'(lambda (detail object &rest args)
410           (unless (= (length args) (1- n-params))
411             (error "Invalid number of arguments: ~A" (+ 2 (length args))))
412           (unwind-protect
413               (loop
414                for arg in (cons object args)
415                for type in param-types
416                as tmp = params then (sap+ tmp +gvalue-size+)
417                do (gvalue-init tmp type arg)          
418                finally 
419                (if return-type
420                    (return 
421                     (with-gvalue (return-value)
422                       (%signal-emitv params signal-id detail return-value)))
423                  (%signal-emitv params signal-id detail (make-pointer 0))))
424             (loop
425              repeat n-params
426              as tmp = params then (sap+ tmp +gvalue-size+)
427              while (gvalue-p tmp)
428              do (gvalue-unset tmp)))))))
429
430 (defun signal-emit-with-detail (object signal detail &rest args)
431   (let* ((signal-id (ensure-signal-id signal object))
432          (function (or 
433                     (gethash signal-id *signal-emit-functions*)
434                     (setf 
435                      (gethash signal-id *signal-emit-functions*)
436                      (create-signal-emit-function signal-id)))))
437     (apply function detail object args)))
438
439 (defun signal-emit (object signal &rest args)
440   (apply #'signal-emit-with-detail object signal 0 args))
441
442
443 ;;;; Convenient macros
444
445 (defmacro define-callback-marshal (name return-type args &key (callback-id :last))
446   (let* ((ignore ())
447          (params ())
448          (names (loop 
449                  for arg in args 
450                  collect (if (or 
451                               (eq arg :ignore) 
452                               (and (consp arg) (eq (first arg) :ignore)))
453                              (let ((name (gensym "IGNORE")))
454                                (push name ignore)
455                                name)
456                            (let ((name (if (atom arg)
457                                            (gensym (string arg))
458                                          (first arg))))
459                              (push name params)
460                              name))))
461          (types (loop 
462                  for arg in args 
463                  collect (cond
464                           ((eq arg :ignore) 'pointer)
465                           ((atom arg) arg)
466                           (t (second arg))))))
467     `(define-callback ,name ,return-type 
468        ,(ecase callback-id
469           (:first `((callback-id unsigned-int) ,@(mapcar #'list names types)))
470           (:last `(,@(mapcar #'list names types) (callback-id unsigned-int))))
471        (declare (ignore ,@ignore))
472        (invoke-callback callback-id ',return-type ,@params))))
473
474 (defmacro with-callback-function ((id function) &body body)
475   `(let ((,id (register-callback-function ,function)))
476     (unwind-protect
477          (progn ,@body)
478       (destroy-user-data ,id))))
479
480 ;; For backward compatibility
481 (defmacro def-callback-marshal (name (return-type &rest args))
482   `(define-callback-marshal ,name ,return-type ,args))