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