chiark / gitweb /
Fix for CLISP
[clg] / gffi / interface.lisp
1 ;; Common Lisp bindings for GTK+ v2.x
2 ;; Copyright 1999-2006 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: interface.lisp,v 1.8 2007-11-29 18:37:14 espen Exp $
24
25 (in-package "GFFI")
26
27
28 ;;;; Foreign function call interface
29
30 (defvar *package-prefix* nil)
31
32 (defun set-package-prefix (prefix &optional (package *package*))
33   (let ((package (find-package package)))
34     (setq *package-prefix* (delete package *package-prefix* :key #'car))
35     (push (cons package prefix) *package-prefix*))
36   prefix)
37
38 (defun package-prefix (&optional (package *package*))
39   (let ((package (find-package package)))
40     (or
41      (cdr (assoc package *package-prefix*))
42      (substitute #\_ #\- (string-downcase (package-name package))))))
43
44 (defun find-prefix-package (prefix)
45   (or
46    (car (rassoc (string-downcase prefix) *package-prefix* :test #'string=))
47    (find-package (string-upcase prefix))))
48
49 (defmacro use-prefix (prefix &optional (package *package*))
50   `(eval-when (:compile-toplevel :load-toplevel :execute)
51      (set-package-prefix ,prefix ,package)))
52
53
54 (defun default-alien-fname (lisp-name)
55   (let* ((name (substitute #\_ #\- (string-downcase lisp-name)))
56          (start (position-if-not #'(lambda (char) (char= char #\%)) name))
57          (end (if (string= "_p" name :start2 (- (length name) 2))
58                   (- (length name) 2)
59                 (length name)))
60          (stripped-name (subseq name start end))
61          (prefix (package-prefix *package*)))
62     (if (or (not prefix) (string= prefix ""))
63         stripped-name
64       (format nil "~A_~A" prefix stripped-name))))
65
66 (defun default-alien-type-name (type-name)
67   (let ((prefix (package-prefix *package*)))
68     (apply
69      #'concatenate
70      'string
71      (mapcar
72       #'string-capitalize    
73       (cons prefix (split-string (symbol-name type-name) :delimiter #\-))))))
74
75 (defun default-type-name (alien-name)
76   (let ((parts
77          (mapcar
78           #'string-upcase
79           (split-string-if alien-name #'upper-case-p))))
80     (intern
81      (concatenate-strings (rest parts) #\-)
82      (find-prefix-package (first parts)))))
83
84
85 (defun in-arg-p (style)
86   (find style '(:in :in/out :in/return :in-out :return)))
87
88 (defun out-arg-p (style)
89   (find style '(:out :in/out :in-out)))
90
91 (defun return-arg-p (style)
92   (find style '(:in/return :return)))
93
94 (defmacro defbinding (name lambda-list return-type &rest args)
95   (multiple-value-bind (lisp-name c-name)
96       (if (atom name)
97           (values name (default-alien-fname name))
98         (values-list name))
99                        
100     (let* ((lambda-list-supplied-p lambda-list)
101            (lambda-list (unless (equal lambda-list '(nil)) lambda-list))
102            (arg-types ())
103            (aux-bindings ())
104            (doc-string (when (stringp (first args)) (pop args)))
105            (parsed-args          
106             (mapcar 
107              #'(lambda (arg)
108                  (destructuring-bind 
109                      (expr type &optional (style :in) (out-type type)) 
110                      (if (atom arg) 
111                          (list arg arg)
112                        arg)
113                    (cond
114                     ((find style '(:in-out :return))
115                      (warn "Deprecated argument style: ~S" style))
116                     ((not (find style '(:in :out :in/out :in/return)))
117                      (error "Bogus argument style: ~S" style)))
118                    (when (and 
119                           (not lambda-list-supplied-p) 
120                           (namep expr) (in-arg-p style)
121                           (not (find expr lambda-list)))
122                      (push expr lambda-list)
123                      (push type arg-types))
124                    (let ((aux (unless (or (not (in-arg-p style)) (namep expr))
125                                 (gensym))))
126                      (when aux
127                        (push (list aux expr) aux-bindings))
128                      (list 
129                       (cond 
130                        ((and (namep expr) (not (in-arg-p style))) expr)
131                        ((namep expr)                    
132                         #-clisp(make-symbol (string expr))
133                         ;; The above used to work in CLISP, but I'm
134                         ;; not sure exactly at which version it
135                         ;; broke. The following could potentially
136                         ;; cause variable capturing
137                         #+clisp(intern (format nil "~A-~A" (string expr) (gensym))))
138                        (#-clisp(gensym)
139                         #+clisp(intern (string (gensym)))))
140                       (or aux expr) type style out-type))))
141              args)))
142   
143       (%defbinding c-name lisp-name
144        (if lambda-list-supplied-p lambda-list (nreverse lambda-list))
145        (not lambda-list-supplied-p) (nreverse arg-types)
146        aux-bindings return-type doc-string parsed-args))))
147
148
149 #+(or cmu sbcl)
150 (defun foreign-funcall (cname args return-type)
151   (let ((fparams (loop
152                   for (var expr type style out-type) in args
153                   collect (if (out-arg-p style)
154                               `(addr ,var)
155                             var)))
156         (ftypes (loop
157                  for (var expr type style out-type) in args
158                  collect (if (out-arg-p style)
159                              `(* ,(alien-type out-type))
160                            (alien-type out-type))))
161         (fname (make-symbol cname)))
162     `(with-alien ((,fname (function ,(alien-type return-type) ,@ftypes) :extern ,cname))
163       (alien-funcall ,fname ,@fparams))))
164
165 #+clisp
166 (defun foreign-funcall (cname args return-type)
167   (let* ((fparams (loop
168                    for (var expr type style out-type) in args
169                    collect (if (out-arg-p style)
170                                `(ffi:c-var-address ,var)
171                              var)))
172          (fargs (loop
173                  for (var expr type style out-type) in args
174                  collect (list var (if (out-arg-p style)
175                                        'ffi:c-pointer
176                                      (alien-type out-type)))))
177          (c-function `(ffi:c-function 
178                        (:arguments ,@fargs)
179                        (:return-type ,(alien-type return-type))
180                        (:language :stdc))))
181     `(funcall
182       (load-time-value
183        (ffi::foreign-library-function 
184         ,cname (ffi::foreign-library :default) #?(clisp>= 2 40)nil
185         nil (ffi:parse-c-type ',c-function)))
186       ,@fparams)))
187
188
189 ;; TODO: check if in and out types (if different) translates to same
190 ;; alien type
191 (defun %defbinding (cname lisp-name lambda-list declare-p arg-types aux-bindings return-type doc args)
192   (let ((out (loop
193               for (var expr type style out-type) in args
194               when (or (out-arg-p style) (return-arg-p style))
195               collect (from-alien-form out-type var)))
196         (fcall (from-alien-form return-type 
197                 (foreign-funcall cname args return-type))))
198
199     (labels ((create-wrapper (args body)
200                (if args
201                    (destructuring-bind (var expr type style out-type) (first args)
202                      (declare (ignore out-type))
203                      (alien-arg-wrapper type var expr style
204                       (create-wrapper (rest args) body)))
205                  body)))
206        `(progn
207           ,(when declare-p
208              `(declaim 
209                (ftype 
210                 (function 
211                  ,(mapcar #'argument-type arg-types)
212                  (values 
213                   ,@(when return-type (list (return-type return-type)))
214                   ,@(loop
215                      for (var expr type style out-type) in args
216                      when (out-arg-p style)
217                      collect (return-type out-type)
218                      when (return-arg-p style)
219                      collect (return-type type)))))))
220           (defun ,lisp-name ,lambda-list
221           ,doc
222           (let ,aux-bindings
223             ,(if return-type
224                  (create-wrapper args `(values ,fcall ,@out))
225                (create-wrapper args `(progn ,fcall (values ,@out))))))))))
226
227
228
229 ;;;; Dynamic (runtime) bindings
230
231 (defun mkbinding (name return-type &rest arg-types)
232   #+cmu(declare (optimize (inhibit-warnings 3)))
233   #+sbcl(declare (muffle-conditions compiler-note))
234   (let* ((c-function
235           #+(or cmu sbcl)
236           `(function ,@(mapcar #'alien-type (cons return-type arg-types)))
237           #+clisp
238           `(ffi:c-function 
239             (:arguments ,@(mapcar 
240                            #'(lambda (type)
241                                (list (gensym) (alien-type type)))
242                            arg-types)) 
243             (:return-type ,(alien-type return-type))
244             (:language :stdc)))
245          (foreign
246           #+(or cmu sbcl)
247           (handler-bind (#+sbcl(compiler-note #'(lambda (condition)
248                                                   (declare (ignore condition))
249                                                   (muffle-warning))))
250             (%heap-alien
251              (make-heap-alien-info
252               :type (parse-alien-type c-function #+sbcl nil)
253               :sap-form (let ((address (foreign-symbol-address name)))
254                           (etypecase address
255                             (integer (int-sap address))
256                             (system-area-pointer address))))))
257           #+clisp
258           (ffi::foreign-library-function name 
259            (ffi::foreign-library :default) #?(clisp>= 2 40)nil
260            nil (ffi:parse-c-type c-function)))
261          (return-value-translator (from-alien-function return-type)))
262     (multiple-value-bind (arg-translators cleanup-funcs)
263         (let ((translator/cleanup-pairs
264                (mapcar 
265                 #'(lambda (type)
266                     (multiple-value-list (to-alien-function type)))
267                 arg-types)))
268           (values 
269            (mapcar #'first translator/cleanup-pairs)
270            (mapcar #'second translator/cleanup-pairs)))
271       #'(lambda (&rest args)
272           (let ((translated-args (mapcar #'funcall arg-translators args)))
273             (prog1
274                 (funcall return-value-translator 
275                  #+(or cmu sbcl)(apply #'alien-funcall foreign translated-args)
276                  #+clisp(apply foreign translated-args))
277               (mapc 
278                #'(lambda (cleanup arg translated-arg)
279                    (when cleanup
280                      (funcall cleanup arg translated-arg)))
281                cleanup-funcs args translated-args)))))))
282
283
284
285 ;;;; C Callbacks
286
287 (defun callback-body (args return-type body)
288   (labels ((create-wrappers (args body)
289              (if args
290                  (destructuring-bind (var type) (first args)
291                    (callback-wrapper type var var
292                     (create-wrappers (rest args) body)))
293                body))
294            (create-body (args body)
295              (to-alien-form return-type 
296               (create-wrappers args `(progn ,@body)))))
297     (if (and (consp (first body)) (eq (caar body) 'declare))
298         (let ((ignored (loop
299                         for declaration in (cdar body)
300                         when (eq (first declaration) 'ignore)
301                         nconc (rest declaration))))
302           `(,(first body)
303             ,(create-body 
304               (remove-if #'(lambda (arg)
305                              (find (first arg) ignored))
306                          args)
307               (rest body))))
308       (list (create-body args body)))))
309
310
311 #+(or cmu sbcl)
312 (defmacro define-callback (name return-type args &body body)
313   (let ((define-callback 
314           #+cmu'alien:def-callback                    
315           #+(and sbcl alien-callbacks)'sb-alien::define-alien-callback
316           #+(and sbcl (not alien-callbacks))'sb-alien:define-alien-function)
317         (args (mapcar #'(lambda (arg)
318                           (if (atom arg) (list arg arg) arg))
319                       args)))
320     `(progn
321        #+cmu(defparameter ,name nil)
322        (,define-callback ,name 
323            #+(and sbcl alien-callbacks) ,(alien-type return-type) 
324            (#+(or cmu (and sbcl (not alien-callbacks))),(alien-type return-type)
325             ,@(loop
326                for (name type) in args
327                collect `(,name ,(alien-type type))))
328          ,@(callback-body args return-type body)))))
329
330 #+(or cmu sbcl)    
331 (defun callback-address (callback)
332   #+cmu(alien::callback-trampoline callback)
333   #+(and sbcl (not alien-callbacks))(sb-alien:alien-function-sap callback)
334   #+(and sbcl alien-callbacks)(sb-alien:alien-sap callback))
335
336 #+sbcl
337 (deftype callback () 
338   #-alien-callbacks'sb-alien:alien-function
339   #+alien-callbacks'sb-alien:alien)
340
341
342 ;;; The callback code for CLISP is based on code from CFFI
343 ;;; Copyright (C) 2005, James Bielman  <jamesjb@jamesjb.com>
344 ;;;           (C) 2005, Joerg Hoehle  <hoehle@users.sourceforge.net>
345
346
347 ;;; *CALLBACKS* contains the callbacks defined by the %DEFCALLBACK
348 ;;; macro.  The symbol naming the callback is the key, and the value
349 ;;; is a list containing a Lisp function, the parsed CLISP FFI type of
350 ;;; the callback, and a saved pointer that should not persist across
351 ;;; saved images.
352 #+clisp
353 (progn
354   (defvar *callbacks* (make-hash-table))
355
356   ;;; Return a CLISP FFI function type for a CFFI callback function
357   ;;; given a return type and list of argument names and types.
358   (eval-when (:compile-toplevel :load-toplevel :execute)
359     (defun callback-type (return-type arg-names arg-types)
360       (ffi:parse-c-type
361        `(ffi:c-function
362          (:arguments ,@(mapcar (lambda (sym type)
363                                  (list sym (alien-type type)))
364                                arg-names arg-types))
365          (:return-type ,(alien-type return-type))
366          (:language :stdc)))))
367   
368   ;;; Register and create a callback function.
369   (defun register-callback (name function parsed-type)
370     (setf (gethash name *callbacks*)
371           (list function parsed-type
372                 (ffi:with-foreign-object (ptr 'ffi:c-pointer)
373                  ;; Create callback by converting Lisp function to foreign
374                  (setf (ffi:memory-as ptr parsed-type) function)
375                  (ffi:foreign-value ptr)))))
376
377   ;;; Restore all saved callback pointers when restarting the Lisp
378   ;;; image.  This is pushed onto CUSTOM:*INIT-HOOKS*.
379   ;;; Needs clisp > 2.35, bugfix 2005-09-29
380   (defun restore-callback-pointers ()
381     (maphash
382      (lambda (name list)
383        (register-callback name (first list) (second list)))
384      *callbacks*))
385
386   ;;; Add RESTORE-CALLBACK-POINTERS to the lists of functions to run
387   ;;; when an image is restarted.
388   (eval-when (:load-toplevel :execute)
389     (pushnew 'restore-callback-pointers custom:*init-hooks*))
390
391   ;;; Define a callback function NAME to run BODY with arguments
392   ;;; ARG-NAMES translated according to ARG-TYPES and the return type
393   ;;; translated according to RETTYPE.  Obtain a pointer that can be
394   ;;; passed to C code for this callback by calling %CALLBACK.
395   (defmacro define-callback (name return-type args &body body)
396     (let* ((args (mapcar #'(lambda (arg)
397                              (if (atom arg) (list arg arg) arg))
398                          args))
399            (arg-names (mapcar #'first args))
400            (arg-types  (mapcar #'second args)))
401       `(progn
402          (defvar ,name ',name)
403          (register-callback ',name 
404           (lambda ,arg-names ,@(callback-body args return-type body))
405           ,(callback-type return-type arg-names arg-types)))))
406
407   ;;; Look up the name of a callback and return a pointer that can be
408   ;;; passed to a C function.  Signals an error if no callback is
409   ;;; defined called NAME.
410   (defun callback-address (name)
411     (multiple-value-bind (list winp) (gethash name *callbacks*)
412       (unless winp
413         (error "Undefined callback: ~S" name))
414       (third list)))
415
416   (deftype callback () 'symbol))
417
418
419
420 ;;;; Type expansion
421
422 (defun type-expand-1 (form)
423   #+(or cmu sbcl)
424   (let ((def (cond ((symbolp form)
425                     #+cmu(kernel::info type expander form)
426                     #+sbcl(sb-impl::info :type :expander form))
427                    ((and (consp form) (symbolp (car form)))
428                     #+cmu(kernel::info type expander (car form))
429                     #+sbcl(sb-impl::info :type :expander (car form)))
430                    (t nil))))
431     (if def
432         (values (funcall def (if (consp form) form (list form))) t)
433       (values form nil)))
434   #+clisp(ext:type-expand form t))
435
436 (defun type-expand-to (type form)
437   (labels ((expand (form0)
438              (if (eq (first (mklist form0)) type)
439                  form0
440                (multiple-value-bind (expanded-form expanded-p)
441                    (type-expand-1 form0)
442                  (if expanded-p
443                      (expand expanded-form)
444                    (error "~A can not be expanded to ~A" form type))))))
445     (expand form)))
446
447
448
449 ;;;; Type methods
450
451 (defun find-type-method (name type-spec &optional (error-p t))
452   (let ((type-methods (get name 'type-methods))
453         (specifier (if (atom type-spec)
454                        type-spec
455                      (first type-spec))))
456     (or
457      (gethash specifier type-methods)
458      (when error-p 
459        (error 
460         "No explicit type method for ~A when call width type specifier ~A found"
461         name type-spec)))))
462
463 (defun find-next-type-method (name type-spec &optional (error-p t))
464   (let ((type-methods (get name 'type-methods)))
465     (labels ((search-method-in-cpl-order (classes)
466                (when classes
467                  (or 
468                   (gethash (class-name (first classes)) type-methods)
469                   (search-method-in-cpl-order (rest classes)))))
470              (lookup-method (type-spec)
471                (if (and (symbolp type-spec) (find-class type-spec nil))
472                    (let ((class (find-class type-spec)))
473                      #?(or (sbcl>= 0 9 15) (featurep :clisp))
474                      (unless (class-finalized-p class)
475                        (finalize-inheritance class))
476                      (search-method-in-cpl-order 
477                       (rest (class-precedence-list class))))
478                  (multiple-value-bind (expanded-type expanded-p) 
479                       (type-expand-1 type-spec)
480                    (when expanded-p
481                      (or 
482                       (let ((specifier (etypecase expanded-type
483                                          (symbol expanded-type)
484                                          (list (first expanded-type)))))
485                         (gethash specifier type-methods))
486                       (lookup-method expanded-type))))))
487              (search-built-in-type-hierarchy (sub-tree)
488                (when (subtypep type-spec (first sub-tree))
489                  (or
490                   (search-nodes (cddr sub-tree))
491                   (second sub-tree))))
492              (search-nodes (nodes)
493                (loop
494                 for node in nodes
495                 as method = (search-built-in-type-hierarchy node)
496                 until method
497                 finally (return method))))
498       (or 
499        (lookup-method type-spec)
500        ;; This is to handle unexpandable types whichs doesn't name a
501        ;; class.  It may cause infinite loops with illegal
502        ;; call-next-method calls
503        (unless (or 
504                 (null type-spec)
505                 (and (symbolp type-spec) (find-class type-spec nil)))
506          (search-nodes (get name 'built-in-type-hierarchy)))
507        (when error-p
508          (error "No next type method ~A for type specifier ~A"
509           name type-spec))))))
510
511 (defun find-applicable-type-method (name type-spec &optional (error-p t))
512   (or
513    (find-type-method name type-spec nil)
514    (find-next-type-method name type-spec nil)
515    (when error-p 
516      (error 
517       "No applicable type method for ~A when call width type specifier ~A"
518       name type-spec))))
519
520
521 (defun insert-type-in-hierarchy (specifier function nodes)
522   (cond
523    ((let ((node (find specifier nodes :key #'first)))
524       (when node
525         (setf (second node) function)
526         nodes)))
527    ((let ((node
528            (find-if 
529             #'(lambda (node)
530                 (subtypep specifier (first node)))
531             nodes)))
532       (when node
533         (setf (cddr node) 
534               (insert-type-in-hierarchy specifier function (cddr node)))
535         nodes)))
536    ((let ((sub-nodes (remove-if-not 
537                       #'(lambda (node)
538                           (subtypep (first node) specifier))
539                       nodes)))
540       (cons
541        (list* specifier function sub-nodes)
542        (nset-difference nodes sub-nodes))))))
543
544 (defun add-type-method (name specifier function)
545   (setf (gethash specifier (get name 'type-methods)) function)
546   (when (typep (find-class specifier nil) 'built-in-class)
547     (setf (get name 'built-in-type-hierarchy)
548      (insert-type-in-hierarchy specifier function 
549       (get name 'built-in-type-hierarchy)))))
550   
551
552 (defmacro define-type-generic (name lambda-list &optional documentation)
553   (let ((type-spec (first lambda-list)))
554     (if (or 
555          (not lambda-list) 
556          (find type-spec '(&optional &key &rest &allow-other-keys)))
557         (error "A type generic needs at least one required argument")
558       `(progn 
559          (unless (get ',name 'type-methods)
560            (setf (get ',name 'type-methods) (make-hash-table))   
561            (setf (get ',name 'built-in-type-hierarchy) ()))
562          ,(if (intersection '(&optional &key &rest &allow-other-keys) lambda-list)
563               (let ((args (make-symbol "ARGS")))
564                 `(defun ,name (,type-spec &rest ,args)
565                    ,documentation
566                    (apply
567                     (find-applicable-type-method ',name ,type-spec)
568                     ,type-spec ,args)))
569             `(defun ,name ,lambda-list
570                ,documentation
571                (funcall 
572                 (find-applicable-type-method ',name ,type-spec)
573                 ,@lambda-list)))))))
574
575
576 (defmacro define-type-method (name lambda-list &body body)
577   (let ((specifier (cadar lambda-list)) 
578         (args (make-symbol "ARGS")))
579     `(progn
580        (add-type-method ',name ',specifier 
581         #'(lambda (&rest ,args)
582             (flet ((call-next-method (&rest args)
583                      (let ((next-method (find-next-type-method ',name ',specifier)))
584                        (apply next-method (or args ,args)))))
585               (destructuring-bind (,(caar lambda-list) ,@(rest lambda-list)) ,args
586                 ,@body))))
587        ',name)))
588
589
590 ;;; Rules for auto-exporting symbols
591
592 (defexport defbinding (name &rest args)
593   (declare (ignore args))
594   (if (symbolp name)
595       name
596     (first name)))
597
598 (defexport define-type-generic (name &rest args)
599   (declare (ignore args))
600   name)