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