chiark / gitweb /
Added missing package prefix to FEATUREP
[clg] / gffi / basic-types.lisp
1 ;; Common Lisp bindings for GTK+ v2.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: basic-types.lisp,v 1.9 2007-06-20 09:49:06 espen Exp $
24
25 (in-package "GFFI")
26
27
28 (deftype int ()
29   '(signed-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:int)
30                 #+clisp #.(ffi:bitsizeof 'ffi:int)
31                 #-(or sbcl clisp) 32))
32 (deftype unsigned-int () 
33   '(unsigned-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:int)
34                   #+clisp #.(ffi:bitsizeof 'ffi:int)
35                   #-(or sbcl clisp) 32))
36 (deftype long () 
37   '(signed-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:long)
38                 #+clisp #.(ffi:bitsizeof 'ffi:long)
39                 #-(or sbcl clisp) 32))
40 (deftype unsigned-long () 
41   '(unsigned-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:long)
42                   #+clisp #.(ffi:bitsizeof 'ffi:long)
43                   #-(or sbcl clisp) 32))
44 (deftype short () 
45   '(signed-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:short)
46                 #+clisp #.(ffi:bitsizeof 'ffi:short)
47                 #-(or sbcl clisp) 16))
48 (deftype unsigned-short () 
49   '(unsigned-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:short)
50                   #+clisp #.(ffi:bitsizeof 'ffi:short)
51                   #-(or sbcl clisp) 16))
52 (deftype signed (&optional (size '*)) `(signed-byte ,size))
53 (deftype unsigned (&optional (size '*)) `(unsigned-byte ,size))
54 (deftype char () 'base-char)
55 (deftype pointer () 
56   #+(or cmu sbcl) 'system-area-pointer
57   #+clisp 'ffi:foreign-address)
58 (deftype pointer-data () 
59   '(unsigned-byte #+sbcl #.(sb-sizeof-bits 'sb-alien:system-area-pointer)
60                   #+clisp #.(ffi:bitsizeof 'ffi:c-pointer)
61                   #-(or sbcl clisp) 32))
62   
63 (deftype bool (&optional (size '*)) (declare (ignore size)) 'boolean)
64 (deftype copy-of (type) type)
65 (deftype static (type) type)
66 (deftype inlined (type) type)
67
68
69
70 (define-type-generic alien-type (type)
71   "Returns the foreign type corresponding to TYPE")
72 (define-type-generic size-of (type &key inlined)
73   "Returns the foreign size of TYPE. The default value of INLINED is
74 T for basic C types and NIL for other types.")
75 (define-type-generic type-alignment (type &key inlined)
76   "Returns the alignment of TYPE. The default value of INLINED is
77 T for basic C types and NIL for other types.")
78 (define-type-generic alien-arg-wrapper (type var arg style form &optional copy-p)
79   "Creates a wrapper around FORM which binds the alien translation of
80 ARG to VAR in a way which makes it possible to pass the location of
81 VAR in a foreign function call. It should also do any necessary clean
82 up before returning the value of FORM.")
83 (define-type-generic to-alien-form (type form &optional copy-p)
84   "Returns a form which translates FORM to alien representation. If
85 COPY-P is non NIL then any allocated foreign memory must not be
86 reclaimed later.")
87 (define-type-generic from-alien-form (type form &key ref)
88   "Returns a form which translates FORM from alien to lisp
89 representation. REF should be :FREE, :COPY, :STATIC or :TEMP")
90 (define-type-generic to-alien-function (type &optional copy-p)
91   "Returns a function of one argument which will translate objects of the given type to alien repesentation. An optional function, taking the origional object and the alien representation as arguments, to clean up after the alien value is not needed any more may be returned as a second argument.")
92 (define-type-generic from-alien-function (type &key ref)
93   "Returns a function of one argument which will translate alien objects of the given type to lisp representation. REF should be :FREE, :COPY, :STATIC or :TEMP")
94 (define-type-generic callback-wrapper (type var arg form)
95   "Creates a wrapper around FORM which binds the lisp translation of
96 ARG to VAR during a C callback.")
97
98 (define-type-generic writer-function (type &key temp inlined)
99   "Returns a function taking a value, an address and an optional
100 offset which when called will write a reference an object at the given
101 location. If TEMP is non NIL then the object is expected to be valid
102 as long as the reference exists.")
103 (define-type-generic reader-function (type &key ref inlined)
104   "Returns a function taking an address and optional offset which when
105 called will return the object at given location. REF should be :READ,
106 :PEEK or :GET")
107 (define-type-generic destroy-function (type &key temp inlined)
108   "Returns a function taking an address and optional offset which when
109 called will destroy the reference at the given location. This may
110 involve freeing the foreign object being referenced or decreasing it's
111 ref. count. If TEMP is non NIL then the reference is expected to
112 have been written as temporal.")
113 (define-type-generic copy-function (type &key inlined))
114
115 (define-type-generic unbound-value (type-spec)
116   "Returns a value which should be interpreted as unbound for slots with virtual allocation")
117
118 (defun assert-inlined (type inlined-p)
119   (unless inlined-p
120     (error "Type ~A can only be inlined" type)))
121
122 (defun assert-not-inlined (type inlined-p)
123   (when inlined-p
124     (error "Type ~A can not be inlined" type)))
125
126
127 (define-type-method alien-arg-wrapper ((type t) var arg style form &optional 
128                                        (copy-in-p nil copy-in-given-p))
129   (let ((alien-type (alien-type type)))
130     (cond
131       ((in-arg-p style)
132        (let ((to-alien (if copy-in-given-p
133                            (to-alien-form type arg copy-in-p)
134                          (to-alien-form type arg))))
135          #+(or cmu sbcl)
136          `(with-alien ((,var ,alien-type ,to-alien))
137             ,form)
138          #+clisp
139          `(ffi:with-c-var (,var ',alien-type ,to-alien)
140             ,form)))
141       ((out-arg-p style)
142        #+(or cmu sbcl)
143        `(with-alien ((,var ,alien-type))
144           (clear-memory (alien-sap (addr ,var)) ,(size-of type))
145           ,form)
146        #+clisp
147        `(ffi:with-c-var (,var ',alien-type)
148           ,form)))))
149
150 (define-type-method callback-wrapper ((type t) var arg form)
151   `(let ((,var ,(from-alien-form type arg :ref :temp)))
152      ,form))
153
154 (define-type-method alien-type ((type t))
155   (error "No alien type corresponding to the type specifier ~A" type))
156
157 (define-type-method to-alien-form ((type t) form &optional copy-p)
158   (declare (ignore form copy-p))
159   (error "Not a valid type specifier for arguments: ~A" type))
160
161 (define-type-method to-alien-function ((type t) &optional copy-p)
162   (declare (ignore copy-p))
163   (error "Not a valid type specifier for arguments: ~A" type))
164
165 (define-type-method from-alien-form ((type t) form &key ref)
166   (declare (ignore form ref))
167   (error "Not a valid type specifier for return values: ~A" type))
168
169 (define-type-method from-alien-function ((type t) &key ref)
170   (declare (ignore ref))
171   (error "Not a valid type specifier for return values: ~A" type))
172
173 (define-type-method destroy-function ((type t) &key temp (inlined t inlined-p))
174   (declare (ignore temp))
175   (let ((size (if inlined-p 
176                   (size-of type :inlined inlined)
177                 (size-of type))))
178     #'(lambda (location &optional (offset 0))
179         (clear-memory location size offset))))
180
181 (define-type-method copy-function ((type t) &key (inlined t inlined-p))
182   (let ((size (if inlined-p 
183                   (size-of type :inlined inlined)
184                 (size-of type))))
185     #'(lambda (from to &optional (offset 0))
186         (copy-memory (pointer+ from offset) size (pointer+ to offset)))))
187
188 (define-type-method to-alien-form ((type real) form &optional copy-p)
189   (declare (ignore type copy-p))
190   form)
191
192 (define-type-method to-alien-function ((type real) &optional copy-p)
193   (declare (ignore type copy-p))
194   #'identity)
195
196 (define-type-method from-alien-form ((type real) form &key ref)
197   (declare (ignore type ref))
198   form)
199
200 (define-type-method from-alien-function ((type real) &key ref)
201   (declare (ignore type ref))
202   #'identity)
203
204
205 (define-type-method alien-type ((type integer))
206   (declare (ignore type))
207   (alien-type 'signed-byte))
208
209 (define-type-method size-of ((type integer) &key (inlined t))
210   (declare (ignore type))
211   (size-of 'signed-byte :inlined inlined))
212
213 (define-type-method type-alignment ((type integer) &key (inlined t))
214   (declare (ignore type))
215   (type-alignment 'signed-byte :inlined inlined))
216
217 (define-type-method writer-function ((type integer) &key temp (inlined t))
218   (declare (ignore temp))
219   (assert-inlined type inlined)
220   (writer-function 'signed-byte))
221
222 (define-type-method reader-function ((type integer) &key ref (inlined t))
223   (declare (ignore ref))
224   (assert-inlined type inlined)
225   (reader-function 'signed-byte))
226
227
228 ;;; Signed Byte
229   
230 (define-type-method alien-type ((type signed-byte))
231   (destructuring-bind (&optional (size '*))
232       (rest (mklist (type-expand-to 'signed-byte type)))
233     (let ((size (if (eq size '*) 
234                     (second (type-expand-to 'signed-byte 'int))
235                   size)))
236       #+cmu
237       (ecase size
238         ( 8 '(alien:signed 8))
239         (16 '(alien:signed 16))
240         (32 '(alien:signed 32))
241         (64 '(alien:signed 64)))
242       #+sbcl
243       (ecase size
244         ( 8 '(sb-alien:signed  8))
245         (16 '(sb-alien:signed 16))
246         (32 '(sb-alien:signed 32))
247         (64 '(sb-alien:signed 64)))
248       #+clisp
249       (ecase size
250         ( 8 'ffi:sint8)
251         (16 'ffi:sint16)
252         (32 'ffi:sint32)
253         (64 'ffi:sint64)))))
254
255 (define-type-method size-of ((type signed-byte) &key (inlined t))
256   (assert-inlined type inlined)
257   (destructuring-bind (&optional (size '*))
258       (rest (mklist (type-expand-to 'signed-byte type)))
259     (let ((size (if (eq size '*) 
260                     (second (type-expand-to 'signed-byte 'int))
261                   size)))
262       (ecase size
263         ( 8 1)
264         (16 2)
265         (32 4)
266         (64 8)))))
267
268 (define-type-method type-alignment ((type signed-byte) &key (inlined t))
269   (assert-inlined type inlined)
270   (destructuring-bind (&optional (size '*))
271       (rest (mklist (type-expand-to 'signed-byte type)))
272     (let ((size (if (eq size '*) 
273                     (second (type-expand-to 'signed-byte 'int))
274                   size)))
275       #+sbcl(sb-alignment `(sb-alien:signed ,size))
276       #+clisp(ecase size
277                ( 8 (nth-value 1 (ffi:sizeof 'ffi:sint8)))
278                (16 (nth-value 1 (ffi:sizeof 'ffi:sint16)))
279                (32 (nth-value 1 (ffi:sizeof 'ffi:sint32)))
280                (64 (nth-value 1 (ffi:sizeof 'ffi:sint64))))
281       #-(or sbcl clisp) 4)))
282
283 (define-type-method writer-function ((type signed-byte) &key temp (inlined t))
284   (declare (ignore temp))
285   (assert-inlined type inlined)
286   (destructuring-bind (&optional (size '*))
287       (rest (mklist (type-expand-to 'signed-byte type)))
288     (let ((size (if (eq size '*) 
289                     (second (type-expand-to 'signed-byte 'int))
290                   size)))
291       (ecase size
292         ( 8 #'(lambda (value location &optional (offset 0))
293                 (setf 
294                  #+(or cmu sbcl)(signed-sap-ref-8 location offset)
295                  #+clisp(ffi:memory-as location 'ffi:sint8 offset)
296                  value)))
297         (16 #'(lambda (value location &optional (offset 0))
298                 (setf 
299                  #+(or cmu sbcl)(signed-sap-ref-16 location offset)
300                  #+clisp(ffi:memory-as location 'ffi:sint16 offset)
301                  value)))
302         (32 #'(lambda (value location &optional (offset 0))            
303                 (setf 
304                  #+(or cmu sbcl)(signed-sap-ref-32 location offset)
305                  #+clisp(ffi:memory-as location 'ffi:sint32 offset)
306                  value)))
307         (64 #'(lambda (value location &optional (offset 0))
308                 (setf 
309                  #+(or cmu sbcl)(signed-sap-ref-64 location offset)
310                  #+clisp(ffi:memory-as location 'ffi:sint64 offset)
311                  value)))))))
312
313 (define-type-method reader-function ((type signed-byte) &key ref (inlined t))
314   (declare (ignore ref))
315   (assert-inlined type inlined)
316   (destructuring-bind (&optional (size '*))
317       (rest (mklist (type-expand-to 'signed-byte type)))
318     (let ((size (if (eq size '*) 
319                     (second (type-expand-to 'signed-byte 'int))
320                   size)))
321       (ecase size
322         ( 8 #'(lambda (location &optional (offset 0)) 
323                 #+(or cmu sbcl)(signed-sap-ref-8 location offset)
324                 #+clisp(ffi:memory-as location 'ffi:sint8 offset)))
325         (16 #'(lambda (location &optional (offset 0))
326                 #+(or cmu sbcl)(signed-sap-ref-16 location offset)
327                 #+clisp(ffi:memory-as location 'ffi:sint16 offset)))
328         (32 #'(lambda (location &optional (offset 0)) 
329                 #+(or cmu sbcl)(signed-sap-ref-32 location offset)
330                 #+clisp(ffi:memory-as location 'ffi:sint32 offset)))
331         (64 #'(lambda (location &optional (offset 0)) 
332                 #+(or cmu sbcl)(signed-sap-ref-64 location offset)
333                 #+clisp(ffi:memory-as location 'ffi:sint64 offset)))))))
334
335
336
337 ;;; Unsigned Byte
338   
339 (define-type-method alien-type ((type unsigned-byte))
340   (destructuring-bind (&optional (size '*))
341       (rest (mklist (type-expand-to 'unsigned-byte type)))
342     (let ((size (if (eq size '*) 
343                     (second (type-expand-to 'signed-byte 'int))
344                   size)))
345       #+cmu
346       (ecase size
347         ( 8 '(alien:unsigned 8))
348         (16 '(alien:unsigned 16))
349         (32 '(alien:unsigned 32))
350         (64 '(alien:unsigned 64)))
351       #+sbcl
352       (ecase size
353         ( 8 '(sb-alien:unsigned  8))
354         (16 '(sb-alien:unsigned 16))
355         (32 '(sb-alien:unsigned 32))
356         (64 '(sb-alien:unsigned 64)))
357       #+clisp
358       (ecase size
359         ( 8 'ffi:uint8)
360         (16 'ffi:uint16)
361         (32 'ffi:uint32)
362         (64 'ffi:uint64)))))
363
364 (define-type-method size-of ((type unsigned-byte) &key (inlined t))
365   (assert-inlined type inlined)
366   (destructuring-bind (&optional (size '*))
367       (rest (mklist (type-expand-to 'unsigned-byte type)))
368     (size-of `(signed ,size))))
369
370 (define-type-method type-alignment ((type unsigned-byte) &key (inlined t))
371   (assert-inlined type inlined)
372   (destructuring-bind (&optional (size '*))
373       (rest (mklist (type-expand-to 'unsigned-byte type)))
374     (type-alignment `(signed ,size))))
375
376 (define-type-method writer-function ((type unsigned-byte) &key temp (inlined t))
377   (declare (ignore temp))
378   (assert-inlined type inlined)
379   (destructuring-bind (&optional (size '*))
380       (rest (mklist (type-expand-to 'unsigned-byte type)))
381     (let ((size (if (eq size '*) 
382                     (second (type-expand-to 'signed-byte 'int))
383                   size)))
384       (ecase size
385         ( 8 #'(lambda (value location &optional (offset 0))             
386                 (setf 
387                  #+(or cmu sbcl)(sap-ref-8 location offset)
388                  #+clisp(ffi:memory-as location 'ffi:uint8 offset)
389                  value)))
390         (16 #'(lambda (value location &optional (offset 0))
391                 (setf 
392                  #+(or cmu sbcl)(sap-ref-16 location offset)
393                  #+clisp(ffi:memory-as location 'ffi:uint16 offset)
394                  value)))
395         (32 #'(lambda (value location &optional (offset 0))            
396                 (setf 
397                  #+(or cmu sbcl)(sap-ref-32 location offset)
398                  #+clisp(ffi:memory-as location 'ffi:uint32 offset)
399                  value)))
400         (64 #'(lambda (value location &optional (offset 0))
401                 (setf 
402                  #+(or cmu sbcl)(sap-ref-64 location offset)
403                  #+clisp(ffi:memory-as location 'ffi:uint64 offset)
404                  value)))))))
405       
406 (define-type-method reader-function ((type unsigned-byte) &key ref (inlined t))
407   (declare (ignore ref))
408   (assert-inlined type inlined)
409   (destructuring-bind (&optional (size '*))
410       (rest (mklist (type-expand-to 'unsigned-byte type)))
411     (let ((size (if (eq size '*) 
412                     (second (type-expand-to 'signed-byte 'int))
413                   size)))
414       (ecase size
415         ( 8 #'(lambda (location &optional (offset 0)) 
416                 #+(or cmu sbcl)(sap-ref-8 location offset)
417                 #+clisp(ffi:memory-as location 'ffi:uint8 offset)))
418         (16 #'(lambda (location &optional (offset 0))
419                 #+(or cmu sbcl)(sap-ref-16 location offset)
420                 #+clisp(ffi:memory-as location 'ffi:uint16 offset)))
421         (32 #'(lambda (location &optional (offset 0)) 
422                 #+(or cmu sbcl)(sap-ref-32 location offset)
423                 #+clisp(ffi:memory-as location 'ffi:uint32 offset)))
424         (64 #'(lambda (location &optional (offset 0)) 
425                 #+(or cmu sbcl)(sap-ref-64 location offset)
426                 #+clisp(ffi:memory-as location 'ffi:uint64 offset)))))))
427
428
429
430 ;;; Single Float
431
432 (define-type-method alien-type ((type single-float))
433   (declare (ignore type))
434   #+cmu 'alien:single-float 
435   #+sbcl 'sb-alien:single-float
436   #+clisp 'single-float)
437
438 (define-type-method size-of ((type single-float) &key (inlined t))
439   (assert-inlined type inlined)
440   #+sbcl (sb-sizeof 'sb-alien:float)
441   #+clisp (ffi:sizeof 'single-float)
442   #-(or sbcl clisp) 4)
443
444 (define-type-method type-alignment ((type single-float) &key (inlined t))
445   (assert-inlined type inlined)
446   #+sbcl (sb-alignment 'single-float)
447   #+clisp (nth-value 1 (ffi:sizeof 'single-float))
448   #-(or sbcl clisp) 4)
449
450 (define-type-method to-alien-form ((type single-float) form &optional copy-p)
451   (declare (ignore type copy-p))
452   `(coerce ,form 'single-float))
453
454 (define-type-method to-alien-function ((type single-float) &optional copy-p)
455   (declare (ignore type copy-p))
456   #'(lambda (number)
457       (coerce number 'single-float)))
458
459 (define-type-method writer-function ((type single-float) &key temp (inlined t))
460   (declare (ignore temp))
461   (assert-inlined type inlined)
462   #'(lambda (number location &optional (offset 0))
463       (setf (ref-single-float location offset) (coerce number 'single-float))))
464
465 (define-type-method reader-function ((type single-float) &key ref (inlined t))
466   (declare (ignore ref))
467   (assert-inlined type inlined)
468   #'ref-single-float)
469
470
471
472 ;;; Double Float
473
474 (define-type-method alien-type ((type double-float))
475   (declare (ignore type))
476   #+cmu 'alien:double-float 
477   #+sbcl 'sb-alien:double-float
478   #+clisp 'double-float)
479
480 (define-type-method size-of ((type double-float) &key (inlined t))
481   (assert-inlined type inlined)
482   #+sbcl (sb-sizeof 'sb-alien:double)
483   #+clisp (ffi:sizeof 'double-float)
484   #-(or sbcl clisp) 8)
485
486 (define-type-method type-alignment ((type double-float) &key (inlined t))
487   (assert-inlined type inlined)
488   #+sbcl (sb-alignment 'double-float)
489   #+clisp (nth-value 1 (ffi:sizeof 'double-float))
490   #-(or sbcl clisp) 4)
491
492 (define-type-method to-alien-form ((type double-float) form &optional copy-p)
493   (declare (ignore type copy-p))
494   `(coerce ,form 'double-float))
495
496 (define-type-method to-alien-function ((type double-float) &optional copy-p)
497   (declare (ignore type copy-p))
498   #'(lambda (number)
499       (coerce number 'double-float)))
500
501 (define-type-method writer-function ((type double-float) &key temp (inlined t))
502   (declare (ignore temp))
503   (assert-inlined type inlined)
504   #'(lambda (value location &optional (offset 0))
505       (setf (ref-double-float location offset) (coerce value 'double-float))))
506
507 (define-type-method reader-function ((type double-float) &key ref (inlined t))
508   (declare (ignore ref))
509   (assert-inlined type inlined)
510   #'ref-double-float)
511
512 (deftype optimized-double-float () 'double-float)
513
514 (define-type-method to-alien-form ((type optimized-double-float) form &optional copy-p)
515   (declare (ignore type copy-p))
516   form)
517
518
519
520 ;;; Character
521
522 (define-type-method alien-type ((type base-char))
523   (declare (ignore type))
524   #+cmu 'c-call:char 
525   #+sbcl 'sb-alien:char
526   #+clisp 'ffi:character)
527
528 (define-type-method size-of ((type base-char) &key (inlined t))
529   (assert-inlined type inlined)
530   1)
531
532 (define-type-method type-alignment ((type base-char) &key (inlined t))
533   (assert-inlined type inlined)
534   #+sbcl (sb-alignment 'sb-alien:char)
535   #+clisp (nth-value 1 (ffi:sizeof 'ffi:character))
536   #-(or sbcl clisp) 4)
537   
538 (define-type-method to-alien-form ((type base-char) form &optional copy-p)
539   (declare (ignore type copy-p))
540   form)
541
542 (define-type-method to-alien-function ((type base-char) &optional copy-p)
543   (declare (ignore type copy-p))
544   #'identity)
545
546 (define-type-method from-alien-form ((type base-char) form &key ref)
547   (declare (ignore type ref))
548   form)
549
550 (define-type-method from-alien-function ((type base-char) &key ref)
551   (declare (ignore type ref))
552   #'identity)
553
554 (define-type-method writer-function ((type base-char) &key temp (inlined t))
555   (declare (ignore temp))
556   (assert-inlined type inlined)
557   #'(lambda (char location &optional (offset 0))
558       #+(or cmu sbcl)
559       (setf (sap-ref-8 location offset) (char-code char))
560       #+clisp(setf (ffi:memory-as location 'ffi:character offset) char)))
561
562 (define-type-method reader-function ((type base-char) &key ref (inlined t))
563   (declare (ignore ref))
564   (assert-inlined type inlined)
565   #'(lambda (location &optional (offset 0))
566       #+(or cmu sbcl)(code-char (sap-ref-8 location offset))
567       #+clisp(ffi:memory-as location 'ffi:character offset)))
568
569
570
571 ;;; String
572
573 (defun utf8-length (string)
574   "Returns the length including the trailing zero, of STRING encoded as UTF8"
575   (1+ (loop
576        for char across string
577        as char-code = (char-code char)
578        sum (cond
579             ((< char-code #x7F) 1)
580             ((< char-code #x7FF) 2)
581             ((< char-code #xFFFF) 3)
582             ((< char-code #x1FFFFF) 4)))))
583
584 (defun encode-utf8-string (string &optional location)
585   (let* ((len (utf8-length string))
586          (location (or location (allocate-memory len))))
587     (loop
588      for char across string
589      for i from 0
590      as char-code = (char-code char)
591      do (flet ((encode (size)
592                  (let ((rem (mod size 6)))
593                    (setf (ref-byte location i)
594                     (deposit-field 
595                      #xFF (byte (- 7 rem) (1+ rem))
596                      (ldb (byte rem (- size rem)) char-code)))
597                    (loop
598                     for pos from (- size rem 6) downto 0 by 6
599                     do (setf (ref-byte location (incf i)) 
600                         (+ 128 (ldb (byte 6 pos) char-code)))))))
601           (cond
602            ((< char-code #x80) (setf (ref-byte location i) char-code))
603            ((< char-code #x800) (encode 11))
604            ((< char-code #x10000) (encode 16))
605            ((< char-code #x200000) (encode 21)))))
606     (setf (ref-byte location (1- len)) 0)
607     location))
608
609 (defun decode-utf8-string (c-string)
610   (with-output-to-string (string)
611     (loop
612      for i from 0
613      as octet = (ref-byte c-string i)
614      until (zerop octet)
615      do (flet ((decode (size)
616                  (loop
617                   with rem = (mod size 6)
618                   for pos from (- size rem) downto 0 by 6
619                   as code = (dpb (ldb (byte rem 0) octet) (byte rem pos) 0)
620                   then (dpb 
621                         (ldb (byte 6 0) (ref-byte c-string (incf i)))
622                         (byte 6 pos) code)
623                   finally (write-char (code-char code) string))))
624           (cond
625            ((< octet 128) (write-char (code-char octet) string))
626            ((< octet 224) (decode 11))
627            ((< octet 240) (decode 16))
628            ((< octet 248) (decode 21)))))))
629
630
631 (define-type-method alien-arg-wrapper ((type string) var string style form &optional copy-in-p)
632   (declare (ignore type))
633   (cond
634    ((and (in-arg-p style) copy-in-p)
635     `(with-pointer (,var (encode-utf8-string ,string))
636        ,form))
637    ((and (in-arg-p style) (not (out-arg-p style)))
638     `(with-memory (,var (utf8-length ,string))
639        (encode-utf8-string ,string ,var)
640        ,form))
641    ((and (in-arg-p style) (out-arg-p style))
642     (let ((c-string (make-symbol "C-STRING")))
643       `(with-memory (,c-string (utf8-length ,string))
644          (encode-utf8-string ,string ,c-string)
645          (with-pointer (,var ,c-string)
646            ,form))))
647    ((and (out-arg-p style) (not (in-arg-p style)))
648     `(with-pointer (,var)
649        ,form))))
650
651 (define-type-method alien-type ((type string))
652   (declare (ignore type))
653   (alien-type 'pointer))
654
655 (define-type-method size-of ((type string) &key inlined)
656   (assert-not-inlined type inlined)
657   (size-of 'pointer))
658
659 (define-type-method type-alignment ((type string) &key inlined)
660   (assert-not-inlined type inlined)
661   (type-alignment 'pointer))
662
663 (define-type-method to-alien-form ((type string) string &optional copy-p)
664   (declare (ignore type copy-p))
665   `(encode-utf8-string ,string))
666
667 (define-type-method to-alien-function ((type string) &optional copy-p)
668   (declare (ignore type))
669   (values
670    #'encode-utf8-string
671    (unless copy-p
672      #'(lambda (string c-string)
673          (declare (ignore string))
674          (deallocate-memory c-string)))))
675
676 (define-type-method from-alien-form ((type string) form &key (ref :free))
677   (declare (ignore type))
678   `(let ((c-string ,form))
679      (unless (null-pointer-p c-string)
680        (prog1
681            (decode-utf8-string c-string)
682          ,(when (eq ref :free)
683             `(deallocate-memory c-string))))))
684
685 (define-type-method from-alien-function ((type string) &key (ref :free))
686   (declare (ignore type))
687   (if (eq ref :free)
688       #'(lambda (c-string)
689           (unless (null-pointer-p c-string)
690             (prog1
691                 (decode-utf8-string c-string)
692               (deallocate-memory c-string))))
693     #'(lambda (c-string)
694         (unless (null-pointer-p c-string)
695           (decode-utf8-string c-string)))))
696
697 (define-type-method writer-function ((type string) &key temp inlined)
698   (declare (ignore temp))
699   (assert-not-inlined type inlined)
700   #'(lambda (string location &optional (offset 0))
701       (assert (null-pointer-p (ref-pointer location offset)))
702       (setf (ref-pointer location offset) (encode-utf8-string string))))
703
704 (define-type-method reader-function ((type string) &key (ref :read) inlined)
705   (assert-not-inlined type inlined)
706   (ecase ref
707     ((:read :peek)
708      #'(lambda (location &optional (offset 0))
709          (unless (null-pointer-p (ref-pointer location offset))
710            (decode-utf8-string (ref-pointer location offset)))))
711     (:get
712      #'(lambda (location &optional (offset 0))
713          (unless (null-pointer-p (ref-pointer location offset))
714            (prog1
715                (decode-utf8-string (ref-pointer location offset))
716              (deallocate-memory (ref-pointer location offset))
717              (setf (ref-pointer location offset) (make-pointer 0))))))))
718
719 (define-type-method destroy-function ((type string) &key temp inlined)
720   (declare (ignore temp))
721   (assert-not-inlined type inlined)
722   #'(lambda (location &optional (offset 0))
723       (unless (null-pointer-p (ref-pointer location offset))
724         (deallocate-memory (ref-pointer location offset))
725         (setf (ref-pointer location offset) (make-pointer 0)))))
726
727 (define-type-method copy-function ((type string) &key inlined)
728   (assert-not-inlined type inlined)  
729   (lambda (from to &optional (offset 0))
730     (let* ((string (ref-pointer from offset))
731            (length (loop
732                     for i from 0
733                     until (zerop (ref-byte string i))
734                     finally (return (1+ i)))))
735       (setf (ref-pointer to offset) (copy-memory string length)))))
736
737 (define-type-method unbound-value ((type string))
738   (declare (ignore type))
739   nil)
740
741
742
743 ;;; Pathname
744
745 (define-type-method alien-type ((type pathname))
746   (declare (ignore type))
747   (alien-type 'string))
748
749 (define-type-method size-of ((type pathname) &key inlined)
750   (assert-not-inlined type inlined)
751   (size-of 'string))
752
753 (define-type-method type-alignment ((type pathname) &key inlined)
754   (assert-not-inlined type inlined)
755   (type-alignment 'string))
756
757 (define-type-method alien-arg-wrapper ((type pathname) var pathname style form &optional copy-in-p)
758   (declare (ignore type))
759   (alien-arg-wrapper 'string var `(namestring (translate-logical-pathname ,pathname)) style form copy-in-p))
760
761 (define-type-method to-alien-form ((type pathname) path)
762   (declare (ignore type))
763   (to-alien-form 'string `(namestring (translate-logical-pathname ,path))))
764
765 (define-type-method to-alien-function ((type pathname) &optional copy-p)
766   (declare (ignore type))
767   (let ((string-function (to-alien-function 'string copy-p)))
768     #'(lambda (path)
769         (funcall string-function (namestring path)))))
770
771 (define-type-method from-alien-form ((type pathname) form &key (ref :free))
772   (declare (ignore type))
773   `(parse-namestring ,(from-alien-form 'string form :ref ref)))
774
775 (define-type-method from-alien-function ((type pathname) &key (ref :free))
776   (declare (ignore type))
777   (let ((string-function (from-alien-function 'string :ref ref)))
778     #'(lambda (string)
779         (parse-namestring (funcall string-function string)))))
780
781 (define-type-method writer-function ((type pathname) &key temp inlined)
782   (declare (ignore temp))
783   (assert-not-inlined type inlined)
784   (let ((string-writer (writer-function 'string)))
785     #'(lambda (path location &optional (offset 0))
786         (funcall string-writer (namestring path) location offset))))
787
788 (define-type-method reader-function ((type pathname) &key ref inlined)
789   (declare (ignore ref))
790   (assert-not-inlined type inlined)
791   (let ((string-reader (reader-function 'string)))
792   #'(lambda (location &optional (offset 0))
793       (let ((string (funcall string-reader location offset)))
794         (when string
795           (parse-namestring string))))))
796
797 (define-type-method destroy-function ((type pathname) &key temp inlined)
798   (declare (ignore temp))
799   (assert-not-inlined type inlined)
800   (destroy-function 'string))
801
802 (define-type-method copy-function ((type pathname) &key inlined)
803   (assert-not-inlined type inlined)
804   (copy-function 'string))
805
806 (define-type-method unbound-value ((type pathname))
807   (declare (ignore type))
808   (unbound-value 'string))
809
810
811
812 ;;; Bool
813
814 (define-type-method alien-type ((type bool))
815   (destructuring-bind (&optional (size '*))
816       (rest (mklist (type-expand-to 'bool type)))
817     (alien-type `(signed-byte ,size))))
818
819 (define-type-method size-of ((type bool) &key (inlined t))
820   (assert-inlined type inlined)
821   (destructuring-bind (&optional (size '*))
822       (rest (mklist (type-expand-to 'bool type)))
823     (size-of `(signed-byte ,size))))
824
825 (define-type-method type-alignment ((type bool) &key (inlined t))
826   (assert-inlined type inlined)
827   (destructuring-bind (&optional (size '*))
828       (rest (mklist (type-expand-to 'bool type)))
829     (type-alignment `(signed-byte ,size))))
830
831 (define-type-method to-alien-form ((type bool) bool &optional copy-p)
832   (declare (ignore type copy-p))
833   `(if ,bool 1 0))
834
835 (define-type-method to-alien-function ((type bool) &optional copy-p)
836   (declare (ignore type copy-p))
837   #'(lambda (bool)
838       (if bool 1 0)))
839
840 (define-type-method from-alien-form ((type bool) form &key ref)
841   (declare (ignore type ref))
842   `(not (zerop ,form)))
843
844 (define-type-method from-alien-function ((type bool) &key ref)
845   (declare (ignore type ref))
846   #'(lambda (bool)
847       (not (zerop bool))))
848
849 (define-type-method writer-function ((type bool) &key temp (inlined t))
850   (declare (ignore temp))
851   (assert-inlined type inlined)
852   (destructuring-bind (&optional (size '*))
853       (rest (mklist (type-expand-to 'bool type)))
854     (let ((writer (writer-function `(signed-byte ,size))))
855       #'(lambda (bool location &optional (offset 0))
856           (funcall writer (if bool 1 0) location offset)))))
857
858 (define-type-method reader-function ((type bool) &key ref (inlined t))
859   (declare (ignore ref))
860   (assert-inlined type inlined)
861   (destructuring-bind (&optional (size '*))
862       (rest (mklist (type-expand-to 'bool type)))
863     (let ((reader (reader-function `(signed-byte ,size))))
864       #'(lambda (location &optional (offset 0))
865           (not (zerop (funcall reader location offset)))))))
866
867
868
869 ;;; Boolean
870
871 (define-type-method alien-type ((type boolean))
872   (declare (ignore type))
873   (alien-type 'bool))
874
875 (define-type-method size-of ((type boolean) &key (inlined t))
876   (assert-inlined type inlined)
877   (size-of 'bool))
878
879 (define-type-method type-alignment ((type boolean) &key (inlined t))
880   (assert-inlined type inlined)
881   (type-alignment 'bool))
882
883 (define-type-method to-alien-form ((type boolean) boolean &optional copy-p)
884   (declare (ignore type copy-p))
885   (to-alien-form 'bool boolean))
886
887 (define-type-method to-alien-function ((type boolean) &optional copy-p)
888   (declare (ignore type copy-p))
889   (to-alien-function 'bool))
890
891 (define-type-method from-alien-form ((type boolean) form &key ref)
892   (declare (ignore type ref))
893   (from-alien-form 'bool form))
894
895 (define-type-method from-alien-function ((type boolean) &key ref)
896   (declare (ignore type ref))
897   (from-alien-function 'bool))
898
899 (define-type-method writer-function ((type boolean) &key temp (inlined t))
900   (declare (ignore temp))
901   (assert-inlined type inlined)
902   (writer-function 'bool))
903
904 (define-type-method reader-function ((type boolean) &key ref (inlined t))
905   (declare (ignore ref))
906   (assert-inlined type inlined)
907   (reader-function 'bool))
908
909
910 ;;; Or
911
912 (define-type-method alien-type ((type or))
913   (let* ((expanded-type (type-expand-to 'or type))
914          (alien-type (alien-type (second expanded-type))))
915     (unless (every #'(lambda (type)
916                        (eq alien-type (alien-type type)))
917                    (cddr expanded-type))
918       (error "No common alien type specifier for union type: ~A" type))
919     alien-type))
920
921 (define-type-method size-of ((type or) &key (inlined nil inlined-p))
922   (loop
923    for subtype in (type-expand-to 'or type)
924    maximize (if inlined-p
925                 (size-of subtype inlined)
926               (size-of subtype))))
927
928 (define-type-method type-alignment ((type or) &key (inlined nil inlined-p))
929   (loop
930    for subtype in (type-expand-to 'or type)
931    maximize (if inlined-p
932                 (type-alignment subtype inlined)
933               (type-alignment subtype))))
934
935 (define-type-method alien-arg-wrapper ((type or) var value style form &optional copy-in-p)
936   (cond 
937    ((and (in-arg-p style) (out-arg-p style))
938     `(etypecase ,value
939        ,@(mapcar         
940           #'(lambda (type)
941               `(,type ,(alien-arg-wrapper type var value style form copy-in-p)))
942           (rest (type-expand-to 'or type)))))
943    ((in-arg-p style)
944     (let ((body (make-symbol "BODY")))
945       `(flet ((,body (,var)
946                  ,form))
947          (etypecase ,value
948            ,@(mapcar     
949               #'(lambda (type)
950                   `(,type ,(alien-arg-wrapper type var value style `(,body ,var) copy-in-p)))
951               (rest (type-expand-to 'or type)))))))
952    ((out-arg-p style)
953     #+(or cmu sbcl)
954     `(with-alien ((,var ,(alien-type type)))
955        (clear-memory (alien-sap (addr ,var)) ,(size-of type))
956          ,form)
957     #+clisp
958     `(ffi:with-c-var (,var ',(alien-type type))
959        ,form))))
960
961 (define-type-method to-alien-form ((type or) form &optional copy-p)
962   `(let ((value ,form))
963      (etypecase value
964        ,@(mapcar         
965           #'(lambda (type)
966               `(,type ,(to-alien-form type 'value copy-p)))
967           (rest (type-expand-to 'or type))))))
968
969 (define-type-method to-alien-function ((type or) &optional copy-p)
970   (let* ((expanded-type (type-expand-to 'or type))
971          (functions (loop
972                      for type in (rest expanded-type)
973                      collect (to-alien-function type copy-p))))
974     #'(lambda (value)
975         (loop
976          for function in functions
977          for alt-type in (rest expanded-type)
978          when (typep value alt-type)
979          do (return (funcall function value))
980          finally (error "~S is not of type ~A" value type)))))
981
982
983 ;;; Pointer
984
985 (define-type-method alien-type ((type pointer))
986   (declare (ignore type))
987   #+(or cmu sbcl) 'system-area-pointer
988   #+clisp 'ffi:c-pointer)
989
990 (define-type-method size-of ((type pointer) &key (inlined t))
991   (assert-inlined type inlined)
992   #+sbcl (sb-sizeof 'sb-alien:system-area-pointer)
993   #+clisp (ffi:sizeof 'ffi:c-pointer)
994   #-(or sbcl clisp) 4)
995
996 (define-type-method type-alignment ((type pointer) &key (inlined t))
997   (assert-inlined type inlined)
998   #+sbcl (sb-alignment 'system-area-pointer)
999   #+clisp (ffi:sizeof 'ffi:c-pointer)
1000   #-(or sbcl clisp) (size-of 'pointer))
1001
1002 (define-type-method to-alien-form ((type pointer) form &optional copy-p)
1003   (declare (ignore type copy-p))
1004   form)
1005
1006 (define-type-method to-alien-function ((type pointer) &optional copy-p)
1007   (declare (ignore type copy-p))
1008   #'identity)
1009
1010 (define-type-method from-alien-form ((type pointer) form &key ref)
1011   (declare (ignore type ref))
1012   form)
1013
1014 (define-type-method from-alien-function ((type pointer) &key ref)
1015   (declare (ignore type ref))
1016   #'identity)
1017
1018 (define-type-method writer-function ((type pointer) &key temp (inlined t))
1019   (declare (ignore temp))
1020   (assert-inlined type inlined)
1021   #'(setf ref-pointer))
1022
1023 (define-type-method reader-function ((type pointer) &key ref (inlined t))
1024   (declare (ignore ref))
1025   (assert-inlined type inlined)
1026   #'ref-pointer)
1027
1028
1029 (define-type-method alien-type ((type null))
1030   (declare (ignore type))
1031   (alien-type 'pointer))
1032
1033 (define-type-method size-of ((type null) &key (inlined t))
1034   (assert-inlined type inlined)
1035   (size-of 'pointer))
1036
1037 (define-type-method to-alien-form ((type null) null &optional copy-p)
1038   (declare (ignore type copy-p))
1039   `(progn ,null (make-pointer 0)))
1040
1041 (define-type-method to-alien-function ((type null) &optional copy-p)
1042   (declare (ignore type copy-p))
1043   #'(lambda (null)
1044       (declare (ignore null))
1045       (make-pointer 0)))
1046
1047
1048 (define-type-method alien-type ((type nil))
1049   (declare (ignore type))
1050   #+(or cmu sbcl) 'void
1051   #+clisp nil)
1052
1053 (define-type-method from-alien-form ((type nil) form &key ref)
1054   (declare (ignore type ref))
1055   form)
1056
1057 (define-type-method from-alien-function ((type nil) &key ref)
1058   (declare (ignore type ref))
1059   #'(lambda (value)
1060       (declare (ignore value))
1061       (values)))
1062
1063 (define-type-method to-alien-form ((type nil) form &optional copy-p)
1064   (declare (ignore type copy-p))
1065   form)
1066
1067
1068
1069 ;;; Callbacks
1070
1071 (define-type-method alien-type ((type callback))
1072   (declare (ignore type))
1073   (alien-type 'pointer))
1074
1075 (define-type-method to-alien-form ((type callback) callback &optional copy-p)
1076   (declare (ignore type copy-p))
1077   `(callback-address ,callback))
1078
1079
1080
1081 ;;; Copy-of
1082
1083 (define-type-method from-alien-form ((type copy-of) form &key (ref :copy))
1084   (if (eq ref :copy)
1085       (from-alien-form (second (type-expand-to 'copy-of type)) form :ref ref)
1086     (error "Keyword arg :REF to FROM-ALIEN-FORM should be :COPY for type ~A. It was give ~A" type ref)))
1087
1088 (define-type-method from-alien-function ((type copy-of) &key (ref :copy))
1089   (if (eq ref :copy)
1090       (from-alien-function (second (type-expand-to 'copy-of type)) :ref ref)
1091     (error "Keyword arg :REF to FROM-ALIEN-FUNCTION should be :COPY for type ~A. It was give ~A" type ref)))
1092
1093 (define-type-method to-alien-form ((type copy-of) form &optional (copy-p t))
1094   (if copy-p
1095       (to-alien-form (second (type-expand-to 'copy-of type)) form t)
1096     (error "COPY-P argument to TO-ALIEN-FORM should always be non NIL for type ~A" type)))
1097
1098 (define-type-method to-alien-function ((type copy-of) &optional (copy-p t))
1099   (if copy-p
1100       (to-alien-function (second (type-expand-to 'copy-of type)) t)
1101     (error "COPY-P argument to TO-ALIEN-FUNCTION should always be non NIL for type ~A" type)))
1102
1103 (define-type-method reader-function ((type copy-of) &key (ref :read) (inlined nil inlined-p))
1104   (if inlined-p
1105       (reader-function (second (type-expand-to 'copy-of type)) 
1106        :ref (if (eq ref :get) :read ref) :inlined inlined)
1107     (reader-function (second (type-expand-to 'copy-of type))
1108      :ref (if (eq ref :get) :read ref))))
1109
1110 (define-type-method destroy-function ((type copy-of) &key temp inlined)
1111   (declare (ignore type temp inlined))
1112   #'(lambda (location &optional offset)
1113       (declare (ignore location offset))))
1114
1115 (define-type-method copy-function ((type copy-of) &key (inlined nil inlined-p))
1116   (let ((size (if inlined-p 
1117                   (size-of type :inlined inlined)
1118                 (size-of type))))
1119     #'(lambda (from to &optional (offset 0))
1120         (copy-memory (pointer+ from offset) size (pointer+ to offset)))))
1121
1122
1123
1124 ;;; Static
1125
1126 (define-type-method from-alien-form ((type static) form &key (ref :static))
1127   (if (eq ref :static)
1128       (from-alien-form (second (type-expand-to 'static type)) form :ref ref)
1129     (error "Keyword arg :REF to FROM-ALIEN-FORM should be :STATIC for type ~A. It was give ~A" type ref)))
1130
1131 (define-type-method from-alien-function ((type static) &key (ref :static))
1132   (if (eq ref :static)
1133       (from-alien-function (second (type-expand-to 'static type)) :ref ref)
1134     (error "Keyword arg :REF to FROM-ALIEN-FUNCTION should be :STATIC for type ~A. It was give ~A" type ref)))
1135
1136 (define-type-method to-alien-function ((type static) &optional copy-p)
1137   (if (not copy-p)
1138       (to-alien-function (second (type-expand-to 'static type)) t)
1139     (error "COPY-P argument to TO-ALIEN-FUNCTION should always be NIL for type ~A" type)))
1140
1141 (define-type-method to-alien-form ((type static) &optional copy-p)
1142   (if (not copy-p)
1143       (to-alien-form (second (type-expand-to 'static type)) t)
1144     (error "COPY-P argument to TO-ALIEN-FORM should always be NIL for type ~A" type)))
1145
1146 (define-type-method reader-function ((type static) &key (ref :read) (inlined nil inlined-p))
1147   (if inlined-p
1148       (reader-function (second (type-expand-to 'static type)) 
1149        :ref (if (eq ref :get) :read ref) :inlined inlined)
1150     (reader-function (second (type-expand-to 'static type))
1151      :ref (if (eq ref :get) :read ref))))
1152
1153 (define-type-method writer-function ((type static) &key temp inlined)
1154   (declare (ignore type temp inlined))
1155   (error "Can't overwrite a static (const) reference"))
1156
1157 (define-type-method destroy-function ((type static) &key temp inlined)
1158   (declare (ignore type temp inlined))
1159   #'(lambda (location &optional offset)
1160       (declare (ignore location offset))))
1161
1162 (define-type-method copy-function ((type static) &key (inlined nil inlined-p))
1163   (let ((size (if inlined-p 
1164                   (size-of type :inlined inlined)
1165                 (size-of type))))
1166     #'(lambda (from to &optional (offset 0))
1167         (copy-memory (pointer+ from offset) size (pointer+ to offset)))))
1168
1169
1170
1171 ;;; Pseudo type for inlining of types which are not inlined by default
1172
1173 (define-type-method size-of ((type inlined) &key (inlined t))
1174   (assert-inlined type inlined)
1175   (size-of (second (type-expand-to 'inlined type)) :inlined t))
1176
1177 (define-type-method type-alignment ((type inlined) &key (inlined t))
1178   (assert-inlined type inlined)
1179   (type-alignment (second (type-expand-to 'inlined type)) :inlined t))
1180
1181 (define-type-method reader-function ((type inlined) &key (ref :read) (inlined t))
1182   (assert-inlined type inlined)
1183   (reader-function (second (type-expand-to 'inlined type)) :ref ref :inlined t))
1184
1185 (define-type-method writer-function ((type inlined) &key temp (inlined t))
1186   (assert-inlined type inlined)
1187   (writer-function (second (type-expand-to 'inlined type)) :temp temp :inlined t))
1188
1189 (define-type-method destroy-function ((type inlined) &key temp (inlined t))
1190   (assert-inlined type inlined)
1191   (destroy-function (second (type-expand-to 'inlined type)) :temp temp :inlined t))
1192
1193 (define-type-method copy-function ((type inlined) &key (inlined t))
1194   (assert-inlined type inlined)
1195   (copy-function (second (type-expand-to 'inlined type)) :inlined t))