chiark / gitweb /
Removed comment about setting up logical pathname translation
[clg] / glib / glib.lisp
1 ;; Common Lisp bindings for GTK+ 2.x
2 ;; Copyright 1999-2005 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: glib.lisp,v 1.42 2007-10-17 14:30:41 espen Exp $
24
25
26 (in-package "GLIB")
27
28 (use-prefix "g")
29
30 #-sb-thread
31 (progn
32   (defun make-mutex ()
33     nil)
34   
35   (defmacro with-mutex ((mutex) &body body)
36     (declare (ignore mutex))
37     `(progn ,@body)))
38
39
40 ;;;; Memory management
41
42 (defbinding (%allocate-memory "g_malloc0") () pointer
43   (size unsigned-long))
44
45 (defbinding (%deallocate-memory "g_free") () nil
46   (address pointer))
47
48 ;; (setf
49 ;;  (symbol-function 'allocate-memory) #'%allocate-memory
50 ;;  (symbol-function 'deallocate-memory) #'%deallocate-memory)
51
52 (setf *memory-allocator* #'%allocate-memory)
53 (setf *memory-deallocator* #'%deallocate-memory)
54
55 (defbinding (reallocate-memory "g_realloc") () pointer
56   (address pointer)
57   (size unsigned-long))
58
59 (deftype gsize () 'unsigned-int)
60
61 (defbinding (slice-alloc "g_slice_alloc0") () pointer
62   (block-size gsize))
63
64 ;;;; User data is a mechanism to store references to lisp objects in
65 ;;;; foreign code
66
67 (defvar *user-data-lock* (make-mutex))
68 (defvar *user-data* (make-hash-table))
69 (defvar *user-data-next-id* 1)
70
71 (defun register-user-data (object &optional destroy-function)
72   (check-type destroy-function (or null symbol function))
73   (with-mutex (*user-data-lock*)
74     (setf
75      (gethash *user-data-next-id* *user-data*)
76      (cons object destroy-function))
77     (1- (incf *user-data-next-id*))))
78
79 (defun find-user-data (id)
80   (check-type id fixnum)
81   (with-mutex (*user-data-lock*)
82     (multiple-value-bind (user-data p) (gethash id *user-data*)
83       (values (car user-data) p))))
84
85 (defun user-data-exists-p (id)
86   (nth-value 1 (find-user-data id)))
87
88 (defun update-user-data (id object)
89   (check-type id fixnum)
90   (with-mutex (*user-data-lock*)
91     (multiple-value-bind (user-data exists-p) (gethash id *user-data*)
92       (cond
93        ((not exists-p) (error "User data id ~A does not exist" id))
94        (t 
95         (when (cdr user-data)
96           (funcall (cdr user-data) (car user-data)))
97         (setf (car user-data) object))))))
98
99 (defun destroy-user-data (id)
100   (check-type id fixnum)
101   (with-mutex (*user-data-lock*)
102     (multiple-value-bind (user-data exists-p) (gethash id *user-data*)
103       (cond
104 ;       ((not exists-p) (error "User data id ~A does not exist" id))
105        (t
106         (when (cdr user-data)
107           (funcall (cdr user-data) (car user-data)))
108         (remhash id *user-data*))))))
109
110 (defun take-user-data (id)
111   (check-type id fixnum)
112   (multiple-value-bind (user-data exists-p) (gethash id *user-data*)
113     (cond
114       ((not exists-p) (error "User data id ~A does not exist" id))
115       (t 
116         (when (cdr user-data)
117           (funcall (cdr user-data) (car user-data)))
118         (remhash id *user-data*)
119         (car user-data)))))
120
121 (defmacro with-user-data ((var object) &body body)
122   `(let ((,var (register-user-data ,object)))
123      (unwind-protect
124           ,@body
125        (destroy-user-data ,var))))
126
127
128 (deftype user-data-id () 'pointer-data)
129
130
131 ;;;; Quarks
132
133 (deftype quark () 'unsigned)
134
135 (defbinding %quark-from-string () quark
136   (string string))
137
138 (defun quark-intern (object)
139   (etypecase object
140     (quark object)
141     (string (%quark-from-string object))
142     (symbol (%quark-from-string (format nil "clg-~A:~A" 
143                                  (package-name (symbol-package object)) 
144                                  object)))))
145
146 (defbinding quark-to-string () (static string)
147   (quark quark))
148
149
150 ;;;; Linked list (GList)
151
152 (deftype glist (type) 
153   `(or null (cons ,type list)))
154
155 (defbinding (%glist-append "g_list_append") () pointer
156   (glist (or null pointer))
157   (nil null))
158
159 (defun make-glist (element-type list &optional temp-p)
160   (let ((writer (if (functionp element-type)
161                     element-type
162                   (writer-function element-type :temp temp-p))))
163     (loop
164      for element in list
165      as glist = (%glist-append nil) then (%glist-append glist)
166      do (funcall writer element glist)
167      finally (return glist))))
168
169 (defun glist-next (glist)
170   (unless (null-pointer-p glist)
171     (ref-pointer glist #.(size-of 'pointer))))
172   
173 ;; Also used for gslists
174 (defun map-glist (seqtype function glist element-type &optional (ref :read))
175   (let ((reader (if (functionp element-type)
176                     element-type
177                   (reader-function element-type :ref ref))))
178     (case seqtype 
179      ((nil)
180       (loop
181        as element = glist then (glist-next element)
182        until (null-pointer-p element)
183        do (funcall function (funcall reader element))))
184      (list
185       (loop
186        as element = glist then (glist-next element)
187        until (null-pointer-p element)
188        collect (funcall function (funcall reader element))))
189      (t
190       (coerce 
191        (loop
192         as element = glist then (glist-next element)
193         until (null-pointer-p element)
194         collect (funcall function (funcall reader element)))
195        seqtype)))))
196
197 (defbinding (glist-free "g_list_free") () nil
198   (glist pointer))
199
200 (defun destroy-glist (glist element-type &optional temp-p)
201   (let ((destroy (if (functionp element-type)
202                      element-type
203                    (destroy-function element-type :temp temp-p))))
204     (loop
205      as element = glist then (glist-next element)
206      until (null-pointer-p element)
207      do (funcall destroy element)))
208   (glist-free glist))
209
210 (define-type-method alien-type ((type glist))
211   (declare (ignore type))
212   (alien-type 'pointer))
213
214 (define-type-method argument-type ((type glist))
215   'list)
216
217 (define-type-method return-type ((type glist))
218   'list)
219
220 (define-type-method size-of ((type glist) &key inlined)
221   (assert-not-inlined type inlined)
222   (size-of 'pointer))
223
224 (define-type-method type-alignment ((type glist) &key inlined)
225   (assert-not-inlined type inlined)
226   (type-alignment 'pointer))
227
228 (define-type-method alien-arg-wrapper ((type glist) var list style form &optional copy-in-p)
229   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
230     (cond
231       ((and (in-arg-p style) (not (out-arg-p style)))
232        `(with-pointer (,var (make-glist ',element-type ,list ,(not copy-in-p)))
233           (unwind-protect
234               ,form
235             ,(unless copy-in-p
236                `(destroy-glist ,var ',element-type t)))))
237       ((and (in-arg-p style) (out-arg-p style))
238        (let ((glist (make-symbol "GLIST")))
239          `(with-pointer (,glist (make-glist ',element-type ,list ,(not copy-in-p)))
240             (with-pointer (,var ,glist)               
241               (unwind-protect
242                   ,form
243                 ,(unless copy-in-p
244                    `(destroy-glist ,glist ',element-type t)))))))
245       ((and (out-arg-p style) (not (in-arg-p style)))
246        `(with-pointer (,var)
247           ,form)))))
248
249 (define-type-method to-alien-form ((type glist) list &optional copy-p)
250   (declare (ignore copy-p))
251   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
252     `(make-glist ',element-type ,list)))
253
254 (define-type-method to-alien-function ((type glist) &optional copy-p)
255   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
256     (values
257      #'(lambda (list)
258          (make-glist element-type list (not copy-p)))
259      (unless copy-p
260        #'(lambda (list glist)
261            (declare (ignore list))
262            (destroy-glist glist element-type t))))))
263
264 (define-type-method from-alien-form ((type glist) form &key (ref :free))
265   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
266     `(let ((glist ,form))
267        (unwind-protect
268            (map-glist 'list #'identity glist ',element-type 
269             ,(ecase ref (:free :get) ((:static :temp) :peek) (:copy :read)))
270          ,(when (eq ref :free)
271             `(destroy-glist glist ',element-type))))))
272
273 (define-type-method from-alien-function ((type glist) &key (ref :free))
274   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
275     (ecase ref
276       (:free 
277        #'(lambda (glist)
278            (prog1
279                (map-glist 'list #'identity glist element-type :get)
280              (glist-free glist))))
281       (:copy
282        #'(lambda (glist)
283            (map-glist 'list #'identity glist element-type :read)))
284       ((:static :temp)
285        #'(lambda (glist)
286            (map-glist 'list #'identity glist element-type :peek))))))
287
288 (define-type-method writer-function ((type glist) &key temp inlined)
289   (assert-not-inlined type inlined)
290   (let ((element-type (second (type-expand-to 'glist type))))
291     #'(lambda (list location &optional (offset 0))
292         (setf 
293          (ref-pointer location offset)
294          (make-glist element-type list temp)))))
295
296 (define-type-method reader-function ((type glist) &key (ref :read) inlined)
297   (assert-not-inlined type inlined)
298   (let ((element-type (second (type-expand-to 'glist type))))
299     (ecase ref
300       ((:read :peek)
301        #'(lambda (location &optional (offset 0))
302            (unless (null-pointer-p (ref-pointer location offset))
303              (map-glist 'list #'identity (ref-pointer location offset) element-type ref))))
304       (:get
305        #'(lambda (location &optional (offset 0))
306            (unless (null-pointer-p (ref-pointer location offset))
307              (prog1
308                  (map-glist 'list #'identity (ref-pointer location offset) element-type :get)
309                (glist-free (ref-pointer location offset))
310                (setf (ref-pointer location offset) (make-pointer 0)))))))))
311
312 (define-type-method destroy-function ((type glist) &key temp inlined)
313   (assert-not-inlined type inlined)
314   (let ((element-type (second (type-expand-to 'glist type))))
315     #'(lambda (location &optional (offset 0))
316         (unless (null-pointer-p (ref-pointer location offset))
317           (destroy-glist (ref-pointer location offset) element-type temp)
318           (setf (ref-pointer location offset) (make-pointer 0))))))
319
320 (define-type-method copy-function ((type glist) &key inlined)
321   (assert-not-inlined type inlined)
322   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
323     (let ((copy-element (copy-function element-type)))
324       #'(lambda (from to &optional (offset 0))
325           (unless (null-pointer-p (ref-pointer from offset))
326             (loop
327              as from-list = (ref-pointer from offset) 
328                             then (glist-next from-list)
329              as to-list = (setf (ref-pointer to offset) (%glist-append nil)) 
330                           then (%glist-append to-list)
331              do (funcall copy-element from-list to-list)
332              while (glist-next from-lisT)))))))
333
334
335 ;;;; Single linked list (GSList)
336
337 (deftype gslist (type) `(or null (cons ,type list)))
338
339 (defbinding (%gslist-prepend "g_slist_prepend") () pointer
340   (gslist pointer)
341   (nil null))
342
343 (defbinding (%gslist-append "g_slist_append") () pointer
344   (glist (or null pointer))
345   (nil null))
346
347
348 (defun make-gslist (element-type list &optional temp-p)
349   (let ((writer (if (functionp element-type)
350                     element-type
351                   (writer-function element-type :temp temp-p))))
352     (loop
353      for element in (reverse list)
354      as gslist = (%gslist-prepend (make-pointer 0)) then (%gslist-prepend gslist)
355      do (funcall writer element gslist)
356      finally (return gslist))))
357
358 (defbinding (gslist-free "g_slist_free") () nil
359   (gslist pointer))
360
361 (defun destroy-gslist (gslist element-type &optional temp-p)
362   (loop
363    with destroy = (destroy-function element-type :temp temp-p)
364    as element = gslist then (glist-next element)
365    until (null-pointer-p element)
366    do (funcall destroy element 0))
367   (gslist-free gslist))
368
369 (define-type-method alien-type ((type gslist))
370   (declare (ignore type))
371   (alien-type 'pointer))
372
373 (define-type-method argument-type ((type gslist))
374   'list)
375
376 (define-type-method return-type ((type gslist))
377   'list)
378
379 (define-type-method size-of ((type gslist) &key inlined)
380   (assert-not-inlined type inlined)
381   (size-of 'pointer))
382
383 (define-type-method type-alignment ((type gslist) &key inlined)
384   (assert-not-inlined type inlined)
385   (type-alignment 'pointer))
386
387 (define-type-method alien-arg-wrapper ((type gslist) var list style form &optional copy-in-p)
388   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
389     (cond
390       ((and (in-arg-p style) (not (out-arg-p style)))
391        `(with-pointer (,var (make-gslist ',element-type ,list ,(not copy-in-p)))
392           (unwind-protect
393               ,form
394             ,(unless copy-in-p
395                `(destroy-gslist ,var ',element-type t)))))
396       ((and (in-arg-p style) (out-arg-p style))
397        (let ((gslist (make-symbol "GSLIST")))
398          `(with-pointer (,gslist (make-gslist ',element-type ,list ,(not copy-in-p)))
399             (with-pointer (,var ,gslist)                      
400               (unwind-protect
401                   ,form
402                 ,(unless copy-in-p
403                    `(destroy-gslist ,gslist ',element-type t)))))))
404       ((and (out-arg-p style) (not (in-arg-p style)))
405        `(with-pointer (,var)
406           ,form)))))
407
408 (define-type-method to-alien-form ((type gslist) list &optional copy-p)
409   (declare (ignore copy-p))
410   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
411     `(make-gslist ',element-type ,list)))
412
413 (define-type-method to-alien-function ((type gslist) &optional copy-p)
414   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
415     (values
416      #'(lambda (list)
417          (make-gslist element-type list (not copy-p)))
418      (unless copy-p
419        #'(lambda (list gslist)
420            (declare (ignore list))
421            (destroy-gslist gslist element-type t))))))
422
423 (define-type-method from-alien-form ((type gslist) form &key (ref :free))
424   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
425     `(let ((gslist ,form))
426        (unwind-protect
427            (map-glist 'list #'identity gslist ',element-type
428             ,(ecase ref (:free :get) ((:static :temp) :peek) (:copy :read)))
429          ,(when (eq ref :free)
430             `(destroy-gslist gslist ',element-type))))))
431
432 (define-type-method from-alien-function ((type gslist)  &key (ref :free))
433   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
434     (ecase ref
435       (:free 
436        #'(lambda (glist)
437            (prog1
438                (map-glist 'list #'identity glist element-type :get)
439              (gslist-free glist))))
440       (:copy
441        #'(lambda (glist)
442            (map-glist 'list #'identity glist element-type :read)))
443       ((:static :temp)
444        #'(lambda (glist)
445            (map-glist 'list #'identity glist element-type :peek))))))
446
447 (define-type-method writer-function ((type gslist) &key temp inlined)
448   (assert-not-inlined type inlined)
449   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
450     (let ((element-writer (writer-function element-type :temp temp)))
451       #'(lambda (list location &optional (offset 0))
452           (setf 
453            (ref-pointer location offset)
454            (make-gslist element-writer list))))))
455
456 (define-type-method reader-function ((type gslist) &key (ref :read) inlined)
457   (assert-not-inlined type inlined)
458   (let ((element-type (second (type-expand-to 'gslist type))))
459     (ecase ref
460       ((:read :peek)
461        #'(lambda (location &optional (offset 0))
462            (unless (null-pointer-p (ref-pointer location offset))
463              (map-glist 'list #'identity (ref-pointer location offset) element-type ref))))
464       (:get
465        #'(lambda (location &optional (offset 0))
466            (unless (null-pointer-p (ref-pointer location offset))
467              (prog1
468                  (map-glist 'list #'identity (ref-pointer location offset) element-type :get)
469                (gslist-free (ref-pointer location offset))
470                (setf (ref-pointer location offset) (make-pointer 0)))))))))
471
472 (define-type-method destroy-function ((type gslist) &key temp inlined)
473   (assert-not-inlined type inlined)
474   (let ((element-type (second (type-expand-to 'gslist type))))
475     #'(lambda (location &optional (offset 0))
476         (unless (null-pointer-p (ref-pointer location offset))
477           (destroy-gslist (ref-pointer location offset) element-type temp)
478           (setf (ref-pointer location offset) (make-pointer 0))))))
479
480 (define-type-method copy-function ((type gslist) &key inlined)
481   (assert-not-inlined type inlined)
482   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
483     (let ((copy-element (copy-function element-type)))
484       #'(lambda (from to &optional (offset 0))
485           (unless (null-pointer-p (ref-pointer from offset))
486             (loop
487              as from-list = (ref-pointer from offset) 
488                             then (glist-next from-list)
489              as to-list = (setf (ref-pointer to offset) (%gslist-append nil)) 
490                           then (%gslist-append to-list)
491              do (funcall copy-element from-list to-list)
492              while (glist-next from-list)))))))