chiark / gitweb /
New type USER-CALLBACK and a bug fix
[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.46 2007-08-20 11:15:13 espen Exp $
24
25 (in-package "GLIB")
26
27 (use-prefix "g")
28
29
30 ;;;; Callback invocation
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 (deftype user-callback () '(or function symbol))
40
41 (define-type-method alien-type ((type user-callback))
42   (declare (ignore type))
43   (alien-type 'pointer-data))
44
45 (define-type-method to-alien-form ((type user-callback) func &optional copy-p)
46   (declare (ignore type copy-p))
47   `(register-callback-function ,func))
48
49
50 ;; Callback marshaller for regular signal handlers
51 (define-callback signal-handler-marshal nil
52     ((gclosure gclosure) (return-value gvalue) (n-params unsigned-int) 
53      (param-values pointer) (invocation-hint pointer) 
54      (callback-id pointer-data))
55   (declare (ignore gclosure invocation-hint))
56   (callback-trampoline #'invoke-signal-handler callback-id n-params param-values return-value))
57
58 ;; Callback marshaller for class handlers
59 (define-callback class-handler-marshal nil
60     ((gclosure gclosure) (return-value gvalue) (n-params unsigned-int) 
61      (param-values pointer) (invocation-hint pointer) 
62      (callback-id pointer-data))
63   (declare (ignore gclosure invocation-hint))
64   (callback-trampoline #'invoke-callback callback-id n-params param-values return-value))
65
66 ;; Callback marshaller for emission hooks
67 (define-callback emission-hook-marshal nil
68     ((invocation-hint pointer) (n-params unsigned-int) (param-values pointer)
69      (callback-id pointer-data))
70   (declare (ignore invocation-hint))
71   (callback-trampoline #'invoke-callback callback-id n-params param-values))
72
73 (defun callback-trampoline (restart-wrapper callback-id n-params param-values 
74                             &optional (return-value (make-pointer 0)))
75   (let* ((return-type (unless (null-pointer-p return-value)
76                         (gvalue-type return-value)))
77          (args (loop
78                 for n from 0 below n-params
79                 for offset from 0 by +gvalue-size+
80                 collect (gvalue-peek (pointer+ param-values offset)))))
81     (unwind-protect
82         (multiple-value-bind (result aborted-p)
83             (apply restart-wrapper callback-id nil args)
84           (when (and return-type (not aborted-p))
85             (gvalue-set return-value result)))
86       ;; TODO: this should be made more general, by adding a type
87       ;; method to return invalidating functions.
88       (loop 
89        for arg in args
90        when (typep arg 'struct)
91        do (invalidate-instance arg)))))
92
93 (defun invoke-signal-handler (callback-id return-type &rest args)
94   (declare (ignore return-type))
95   (let* ((instance (first args))
96          (handler-id (signal-handler-find instance '(:data) 
97                       0 0 nil nil callback-id)))
98     (signal-handler-block instance handler-id)
99     (unwind-protect
100         (restart-case (apply #'invoke-callback callback-id nil args)
101           (disconnect () :report "Disconnect and exit signal handler"
102             (when (signal-handler-is-connected-p instance handler-id)
103               (signal-handler-disconnect instance handler-id))
104             (values nil t)))
105       (when (signal-handler-is-connected-p instance handler-id)
106         (signal-handler-unblock instance handler-id)))))
107
108 (defun invoke-callback (callback-id return-type &rest args)
109   (restart-case (apply (find-user-data callback-id) args)
110     (continue nil :report "Return from callback function"
111       (cond
112        (return-type
113         (format *query-io* "Enter return value of type ~S: " return-type)
114         (force-output *query-io*)
115         (eval (read *query-io*)))
116        (t (values nil t))))
117     (re-invoke nil :report "Re-invoke callback function"
118       (apply #'invoke-callback callback-id return-type args))))
119
120
121 ;;;; Timeouts and idle functions
122
123 (defconstant +priority-high+ -100)
124 (defconstant +priority-default+ 0)
125 (defconstant +priority-high-idle+ 100)
126 (defconstant +priority-default-idle+ 200)
127 (defconstant +priority-low+ 300)
128
129 (defbinding source-remove () boolean
130   (tag unsigned-int))
131
132 (define-callback source-callback-marshal boolean ((callback-id unsigned-int))
133   (invoke-source-callback callback-id))
134
135 (defun invoke-source-callback (callback-id &rest args)
136   (restart-case (apply (find-user-data callback-id) args)
137     (remove () :report "Exit and remove source callback"
138       nil)
139     (continue () :report "Return from source callback"
140       t)
141     (re-invoke nil :report "Re-invoke source callback"
142       (apply #'invoke-source-callback callback-id args))))
143
144
145 (defbinding (timeout-add "g_timeout_add_full")
146     (interval function &optional (priority +priority-default+)) unsigned-int 
147   (priority int)
148   (interval unsigned-int)
149   (source-callback-marshal callback)
150   ((register-callback-function function) unsigned-long)
151   (user-data-destroy-callback callback))
152
153 (defun timeout-remove (timeout)
154   (source-remove timeout))
155
156 (defbinding (idle-add "g_idle_add_full")
157     (function &optional (priority +priority-default-idle+)) unsigned-int 
158   (priority int)
159   (source-callback-marshal callback)
160   ((register-callback-function function) unsigned-long)
161   (user-data-destroy-callback callback))
162
163 (defun idle-remove (idle)
164   (source-remove idle))
165
166
167 ;;;; Signal information querying
168
169 (defbinding signal-lookup (name type) unsigned-int
170   ((signal-name-to-string name) string)
171   ((find-type-number type t) type-number))
172
173 (defbinding signal-name () (copy-of string)
174   (signal-id unsigned-int))
175
176 (defbinding signal-list-ids (type) (vector unsigned-int n-ids)
177   ((find-type-number type t) type-number)
178   (n-ids unsigned-int :out))
179
180 (defun signal-list-names (type)
181   (map 'list #'signal-name (signal-list-ids type)))
182
183 (defun ensure-signal-id-from-type (signal-id type)
184   (etypecase signal-id
185     (integer (if (signal-name signal-id)
186                  signal-id
187                (error "Invalid signal id: ~D" signal-id)))
188     ((or symbol string) 
189      (let ((numeric-id (signal-lookup signal-id type)))
190        (if (zerop numeric-id)
191            (error "Invalid signal name for ~S: ~D" type signal-id)
192          numeric-id)))))
193
194 (defun ensure-signal-id (signal-id instance)
195   (ensure-signal-id-from-type signal-id (type-of instance)))
196   
197 (eval-when (:compile-toplevel :load-toplevel :execute)
198   (deftype signal-flags () 
199     '(flags :run-first :run-last :run-cleanup :no-recurse 
200             :detailed :action :no-hooks))
201
202   (define-flags-type signal-match-type
203     :id :detail :closure :func :data :unblocked)
204
205   (defclass signal-query (struct)
206     ((id :allocation :alien :type unsigned-int)
207      (name :allocation :alien :type (copy-of string))
208      (type :allocation :alien :type type-number)
209      (flags :allocation :alien :type signal-flags)
210      (return-type :allocation :alien :type type-number)
211      (n-params :allocation :alien :type unsigned-int)
212      (param-types :allocation :alien :type pointer))
213     (:metaclass struct-class)))
214
215 (defbinding signal-query 
216     (signal-id &optional (signal-query (make-instance 'signal-query))) nil
217   (signal-id unsigned-int)
218   (signal-query signal-query :in/return))
219
220 (defun signal-param-types (info)
221   (with-slots (n-params param-types) info
222    (map-c-vector 'list 
223     #'(lambda (type-number) 
224         (type-from-number type-number))
225     param-types 'type-number n-params)))
226
227
228 (defun describe-signal (signal-id &optional type)
229   (let ((info (signal-query (ensure-signal-id-from-type signal-id type))))
230     (with-slots (id name type flags return-type n-params) info
231       (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))
232       (when flags
233         (format t " It has the followin invocation flags: ~{~S ~}" flags))
234       (format t "~%~%Signal handlers should take ~A and return ~A~%"
235        (if (zerop n-params)
236            "no arguments"
237          (format nil "arguments with the following types: ~A"
238           (signal-param-types info)))
239        (cond
240         ((= return-type (find-type-number "void")) "no values")
241         ((not (type-from-number return-type)) "values of unknown type")
242         ((format nil "values of type ~S" (type-from-number return-type))))))))
243
244
245 ;;;; Signal connecting and controlling
246
247 (defvar *overridden-signals* (make-hash-table :test 'equalp))
248
249 (defbinding %signal-override-class-closure () nil
250   (signal-id unsigned-int)
251   (type-number type-number)
252   (callback-closure pointer))
253
254
255 (defun signal-override-class-closure (name type function)
256   (let* ((signal-id (ensure-signal-id-from-type name type))
257          (type-number (find-type-number type t))
258          (callback-id (gethash (cons type-number signal-id) *overridden-signals*)))
259     (if callback-id
260         (update-user-data callback-id function)
261       (multiple-value-bind (callback-closure callback-id)
262           (make-callback-closure function class-handler-marshal)
263         (%signal-override-class-closure signal-id type-number callback-closure)
264         (setf 
265          (gethash (cons type-number signal-id) *overridden-signals*)
266          callback-id)))))
267
268
269 (defbinding %signal-chain-from-overridden () nil
270   (args pointer)
271   (return-value (or null gvalue)))
272
273
274 (defun %call-next-handler (n-params types args return-type)
275   (let ((params (allocate-memory (* n-params +gvalue-size+))))
276     (loop 
277      for arg in args
278      for type in types
279      for offset from 0 by +gvalue-size+
280      do (gvalue-init (pointer+ params offset) type arg))
281
282     (unwind-protect
283         (if return-type
284             (with-gvalue (return-value return-type)
285               (%signal-chain-from-overridden params return-value))
286           (%signal-chain-from-overridden params nil))
287       (progn
288         (loop
289          repeat n-params
290          for offset from 0 by +gvalue-size+
291          do (gvalue-unset (pointer+ params offset)))
292         (deallocate-memory params)))))
293
294
295 (defmacro define-signal-handler (name ((object class) &rest args) &body body)
296   (let* ((info (signal-query (ensure-signal-id-from-type name class)))
297          (types (cons class (signal-param-types info)))
298          (n-params (1+ (slot-value info 'n-params)))
299          (return-type (type-from-number (slot-value info 'return-type)))
300          (vars (loop
301                 for arg in args
302                 until (eq arg '&rest)
303                 collect arg))
304          (rest (cadr (member '&rest args)))
305          (next (make-symbol "ARGS"))
306          (default (make-symbol "DEFAULT")))
307
308     `(progn
309        (signal-override-class-closure ',name ',class 
310         #'(lambda (,object ,@args)
311             (let ((,default (list* ,object ,@vars ,rest)))
312               (flet ((call-next-handler (&rest ,next)
313                        (%call-next-handler 
314                         ,n-params ',types (or ,next ,default) ',return-type)))
315               ,@body))))
316        ',name)))
317
318
319 (defbinding %signal-stop-emission () nil
320   (instance ginstance)
321   (signal-id unsigned-int)
322   (detail quark))
323
324 (defvar *signal-stop-emission* nil)
325 (declaim (special *signal-stop-emission*))
326
327 (defun signal-stop-emission ()
328   (if *signal-stop-emission*
329       (funcall *signal-stop-emission*)
330     (error "Not inside a signal handler")))
331
332
333 (defbinding signal-add-emission-hook (type signal function &key (detail 0))
334     unsigned-long
335   ((ensure-signal-id-from-type signal type) unsigned-int)
336   (detail quark)
337   (emission-hook-marshal callback)
338   ((register-callback-function function) unsigned-int)
339   (user-data-destroy-callback callback))
340
341 (defbinding signal-remove-emission-hook (type signal hook-id) nil
342   ((ensure-signal-id-from-type signal type) unsigned-int)
343   (hook-id unsigned-long))
344
345
346 (defbinding (signal-has-handler-pending-p "g_signal_has_handler_pending")
347     (instance signal-id &key detail blocked) boolean
348   (instance ginstance)
349   ((ensure-signal-id signal-id instance) unsigned-int)
350   ((or detail 0) quark)
351   (blocked boolean))
352     
353 (defbinding %signal-connect-closure-by-id () unsigned-long
354   (instance ginstance)
355   (signal-id unsigned-int)
356   (detail quark)
357   (closure pointer)
358   (after boolean))
359
360 (defbinding signal-handler-block () nil
361   (instance ginstance)
362   (handler-id unsigned-long))
363
364 (defbinding signal-handler-unblock () nil
365   (instance ginstance)
366   (handler-id unsigned-long))
367
368 ;; Internal
369 (defbinding signal-handler-find () unsigned-long
370   (instance gobject)
371   (mask signal-match-type)
372   (signal-id unsigned-int)
373   (detail quark)
374   (closure (or null pointer))
375   (func (or null pointer))
376   (data pointer-data))
377
378 (defbinding signal-handler-disconnect () nil
379   (instance ginstance)
380   (handler-id unsigned-long))
381
382 (defbinding signal-handler-is-connected-p () boolean
383   (instance ginstance)
384   (handler-id unsigned-long))
385
386 (defbinding (closure-new "g_cclosure_new") () gclosure
387   ((make-pointer #xFFFFFFFF) pointer)
388   (callback-id unsigned-int) 
389   (destroy-notify callback))
390
391 (defbinding closure-set-meta-marshal () nil
392   (gclosure gclosure)
393   (callback-id unsigned-int)
394   (callback callback))
395
396 (defun callback-closure-new (callback-id callback destroy-notify)
397   (let ((gclosure (closure-new callback-id destroy-notify)))
398     (closure-set-meta-marshal gclosure callback-id callback)
399     gclosure))
400
401 (defun make-callback-closure (function &optional (marshaller signal-handler-marshal))
402   (let ((callback-id (register-callback-function function)))
403     (values
404      (callback-closure-new callback-id marshaller user-data-destroy-callback)
405      callback-id)))
406
407 (defgeneric compute-signal-function (gobject signal function object args))
408
409 (defmethod compute-signal-function ((gobject gobject) signal function object args)
410   (declare (ignore signal))
411   (cond
412    ((or (eq object t) (eq object gobject))
413     (if args 
414         #'(lambda (&rest emission-args) 
415             (apply function (nconc emission-args args)))
416       function))
417    (object
418     (if args 
419         #'(lambda (&rest emission-args) 
420             (apply function object (nconc (rest emission-args) args)))
421       #'(lambda (&rest emission-args) 
422           (apply function object (rest emission-args)))))
423    (args 
424     #'(lambda (&rest emission-args) 
425         (apply function (nconc (rest emission-args) args))))
426    (t
427     #'(lambda (&rest emission-args) 
428         (apply function (rest emission-args))))))
429
430 (defgeneric compute-signal-id (gobject signal))
431
432 (defmethod compute-signal-id ((gobject gobject) signal)
433   (ensure-signal-id signal gobject))
434
435
436 (defgeneric signal-connect (gobject signal function &key detail after object remove args))
437
438 (defmethod signal-connect :around ((gobject gobject) signal function &rest args)
439   (declare (ignore gobject signal args))
440   (when function
441     (call-next-method)))
442
443
444 (defmethod signal-connect ((gobject gobject) signal function
445                            &key detail after object remove args)
446 "Connects a callback function to a signal for a particular object. If
447 :OBJECT is T, the object connected to is passed as the first argument
448 to the callback function, or if :OBJECT is any other non NIL value, it
449 is passed as the first argument instead. If :AFTER is non NIL, the
450 handler will be called after the default handler for the signal. If
451 :REMOVE is non NIL, the handler will be removed after beeing invoked
452 once. ARGS is a list of additional arguments passed to the callback
453 function."
454 (let* ((signal-id (compute-signal-id gobject signal))
455        (detail-quark (if detail (quark-intern detail) 0))
456        (signal-stop-emission
457         #'(lambda ()
458             (%signal-stop-emission gobject signal-id detail-quark)))
459        (callback (compute-signal-function gobject signal function object args))
460        (wrapper #'(lambda (&rest args)
461                     (let ((*signal-stop-emission* signal-stop-emission))
462                       (apply callback args)))))
463       (multiple-value-bind (closure-id callback-id)
464           (make-callback-closure wrapper signal-handler-marshal)
465         (let ((handler-id (%signal-connect-closure-by-id 
466                            gobject signal-id detail-quark closure-id after)))
467           (when remove
468             (update-user-data callback-id
469              #'(lambda (&rest args)
470                  (unwind-protect
471                      (let ((*signal-stop-emission* signal-stop-emission))
472                        (apply callback args))
473                    (when (signal-handler-is-connected-p gobject handler-id)
474                      (signal-handler-disconnect gobject handler-id))))))
475           handler-id))))
476
477
478 ;;;; Signal emission
479
480 (defbinding %signal-emitv () nil
481   (gvalues pointer)
482   (signal-id unsigned-int)
483   (detail quark)
484   (return-value gvalue))
485
486 (defvar *signal-emit-functions* (make-hash-table))
487
488 (defun create-signal-emit-function (signal-id)
489   (let ((info (signal-query signal-id)))
490     (let* ((type (type-from-number (slot-value info 'type)))
491            (param-types (cons type (signal-param-types info)))
492            (return-type (type-from-number (slot-value info 'return-type)))
493            (n-params (1+ (slot-value info 'n-params)))
494            (params (allocate-memory (* n-params +gvalue-size+))))
495       #'(lambda (detail object &rest args)
496           (unless (= (length args) (1- n-params))
497             (error "Invalid number of arguments in emmision of signal ~A: ~A" signal-id (length args)))
498           (unwind-protect
499               (loop
500                for arg in (cons object args)
501                for type in param-types
502                as tmp = params then (pointer+ tmp +gvalue-size+)
503                do (gvalue-init tmp type arg)          
504                finally 
505                (if return-type
506                    (return 
507                     (with-gvalue (return-value)
508                       (%signal-emitv params signal-id detail return-value)))
509                  (%signal-emitv params signal-id detail (make-pointer 0))))
510             (loop
511              repeat n-params
512              as tmp = params then (pointer+ tmp +gvalue-size+)
513              while (gvalue-p tmp)
514              do (gvalue-unset tmp)))))))
515
516 (defun signal-emit-with-detail (object signal detail &rest args)
517   (let* ((signal-id (ensure-signal-id signal object))
518          (function (or 
519                     (gethash signal-id *signal-emit-functions*)
520                     (setf 
521                      (gethash signal-id *signal-emit-functions*)
522                      (create-signal-emit-function signal-id)))))
523     (apply function detail object args)))
524
525 (defun signal-emit (object signal &rest args)
526   (apply #'signal-emit-with-detail object signal 0 args))
527
528
529 ;;;; Signal registration
530
531 (defbinding %signal-newv (name itype flags return-type param-types) 
532     unsigned-int
533   ((signal-name-to-string name) string)
534   (itype gtype)
535   (flags signal-flags)
536   (nil null) ; class closure
537   (nil null) ; accumulator
538   (nil null) ; accumulator data
539   (nil null) ; c marshaller
540   (return-type gtype)
541   ((length param-types) unsigned-int)
542   (param-types (vector gtype)))
543
544 (defun signal-new (name itype flags return-type param-types)
545   (when (zerop (signal-lookup name itype))
546     (%signal-newv name itype flags return-type param-types)))
547
548 ;;;; Convenient macros
549
550 (defmacro define-callback-marshal (name return-type args &key (callback-id :last))
551   (let* ((ignore ())
552          (params ())
553          (names (loop 
554                  for arg in args 
555                  collect (if (or 
556                               (eq arg :ignore) 
557                               (and (consp arg) (eq (first arg) :ignore)))
558                              (let ((name (gensym "IGNORE")))
559                                (push name ignore)
560                                name)
561                            (let ((name (if (atom arg)
562                                            (gensym (string arg))
563                                          (first arg))))
564                              (push name params)
565                              name))))
566          (types (loop 
567                  for arg in args 
568                  collect (cond
569                           ((eq arg :ignore) 'pointer)
570                           ((atom arg) arg)
571                           (t (second arg))))))
572     `(define-callback ,name ,return-type 
573        ,(ecase callback-id
574           (:first `((callback-id pointer-data) ,@(mapcar #'list names types)))
575           (:last `(,@(mapcar #'list names types) (callback-id pointer-data))))
576        (declare (ignore ,@ignore))
577        (invoke-callback callback-id ',return-type ,@(nreverse params)))))
578
579 (defmacro with-callback-function ((id function) &body body)
580   `(let ((,id (register-callback-function ,function)))
581     (unwind-protect
582          (progn ,@body)
583       (destroy-user-data ,id))))