chiark / gitweb /
a981bc660e393ef006880005f50380021567d262
[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.40 2007/06/15 12:25:16 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 ;;;; User data mechanism
56
57 (defvar *user-data-lock* (make-mutex))
58 (defvar *user-data* (make-hash-table))
59 (defvar *user-data-count* 0)
60
61 (defun register-user-data (object &optional destroy-function)
62   (check-type destroy-function (or null symbol function))
63   (with-mutex (*user-data-lock*)
64     (incf *user-data-count*)
65     (setf
66      (gethash *user-data-count* *user-data*)
67      (cons object destroy-function))
68     *user-data-count*))
69
70 (defun find-user-data (id)
71   (check-type id fixnum)
72   (with-mutex (*user-data-lock*)
73     (multiple-value-bind (user-data p) (gethash id *user-data*)
74       (values (car user-data) p))))
75
76 (defun user-data-exists-p (id)
77   (nth-value 1 (find-user-data id)))
78
79 (defun update-user-data (id object)
80   (check-type id fixnum)
81   (with-mutex (*user-data-lock*)
82     (multiple-value-bind (user-data exists-p) (gethash id *user-data*)
83       (cond
84        ((not exists-p) (error "User data id ~A does not exist" id))
85        (t 
86         (when (cdr user-data)
87           (funcall (cdr user-data) (car user-data)))
88         (setf (car user-data) object))))))
89
90 (defun destroy-user-data (id)
91   (check-type id fixnum)
92   (with-mutex (*user-data-lock*)
93     (let ((user-data (gethash id *user-data*)))
94       (when (cdr user-data)
95         (funcall (cdr user-data) (car user-data))))
96     (remhash id *user-data*)))
97
98
99 ;;;; Quarks
100
101 (deftype quark () 'unsigned)
102
103 (defbinding %quark-from-string () quark
104   (string string))
105
106 (defun quark-intern (object)
107   (etypecase object
108     (quark object)
109     (string (%quark-from-string object))
110     (symbol (%quark-from-string (format nil "clg-~A:~A" 
111                                  (package-name (symbol-package object)) 
112                                  object)))))
113
114 (defbinding quark-to-string () (static string)
115   (quark quark))
116
117
118 ;;;; Linked list (GList)
119
120 (deftype glist (type) 
121   `(or null (cons ,type list)))
122
123 (defbinding (%glist-append "g_list_append") () pointer
124   (glist (or null pointer))
125   (nil null))
126
127 (defun make-glist (element-type list &optional temp-p)
128   (let ((writer (if (functionp element-type)
129                     element-type
130                   (writer-function element-type :temp temp-p))))
131     (loop
132      for element in list
133      as glist = (%glist-append nil) then (%glist-append glist)
134      do (funcall writer element glist)
135      finally (return glist))))
136
137 (defun glist-next (glist)
138   (unless (null-pointer-p glist)
139     (ref-pointer glist #.(size-of 'pointer))))
140   
141 ;; Also used for gslists
142 (defun map-glist (seqtype function glist element-type &optional (ref :read))
143   (let ((reader (if (functionp element-type)
144                     element-type
145                   (reader-function element-type :ref ref))))
146     (case seqtype 
147      ((nil)
148       (loop
149        as element = glist then (glist-next element)
150        until (null-pointer-p element)
151        do (funcall function (funcall reader element))))
152      (list
153       (loop
154        as element = glist then (glist-next element)
155        until (null-pointer-p element)
156        collect (funcall function (funcall reader element))))
157      (t
158       (coerce 
159        (loop
160         as element = glist then (glist-next element)
161         until (null-pointer-p element)
162         collect (funcall function (funcall reader element)))
163        seqtype)))))
164
165 (defbinding (glist-free "g_list_free") () nil
166   (glist pointer))
167
168 (defun destroy-glist (glist element-type &optional temp-p)
169   (let ((destroy (if (functionp element-type)
170                      element-type
171                    (destroy-function element-type :temp temp-p))))
172     (loop
173      as element = glist then (glist-next element)
174      until (null-pointer-p element)
175      do (funcall destroy element)))
176   (glist-free glist))
177
178 (define-type-method alien-type ((type glist))
179   (declare (ignore type))
180   (alien-type 'pointer))
181
182 (define-type-method size-of ((type glist) &key inlined)
183   (assert-not-inlined type inlined)
184   (size-of 'pointer))
185
186 (define-type-method type-alignment ((type glist) &key inlined)
187   (assert-not-inlined type inlined)
188   (type-alignment 'pointer))
189
190 (define-type-method alien-arg-wrapper ((type glist) var list style form &optional copy-in-p)
191   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
192     (cond
193       ((and (in-arg-p style) (not (out-arg-p style)))
194        `(with-pointer (,var (make-glist ',element-type ,list ,(not copy-in-p)))
195           (unwind-protect
196               ,form
197             ,(unless copy-in-p
198                `(destroy-glist ,var ',element-type t)))))
199       ((and (in-arg-p style) (out-arg-p style))
200        (let ((glist (make-symbol "GLIST")))
201          `(with-pointer (,glist (make-glist ',element-type ,list ,(not copy-in-p)))
202             (with-pointer (,var ,glist)               
203               (unwind-protect
204                   ,form
205                 ,(unless copy-in-p
206                    `(destroy-glist ,glist ',element-type t)))))))
207       ((and (out-arg-p style) (not (in-arg-p style)))
208        `(with-pointer (,var)
209           ,form)))))
210
211 (define-type-method to-alien-form ((type glist) list &optional copy-p)
212   (declare (ignore copy-p))
213   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
214     `(make-glist ',element-type ,list)))
215
216 (define-type-method to-alien-function ((type glist) &optional copy-p)
217   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
218     (values
219      #'(lambda (list)
220          (make-glist element-type list (not copy-p)))
221      (unless copy-p
222        #'(lambda (list glist)
223            (declare (ignore list))
224            (destroy-glist glist element-type t))))))
225
226 (define-type-method from-alien-form ((type glist) form &key (ref :free))
227   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
228     `(let ((glist ,form))
229        (unwind-protect
230            (map-glist 'list #'identity glist ',element-type 
231             ,(ecase ref (:free :get) ((:static :temp) :peek) (:copy :read)))
232          ,(when (eq ref :free)
233             `(destroy-glist glist ',element-type))))))
234
235 (define-type-method from-alien-function ((type glist) &key (ref :free))
236   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
237     (ecase ref
238       (:free 
239        #'(lambda (glist)
240            (prog1
241                (map-glist 'list #'identity glist element-type :get)
242              (glist-free glist))))
243       (:copy
244        #'(lambda (glist)
245            (map-glist 'list #'identity glist element-type :read)))
246       ((:static :temp)
247        #'(lambda (glist)
248            (map-glist 'list #'identity glist element-type :peek))))))
249
250 (define-type-method writer-function ((type glist) &key temp inlined)
251   (assert-not-inlined type inlined)
252   (let ((element-type (second (type-expand-to 'glist type))))
253     #'(lambda (list location &optional (offset 0))
254         (setf 
255          (ref-pointer location offset)
256          (make-glist element-type list temp)))))
257
258 (define-type-method reader-function ((type glist) &key (ref :read) inlined)
259   (assert-not-inlined type inlined)
260   (let ((element-type (second (type-expand-to 'glist type))))
261     (ecase ref
262       ((:read :peek)
263        #'(lambda (location &optional (offset 0))
264            (unless (null-pointer-p (ref-pointer location offset))
265              (map-glist 'list #'identity (ref-pointer location offset) element-type ref))))
266       (:get
267        #'(lambda (location &optional (offset 0))
268            (unless (null-pointer-p (ref-pointer location offset))
269              (prog1
270                  (map-glist 'list #'identity (ref-pointer location offset) element-type :get)
271                (glist-free (ref-pointer location offset))
272                (setf (ref-pointer location offset) (make-pointer 0)))))))))
273
274 (define-type-method destroy-function ((type glist) &key temp inlined)
275   (assert-not-inlined type inlined)
276   (let ((element-type (second (type-expand-to 'glist type))))
277     #'(lambda (location &optional (offset 0))
278         (unless (null-pointer-p (ref-pointer location offset))
279           (destroy-glist (ref-pointer location offset) element-type temp)
280           (setf (ref-pointer location offset) (make-pointer 0))))))
281
282 (define-type-method copy-function ((type glist) &key inlined)
283   (assert-not-inlined type inlined)
284   (destructuring-bind (element-type) (rest (type-expand-to 'glist type))
285     (let ((copy-element (copy-function element-type)))
286       #'(lambda (from to &optional (offset 0))
287           (unless (null-pointer-p (ref-pointer from offset))
288             (loop
289              as from-list = (ref-pointer from offset) 
290                             then (glist-next from-list)
291              as to-list = (setf (ref-pointer to offset) (%glist-append nil)) 
292                           then (%glist-append to-list)
293              do (funcall copy-element from-list to-list)
294              while (glist-next from-lisT)))))))
295
296
297 ;;;; Single linked list (GSList)
298
299 (deftype gslist (type) `(or null (cons ,type list)))
300
301 (defbinding (%gslist-prepend "g_slist_prepend") () pointer
302   (gslist pointer)
303   (nil null))
304
305 (defbinding (%gslist-append "g_slist_append") () pointer
306   (glist (or null pointer))
307   (nil null))
308
309
310 (defun make-gslist (element-type list &optional temp-p)
311   (let ((writer (if (functionp element-type)
312                     element-type
313                   (writer-function element-type :temp temp-p))))
314     (loop
315      for element in (reverse list)
316      as gslist = (%gslist-prepend (make-pointer 0)) then (%gslist-prepend gslist)
317      do (funcall writer element gslist)
318      finally (return gslist))))
319
320 (defbinding (gslist-free "g_slist_free") () nil
321   (gslist pointer))
322
323 (defun destroy-gslist (gslist element-type &optional temp-p)
324   (loop
325    with destroy = (destroy-function element-type :temp temp-p)
326    as element = gslist then (glist-next element)
327    until (null-pointer-p element)
328    do (funcall destroy element 0))
329   (gslist-free gslist))
330
331 (define-type-method alien-type ((type gslist))
332   (declare (ignore type))
333   (alien-type 'pointer))
334
335 (define-type-method size-of ((type gslist) &key inlined)
336   (assert-not-inlined type inlined)
337   (size-of 'pointer))
338
339 (define-type-method type-alignment ((type gslist) &key inlined)
340   (assert-not-inlined type inlined)
341   (type-alignment 'pointer))
342
343 (define-type-method alien-arg-wrapper ((type gslist) var list style form &optional copy-in-p)
344   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
345     (cond
346       ((and (in-arg-p style) (not (out-arg-p style)))
347        `(with-pointer (,var (make-gslist ',element-type ,list ,(not copy-in-p)))
348           (unwind-protect
349               ,form
350             ,(unless copy-in-p
351                `(destroy-gslist ,var ',element-type t)))))
352       ((and (in-arg-p style) (out-arg-p style))
353        (let ((gslist (make-symbol "GSLIST")))
354          `(with-pointer (,gslist (make-gslist ',element-type ,list ,(not copy-in-p)))
355             (with-pointer (,var ,gslist)                      
356               (unwind-protect
357                   ,form
358                 ,(unless copy-in-p
359                    `(destroy-gslist ,gslist ',element-type t)))))))
360       ((and (out-arg-p style) (not (in-arg-p style)))
361        `(with-pointer (,var)
362           ,form)))))
363
364 (define-type-method to-alien-form ((type gslist) list &optional copy-p)
365   (declare (ignore copy-p))
366   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
367     `(make-gslist ',element-type ,list)))
368
369 (define-type-method to-alien-function ((type gslist) &optional copy-p)
370   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
371     (values
372      #'(lambda (list)
373          (make-gslist element-type list (not copy-p)))
374      (unless copy-p
375        #'(lambda (list gslist)
376            (declare (ignore list))
377            (destroy-gslist gslist element-type t))))))
378
379 (define-type-method from-alien-form ((type gslist) form &key (ref :free))
380   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
381     `(let ((gslist ,form))
382        (unwind-protect
383            (map-glist 'list #'identity gslist ',element-type
384             ,(ecase ref (:free :get) ((:static :temp) :peek) (:copy :read)))
385          ,(when (eq ref :free)
386             `(destroy-gslist gslist ',element-type))))))
387
388 (define-type-method from-alien-function ((type gslist)  &key (ref :free))
389   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
390     (ecase ref
391       (:free 
392        #'(lambda (glist)
393            (prog1
394                (map-glist 'list #'identity glist element-type :get)
395              (gslist-free glist))))
396       (:copy
397        #'(lambda (glist)
398            (map-glist 'list #'identity glist element-type :read)))
399       ((:static :temp)
400        #'(lambda (glist)
401            (map-glist 'list #'identity glist element-type :peek))))))
402
403 (define-type-method writer-function ((type gslist) &key temp inlined)
404   (assert-not-inlined type inlined)
405   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
406     (let ((element-writer (writer-function element-type :temp temp)))
407       #'(lambda (list location &optional (offset 0))
408           (setf 
409            (ref-pointer location offset)
410            (make-gslist element-writer list))))))
411
412 (define-type-method reader-function ((type gslist) &key (ref :read) inlined)
413   (assert-not-inlined type inlined)
414   (let ((element-type (second (type-expand-to 'gslist type))))
415     (ecase ref
416       ((:read :peek)
417        #'(lambda (location &optional (offset 0))
418            (unless (null-pointer-p (ref-pointer location offset))
419              (map-glist 'list #'identity (ref-pointer location offset) element-type ref))))
420       (:get
421        #'(lambda (location &optional (offset 0))
422            (unless (null-pointer-p (ref-pointer location offset))
423              (prog1
424                  (map-glist 'list #'identity (ref-pointer location offset) element-type :get)
425                (gslist-free (ref-pointer location offset))
426                (setf (ref-pointer location offset) (make-pointer 0)))))))))
427
428 (define-type-method destroy-function ((type gslist) &key temp inlined)
429   (assert-not-inlined type inlined)
430   (let ((element-type (second (type-expand-to 'gslist type))))
431     #'(lambda (location &optional (offset 0))
432         (unless (null-pointer-p (ref-pointer location offset))
433           (destroy-gslist (ref-pointer location offset) element-type temp)
434           (setf (ref-pointer location offset) (make-pointer 0))))))
435
436 (define-type-method copy-function ((type gslist) &key inlined)
437   (assert-not-inlined type inlined)
438   (destructuring-bind (element-type) (rest (type-expand-to 'gslist type))
439     (let ((copy-element (copy-function element-type)))
440       #'(lambda (from to &optional (offset 0))
441           (unless (null-pointer-p (ref-pointer from offset))
442             (loop
443              as from-list = (ref-pointer from offset) 
444                             then (glist-next from-list)
445              as to-list = (setf (ref-pointer to offset) (%gslist-append nil)) 
446                           then (%gslist-append to-list)
447              do (funcall copy-element from-list to-list)
448              while (glist-next from-list)))))))