Handle run-program with :directory nil.
[sbcl.git] / src / code / host-alieneval.lisp
1 ;;;; the part of the Alien implementation which is needed at
2 ;;;; cross-compilation time
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!ALIEN")
14
15 (/show0 "host-alieneval.lisp 15")
16 \f
17 ;;;; utility functions
18
19 (defun align-offset (offset alignment)
20   (let ((extra (rem offset alignment)))
21     (if (zerop extra) offset (+ offset (- alignment extra)))))
22
23 (defun guess-alignment (bits)
24   (cond ((null bits) nil)
25         #!-(or (and x86 (not win32)) (and ppc darwin)) ((> bits 32) 64)
26         ((> bits 16) 32)
27         ((> bits 8) 16)
28         ((> bits 1) 8)
29         (t 1)))
30 \f
31 ;;;; ALIEN-TYPE-INFO stuff
32
33 (eval-when (#-sb-xc :compile-toplevel :execute :load-toplevel)
34
35 (defstruct (alien-type-class (:copier nil))
36   (name nil :type symbol)
37   (defstruct-name nil :type symbol)
38   (include nil :type (or null alien-type-class))
39   (unparse nil :type (or null function))
40   (type= nil :type (or null function))
41   (lisp-rep nil :type (or null function))
42   (alien-rep nil :type (or null function))
43   (extract-gen nil :type (or null function))
44   (deposit-gen nil :type (or null function))
45   (naturalize-gen nil :type (or null function))
46   (deport-gen nil :type (or null function))
47   (deport-alloc-gen nil :type (or null function))
48   (deport-pin-p nil :type (or null function))
49   ;; Cast?
50   (arg-tn nil :type (or null function))
51   (result-tn nil :type (or null function))
52   (subtypep nil :type (or null function)))
53 (def!method print-object ((type-class alien-type-class) stream)
54   (print-unreadable-object (type-class stream :type t)
55     (prin1 (alien-type-class-name type-class) stream)))
56
57 (defun alien-type-class-or-lose (name)
58   (or (gethash name *alien-type-classes*)
59       (error "no alien type class ~S" name)))
60
61 (defun create-alien-type-class-if-necessary (name defstruct-name include)
62   (let ((old (gethash name *alien-type-classes*))
63         (include (and include (alien-type-class-or-lose include))))
64     (if old
65         (setf (alien-type-class-include old) include)
66         (setf (gethash name *alien-type-classes*)
67               (make-alien-type-class :name name
68                                      :defstruct-name defstruct-name
69                                      :include include)))))
70
71 (defparameter *method-slot-alist*
72   '((:unparse . alien-type-class-unparse)
73     (:type= . alien-type-class-type=)
74     (:subtypep . alien-type-class-subtypep)
75     (:lisp-rep . alien-type-class-lisp-rep)
76     (:alien-rep . alien-type-class-alien-rep)
77     (:extract-gen . alien-type-class-extract-gen)
78     (:deposit-gen . alien-type-class-deposit-gen)
79     (:naturalize-gen . alien-type-class-naturalize-gen)
80     (:deport-gen . alien-type-class-deport-gen)
81     (:deport-alloc-gen . alien-type-class-deport-alloc-gen)
82     (:deport-pin-p . alien-type-class-deport-pin-p)
83     ;; cast?
84     (:arg-tn . alien-type-class-arg-tn)
85     (:result-tn . alien-type-class-result-tn)))
86
87 (defun method-slot (method)
88   (cdr (or (assoc method *method-slot-alist*)
89            (error "no method ~S" method))))
90
91 ) ; EVAL-WHEN
92
93 ;;; We define a keyword "BOA" constructor so that we can reference the
94 ;;; slot names in init forms.
95 (def!macro define-alien-type-class ((name &key include include-args)
96                                     &rest slots)
97   (let ((defstruct-name (symbolicate "ALIEN-" name "-TYPE")))
98     (multiple-value-bind (include include-defstruct overrides)
99         (etypecase include
100           (null
101            (values nil 'alien-type nil))
102           (symbol
103            (values
104             include
105             (alien-type-class-defstruct-name
106              (alien-type-class-or-lose include))
107             nil))
108           (list
109            (values
110             (car include)
111             (alien-type-class-defstruct-name
112              (alien-type-class-or-lose (car include)))
113             (cdr include))))
114       `(progn
115          (eval-when (:compile-toplevel :load-toplevel :execute)
116            (create-alien-type-class-if-necessary ',name ',defstruct-name
117                                                  ',(or include 'root)))
118          (def!struct (,defstruct-name
119                         (:include ,include-defstruct
120                                   (class ',name)
121                                   ,@overrides)
122                         (:constructor
123                          ,(symbolicate "MAKE-" defstruct-name)
124                          (&key class bits alignment
125                                ,@(mapcar (lambda (x)
126                                            (if (atom x) x (car x)))
127                                          slots)
128                                ,@include-args
129                                ;; KLUDGE
130                                &aux (alignment (or alignment (guess-alignment bits))))))
131            ,@slots)))))
132
133 (def!macro define-alien-type-method ((class method) lambda-list &rest body)
134   (let ((defun-name (symbolicate class "-" method "-METHOD")))
135     `(progn
136        (defun ,defun-name ,lambda-list
137          ,@body)
138        (setf (,(method-slot method) (alien-type-class-or-lose ',class))
139              #',defun-name))))
140
141 (def!macro invoke-alien-type-method (method type &rest args)
142   (let ((slot (method-slot method)))
143     (once-only ((type type))
144       `(funcall (do ((class (alien-type-class-or-lose (alien-type-class ,type))
145                             (alien-type-class-include class)))
146                     ((null class)
147                      (error "method ~S not defined for ~S"
148                             ',method (alien-type-class ,type)))
149                   (let ((fn (,slot class)))
150                     (when fn
151                       (return fn))))
152                 ,type ,@args))))
153 \f
154 ;;;; type parsing and unparsing
155
156 ;;; CMU CL used COMPILER-LET to bind *AUXILIARY-TYPE-DEFINITIONS*, and
157 ;;; COMPILER-LET is no longer supported by ANSI or SBCL. Instead, we
158 ;;; follow the suggestion in CLTL2 of using SYMBOL-MACROLET to achieve
159 ;;; a similar effect.
160 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
161   (defun auxiliary-type-definitions (env)
162     (multiple-value-bind (result expanded-p)
163         (%macroexpand '&auxiliary-type-definitions& env)
164       (if expanded-p
165           result
166           ;; This is like having the global symbol-macro definition be
167           ;; NIL, but global symbol-macros make me vaguely queasy, so
168           ;; I do it this way instead.
169           nil))))
170
171 ;;; Process stuff in a new scope.
172 (def!macro with-auxiliary-alien-types (env &body body)
173   ``(symbol-macrolet ((&auxiliary-type-definitions&
174                        ,(append *new-auxiliary-types*
175                                 (auxiliary-type-definitions ,env))))
176       ,(let ((*new-auxiliary-types* nil))
177          ,@body)))
178
179 ;;; Parse TYPE as an alien type specifier and return the resultant
180 ;;; ALIEN-TYPE structure.
181 (defun parse-alien-type (type env)
182   (declare (type (or sb!kernel:lexenv null) env))
183   (if (consp type)
184       (let ((translator (info :alien-type :translator (car type))))
185         (unless translator
186           (error "unknown alien type: ~S" type))
187         (funcall translator type env))
188       (ecase (info :alien-type :kind type)
189         (:primitive
190          (let ((translator (info :alien-type :translator type)))
191            (unless translator
192              (error "no translator for primitive alien type ~S" type))
193            (funcall translator (list type) env)))
194         (:defined
195          (or (info :alien-type :definition type)
196              (error "no definition for alien type ~S" type)))
197         (:unknown
198          (error "unknown alien type: ~S" type)))))
199
200 (defun auxiliary-alien-type (kind name env)
201   (declare (type (or sb!kernel:lexenv null) env))
202   (flet ((aux-defn-matches (x)
203            (and (eq (first x) kind) (eq (second x) name))))
204     (let ((in-auxiliaries
205            (or (find-if #'aux-defn-matches *new-auxiliary-types*)
206                (find-if #'aux-defn-matches (auxiliary-type-definitions env)))))
207       (if in-auxiliaries
208           (values (third in-auxiliaries) t)
209           (ecase kind
210             (:struct
211              (info :alien-type :struct name))
212             (:union
213              (info :alien-type :union name))
214             (:enum
215              (info :alien-type :enum name)))))))
216
217 (defun (setf auxiliary-alien-type) (new-value kind name env)
218   (declare (type (or sb!kernel:lexenv null) env))
219   (flet ((aux-defn-matches (x)
220            (and (eq (first x) kind) (eq (second x) name))))
221     (when (find-if #'aux-defn-matches *new-auxiliary-types*)
222       (error "attempt to multiply define ~A ~S" kind name))
223     (when (find-if #'aux-defn-matches (auxiliary-type-definitions env))
224       (error "attempt to shadow definition of ~A ~S" kind name)))
225   (push (list kind name new-value) *new-auxiliary-types*)
226   new-value)
227
228 (defun verify-local-auxiliaries-okay ()
229   (dolist (info *new-auxiliary-types*)
230     (destructuring-bind (kind name defn) info
231       (declare (ignore defn))
232       (when (ecase kind
233               (:struct
234                (info :alien-type :struct name))
235               (:union
236                (info :alien-type :union name))
237               (:enum
238                (info :alien-type :enum name)))
239         (error "attempt to shadow definition of ~A ~S" kind name)))))
240
241 (defun unparse-alien-type (type)
242   #!+sb-doc
243   "Convert the alien-type structure TYPE back into a list specification of
244    the type."
245   (declare (type alien-type type))
246   (let ((*record-types-already-unparsed* nil))
247     (%unparse-alien-type type)))
248
249 ;;; Does all the work of UNPARSE-ALIEN-TYPE. It's separate because we
250 ;;; need to recurse inside the binding of
251 ;;; *RECORD-TYPES-ALREADY-UNPARSED*.
252 (defun %unparse-alien-type (type)
253   (invoke-alien-type-method :unparse type))
254 \f
255 ;;;; alien type defining stuff
256
257 (def!macro define-alien-type-translator (name lambda-list &body body)
258   (with-unique-names (whole env)
259     (let ((defun-name (symbolicate "ALIEN-" name "-TYPE-TRANSLATOR")))
260       (multiple-value-bind (body decls docs)
261           (sb!kernel:parse-defmacro lambda-list whole body name
262                                     'define-alien-type-translator
263                                     :environment env)
264         `(eval-when (:compile-toplevel :load-toplevel :execute)
265            (defun ,defun-name (,whole ,env)
266              (declare (ignorable ,env))
267              ,@decls
268              (block ,name
269                ,body))
270            (%define-alien-type-translator ',name #',defun-name ,docs))))))
271
272 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
273   (defun %define-alien-type-translator (name translator docs)
274     (declare (ignore docs))
275     (setf (info :alien-type :kind name) :primitive)
276     (setf (info :alien-type :translator name) translator)
277     (clear-info :alien-type :definition name)
278     #+nil
279     (setf (fdocumentation name 'alien-type) docs)
280     name))
281
282 (def!macro define-alien-type (name type &environment env)
283   #!+sb-doc
284   "Define the alien type NAME to be equivalent to TYPE. Name may be NIL for
285    STRUCT and UNION types, in which case the name is taken from the type
286    specifier."
287   (with-auxiliary-alien-types env
288     (let ((alien-type (parse-alien-type type env)))
289       `(eval-when (:compile-toplevel :load-toplevel :execute)
290          ,@(when *new-auxiliary-types*
291              `((%def-auxiliary-alien-types ',*new-auxiliary-types*)))
292          ,@(when name
293              `((%define-alien-type ',name ',alien-type)))))))
294
295 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
296   (defun %def-auxiliary-alien-types (types)
297     (dolist (info types)
298       ;; Clear up the type we're about to define from the toplevel
299       ;; *new-auxiliary-types* (local scopes take care of themselves).
300       ;; Unless this is done we never actually get back the full type
301       ;; from INFO, since the *new-auxiliary-types* have precendence.
302       (setf *new-auxiliary-types*
303             (remove info *new-auxiliary-types*
304                     :test (lambda (a b)
305                             (and (eq (first a) (first b))
306                                  (eq (second a) (second b))))))
307       (destructuring-bind (kind name defn) info
308         (macrolet ((frob (kind)
309                          `(let ((old (info :alien-type ,kind name)))
310                             (unless (or (null old) (alien-type-= old defn))
311                               (warn
312                                "redefining ~A ~S to be:~%  ~S,~%was:~%  ~S"
313                                kind name defn old))
314                             (setf (info :alien-type ,kind name) defn))))
315           (ecase kind
316             (:struct (frob :struct))
317             (:union (frob :union))
318             (:enum (frob :enum)))))))
319   (defun %define-alien-type (name new)
320     (ecase (info :alien-type :kind name)
321       (:primitive
322        (error "~S is a built-in alien type." name))
323       (:defined
324        (let ((old (info :alien-type :definition name)))
325          (unless (or (null old) (alien-type-= new old))
326            (warn "redefining ~S to be:~%  ~S,~%was~%  ~S"
327                  name
328                  (unparse-alien-type new)
329                  (unparse-alien-type old)))))
330       (:unknown))
331     (setf (info :alien-type :definition name) new)
332     (setf (info :alien-type :kind name) :defined)
333     name))
334 \f
335 ;;;; the root alien type
336
337 (eval-when (:compile-toplevel :load-toplevel :execute)
338   (create-alien-type-class-if-necessary 'root 'alien-type nil))
339
340 (def!struct (alien-type
341              (:make-load-form-fun sb!kernel:just-dump-it-normally)
342              (:constructor make-alien-type (&key class bits alignment
343                                             &aux (alignment (or alignment (guess-alignment bits))))))
344   (class 'root :type symbol)
345   (bits nil :type (or null unsigned-byte))
346   (alignment nil :type (or null unsigned-byte)))
347 (def!method print-object ((type alien-type) stream)
348   (print-unreadable-object (type stream :type t)
349     (prin1 (unparse-alien-type type) stream)))
350 \f
351 ;;;; the SAP type
352
353 (define-alien-type-class (system-area-pointer))
354
355 (define-alien-type-translator system-area-pointer ()
356   (make-alien-system-area-pointer-type
357    :bits #!-alpha sb!vm:n-word-bits #!+alpha 64))
358
359 (define-alien-type-method (system-area-pointer :unparse) (type)
360   (declare (ignore type))
361   'system-area-pointer)
362
363 (define-alien-type-method (system-area-pointer :lisp-rep) (type)
364   (declare (ignore type))
365   'system-area-pointer)
366
367 (define-alien-type-method (system-area-pointer :alien-rep) (type context)
368   (declare (ignore type context))
369   'system-area-pointer)
370
371 (define-alien-type-method (system-area-pointer :naturalize-gen) (type alien)
372   (declare (ignore type))
373   alien)
374
375 (define-alien-type-method (system-area-pointer :deport-gen) (type object)
376   (declare (ignore type))
377   (/noshow "doing alien type method SYSTEM-AREA-POINTER :DEPORT-GEN" object)
378   object)
379
380 (define-alien-type-method (system-area-pointer :extract-gen) (type sap offset)
381   (declare (ignore type))
382   `(sap-ref-sap ,sap (/ ,offset sb!vm:n-byte-bits)))
383 \f
384 ;;;; the ALIEN-VALUE type
385
386 (define-alien-type-class (alien-value :include system-area-pointer))
387
388 (define-alien-type-method (alien-value :lisp-rep) (type)
389   (declare (ignore type))
390   nil)
391
392 (define-alien-type-method (alien-value :naturalize-gen) (type alien)
393   `(%sap-alien ,alien ',type))
394
395 (define-alien-type-method (alien-value :deport-gen) (type value)
396   (declare (ignore type))
397   (/noshow "doing alien type method ALIEN-VALUE :DEPORT-GEN" value)
398   `(alien-sap ,value))
399 \f
400 ;;; HEAP-ALIEN-INFO -- defstruct.
401 ;;;
402 ;;; Information describing a heap-allocated alien.
403 (def!struct (heap-alien-info
404              (:make-load-form-fun sb!kernel:just-dump-it-normally))
405   ;; The type of this alien.
406   (type (missing-arg) :type alien-type)
407   ;; Its name.
408   (alien-name (missing-arg) :type simple-string)
409   ;; Data or code?
410   (datap (missing-arg) :type boolean))
411 (def!method print-object ((info heap-alien-info) stream)
412   (print-unreadable-object (info stream :type t)
413     (funcall (formatter "~S ~S~@[ (data)~]")
414              stream
415              (heap-alien-info-alien-name info)
416              (unparse-alien-type (heap-alien-info-type info))
417              (heap-alien-info-datap info))))
418
419 ;;; The form to evaluate to produce the SAP pointing to where in the heap
420 ;;; it is.
421 (defun heap-alien-info-sap-form (info)
422   `(foreign-symbol-sap ,(heap-alien-info-alien-name info)
423                        ,(heap-alien-info-datap info)))
424
425 (defun heap-alien-info-sap (info)
426   (foreign-symbol-sap (heap-alien-info-alien-name info)
427                       (heap-alien-info-datap info)))
428 \f
429 ;;;; Interfaces to the different methods
430
431 (defun alien-type-= (type1 type2)
432   #!+sb-doc
433   "Return T iff TYPE1 and TYPE2 describe equivalent alien types."
434   (or (eq type1 type2)
435       (and (eq (alien-type-class type1)
436                (alien-type-class type2))
437            (invoke-alien-type-method :type= type1 type2))))
438
439 (defun alien-subtype-p (type1 type2)
440   #!+sb-doc
441   "Return T iff the alien type TYPE1 is a subtype of TYPE2. Currently, the
442    only supported subtype relationships are is that any pointer type is a
443    subtype of (* t), and any array type first dimension will match
444    (array <eltype> nil ...). Otherwise, the two types have to be
445    ALIEN-TYPE-=."
446   (or (eq type1 type2)
447       (invoke-alien-type-method :subtypep type1 type2)))
448
449 (defun compute-naturalize-lambda (type)
450   `(lambda (alien ignore)
451      (declare (ignore ignore))
452      ,(invoke-alien-type-method :naturalize-gen type 'alien)))
453
454 (defun compute-deport-lambda (type)
455   (declare (type alien-type type))
456   (/noshow "entering COMPUTE-DEPORT-LAMBDA" type)
457   (multiple-value-bind (form value-type)
458       (invoke-alien-type-method :deport-gen type 'value)
459     `(lambda (value ignore)
460        (declare (type ,(or value-type
461                            (compute-lisp-rep-type type)
462                            `(alien ,type))
463                       value)
464                 (ignore ignore))
465        ,form)))
466
467 (defun compute-deport-alloc-lambda (type)
468   `(lambda (value ignore)
469      (declare (ignore ignore))
470      ,(invoke-alien-type-method :deport-alloc-gen type 'value)))
471
472 (defun compute-extract-lambda (type)
473   `(lambda (sap offset ignore)
474      (declare (type system-area-pointer sap)
475               (type unsigned-byte offset)
476               (ignore ignore))
477      (naturalize ,(invoke-alien-type-method :extract-gen type 'sap 'offset)
478                  ',type)))
479
480 (def!macro maybe-with-pinned-objects (variables types &body body)
481   (declare (ignorable variables types))
482   (let ((pin-variables
483          ;; Only pin things on GENCGC, since on CHENEYGC it'd imply
484          ;; disabling the GC.  Which is something we don't want to do
485          ;; every time we're calling to C.
486          #!+gencgc
487          (loop for variable in variables
488             for type in types
489             when (invoke-alien-type-method :deport-pin-p type)
490             collect variable)))
491     (if pin-variables
492         `(with-pinned-objects ,pin-variables
493            ,@body)
494         `(progn
495            ,@body))))
496
497 (defun compute-deposit-lambda (type)
498   (declare (type alien-type type))
499   `(lambda (value sap offset ignore)
500      (declare (type system-area-pointer sap)
501               (type unsigned-byte offset)
502               (ignore ignore))
503      (let ((alloc-tmp (deport-alloc value ',type)))
504        (maybe-with-pinned-objects (alloc-tmp) (,type)
505          (let ((value (deport alloc-tmp  ',type)))
506            ,(invoke-alien-type-method :deposit-gen type 'sap 'offset 'value)
507            ;; Note: the reason we don't just return the pre-deported value
508            ;; is because that would inhibit any (deport (naturalize ...))
509            ;; optimizations that might have otherwise happen. Re-naturalizing
510            ;; the value might cause extra consing, but is flushable, so probably
511            ;; results in better code.
512            (naturalize value ',type))))))
513
514 (defun compute-lisp-rep-type (type)
515   (invoke-alien-type-method :lisp-rep type))
516
517 ;;; CONTEXT is either :NORMAL (the default) or :RESULT (alien function
518 ;;; return values).  See the :ALIEN-REP method for INTEGER for
519 ;;; details.
520 (defun compute-alien-rep-type (type &optional (context :normal))
521   (invoke-alien-type-method :alien-rep type context))
522 \f
523 ;;;; default methods
524
525 (define-alien-type-method (root :unparse) (type)
526   `(<unknown-alien-type> ,(type-of type)))
527
528 (define-alien-type-method (root :type=) (type1 type2)
529   (declare (ignore type1 type2))
530   t)
531
532 (define-alien-type-method (root :subtypep) (type1 type2)
533   (alien-type-= type1 type2))
534
535 (define-alien-type-method (root :lisp-rep) (type)
536   (declare (ignore type))
537   nil)
538
539 (define-alien-type-method (root :alien-rep) (type context)
540   (declare (ignore type context))
541   '*)
542
543 (define-alien-type-method (root :naturalize-gen) (type alien)
544   (declare (ignore alien))
545   (error "cannot represent ~S typed aliens" type))
546
547 (define-alien-type-method (root :deport-gen) (type object)
548   (declare (ignore object))
549   (error "cannot represent ~S typed aliens" type))
550
551 (define-alien-type-method (root :deport-alloc-gen) (type object)
552   (declare (ignore type))
553   object)
554
555 (define-alien-type-method (root :deport-pin-p) (type)
556   (declare (ignore type))
557   ;; Override this method to return T for classes which take a SAP to a
558   ;; GCable lisp object when deporting.
559   nil)
560
561 (define-alien-type-method (root :extract-gen) (type sap offset)
562   (declare (ignore sap offset))
563   (error "cannot represent ~S typed aliens" type))
564
565 (define-alien-type-method (root :deposit-gen) (type sap offset value)
566   `(setf ,(invoke-alien-type-method :extract-gen type sap offset) ,value))
567
568 (define-alien-type-method (root :arg-tn) (type state)
569   (declare (ignore state))
570   (error "Aliens of type ~S cannot be passed as arguments to CALL-OUT."
571          (unparse-alien-type type)))
572
573 (define-alien-type-method (root :result-tn) (type state)
574   (declare (ignore state))
575   (error "Aliens of type ~S cannot be returned from CALL-OUT."
576          (unparse-alien-type type)))
577 \f
578 ;;;; the INTEGER type
579
580 (define-alien-type-class (integer)
581   (signed t :type (member t nil)))
582
583 (define-alien-type-translator signed (&optional (bits sb!vm:n-word-bits))
584   (make-alien-integer-type :bits bits))
585
586 (define-alien-type-translator integer (&optional (bits sb!vm:n-word-bits))
587   (make-alien-integer-type :bits bits))
588
589 (define-alien-type-translator unsigned (&optional (bits sb!vm:n-word-bits))
590   (make-alien-integer-type :bits bits :signed nil))
591
592 (define-alien-type-method (integer :unparse) (type)
593   (list (if (alien-integer-type-signed type) 'signed 'unsigned)
594         (alien-integer-type-bits type)))
595
596 (define-alien-type-method (integer :type=) (type1 type2)
597   (and (eq (alien-integer-type-signed type1)
598            (alien-integer-type-signed type2))
599        (= (alien-integer-type-bits type1)
600           (alien-integer-type-bits type2))))
601
602 (define-alien-type-method (integer :lisp-rep) (type)
603   (list (if (alien-integer-type-signed type) 'signed-byte 'unsigned-byte)
604         (alien-integer-type-bits type)))
605
606 (define-alien-type-method (integer :alien-rep) (type context)
607   ;; When returning integer values that are narrower than a machine
608   ;; register from a function, some platforms leave the higher bits of
609   ;; the register uninitialized.  On those platforms, we use an
610   ;; alien-rep of the full register width when checking for purposes
611   ;; of return values and override the naturalize method to perform
612   ;; the sign extension (in compiler/target/c-call.lisp).
613   (ecase context
614     ((:normal #!-(or x86 x86-64) :result)
615      (list (if (alien-integer-type-signed type) 'signed-byte 'unsigned-byte)
616            (alien-integer-type-bits type)))
617     #!+(or x86 x86-64)
618     (:result
619      (list (if (alien-integer-type-signed type) 'signed-byte 'unsigned-byte)
620            sb!vm:n-word-bits))))
621
622 ;;; As per the comment in the :ALIEN-REP method above, this is defined
623 ;;; elsewhere for x86oids.
624 #!-(or x86 x86-64)
625 (define-alien-type-method (integer :naturalize-gen) (type alien)
626   (declare (ignore type))
627   alien)
628
629 (define-alien-type-method (integer :deport-gen) (type value)
630   (declare (ignore type))
631   value)
632
633 (define-alien-type-method (integer :extract-gen) (type sap offset)
634   (declare (type alien-integer-type type))
635   (let ((ref-fun
636          (if (alien-integer-type-signed type)
637           (case (alien-integer-type-bits type)
638             (8 'signed-sap-ref-8)
639             (16 'signed-sap-ref-16)
640             (32 'signed-sap-ref-32)
641             (64 'signed-sap-ref-64))
642           (case (alien-integer-type-bits type)
643             (8 'sap-ref-8)
644             (16 'sap-ref-16)
645             (32 'sap-ref-32)
646             (64 'sap-ref-64)))))
647     (if ref-fun
648         `(,ref-fun ,sap (/ ,offset sb!vm:n-byte-bits))
649         (error "cannot extract ~W-bit integers"
650                (alien-integer-type-bits type)))))
651 \f
652 ;;;; the BOOLEAN type
653
654 (define-alien-type-class (boolean :include integer :include-args (signed)))
655
656 ;;; FIXME: Check to make sure that we aren't attaching user-readable
657 ;;; stuff to CL:BOOLEAN in any way which impairs ANSI compliance.
658 (define-alien-type-translator boolean (&optional (bits sb!vm:n-word-bits))
659   (make-alien-boolean-type :bits bits :signed nil))
660
661 (define-alien-type-method (boolean :unparse) (type)
662   `(boolean ,(alien-boolean-type-bits type)))
663
664 (define-alien-type-method (boolean :lisp-rep) (type)
665   (declare (ignore type))
666   `(member t nil))
667
668 (define-alien-type-method (boolean :naturalize-gen) (type alien)
669   (let ((bits (alien-boolean-type-bits type)))
670     (if (= bits sb!vm:n-word-bits)
671         `(not (zerop ,alien))
672         `(logtest ,alien ,(ldb (byte bits 0) -1)))))
673
674 (define-alien-type-method (boolean :deport-gen) (type value)
675   (declare (ignore type))
676   `(if ,value 1 0))
677 \f
678 ;;;; the ENUM type
679
680 (define-alien-type-class (enum :include (integer (bits 32))
681                                :include-args (signed))
682   name          ; name of this enum (if any)
683   from          ; alist from symbols to integers
684   to            ; alist or vector from integers to symbols
685   kind          ; kind of from mapping, :VECTOR or :ALIST
686   offset)       ; offset to add to value for :VECTOR from mapping
687
688 (define-alien-type-translator enum (&whole
689                                  type name
690                                  &rest mappings
691                                  &environment env)
692   (cond (mappings
693          (let ((result (parse-enum name mappings)))
694            (when name
695              (multiple-value-bind (old old-p)
696                  (auxiliary-alien-type :enum name env)
697                (when old-p
698                  (unless (alien-type-= result old)
699                    (cerror "Continue, clobbering the old definition"
700                            "Incompatible alien enum type definition: ~S" name)
701                    (setf (alien-type-from old) (alien-type-from result)
702                          (alien-type-to old) (alien-type-to result)
703                          (alien-type-kind old) (alien-type-kind result)
704                          (alien-type-offset old) (alien-type-offset result)
705                          (alien-type-signed old) (alien-type-signed result)))
706                  (setf result old))
707                (unless old-p
708                  (setf (auxiliary-alien-type :enum name env) result))))
709            result))
710         (name
711          (multiple-value-bind (result found)
712              (auxiliary-alien-type :enum name env)
713            (unless found
714              (error "unknown enum type: ~S" name))
715            result))
716         (t
717          (error "empty enum type: ~S" type))))
718
719 (defun parse-enum (name elements)
720   (when (null elements)
721     (error "An enumeration must contain at least one element."))
722   (let ((min nil)
723         (max nil)
724         (from-alist ())
725         (prev -1))
726     (declare (list from-alist))
727     (dolist (el elements)
728       (multiple-value-bind (sym val)
729           (if (listp el)
730               (values (first el) (second el))
731               (values el (1+ prev)))
732         (setf prev val)
733         (unless (symbolp sym)
734           (error "The enumeration element ~S is not a symbol." sym))
735         (unless (integerp val)
736           (error "The element value ~S is not an integer." val))
737         (unless (and max (> max val)) (setq max val))
738         (unless (and min (< min val)) (setq min val))
739         (when (rassoc val from-alist)
740           (style-warn "The element value ~S is used more than once." val))
741         (when (assoc sym from-alist :test #'eq)
742           (error "The enumeration element ~S is used more than once." sym))
743         (push (cons sym val) from-alist)))
744     (let* ((signed (minusp min))
745            (min-bits (if signed
746                          (1+ (max (integer-length min)
747                                   (integer-length max)))
748                          (integer-length max))))
749       (when (> min-bits 32)
750         (error "can't represent enums needing more than 32 bits"))
751       (setf from-alist (sort from-alist #'< :key #'cdr))
752       (cond
753        ;; If range is at least 20% dense, use vector mapping. Crossover
754        ;; point solely on basis of space would be 25%. Vector mapping
755        ;; is always faster, so give the benefit of the doubt.
756        ((< 0.2 (/ (float (length from-alist)) (float (1+ (- max min)))))
757         ;; If offset is small and ignorable, ignore it to save time.
758         (when (< 0 min 10) (setq min 0))
759         (let ((to (make-array (1+ (- max min)))))
760           (dolist (el from-alist)
761             (setf (svref to (- (cdr el) min)) (car el)))
762           (make-alien-enum-type :name name :signed signed
763                                 :from from-alist :to to :kind
764                                 :vector :offset (- min))))
765        (t
766         (make-alien-enum-type :name name :signed signed
767                               :from from-alist
768                               :to (mapcar (lambda (x) (cons (cdr x) (car x)))
769                                           from-alist)
770                               :kind :alist))))))
771
772 (define-alien-type-method (enum :unparse) (type)
773   `(enum ,(alien-enum-type-name type)
774          ,@(let ((prev -1))
775              (mapcar (lambda (mapping)
776                        (let ((sym (car mapping))
777                              (value (cdr mapping)))
778                          (prog1
779                              (if (= (1+ prev) value)
780                                  sym
781                                  `(,sym ,value))
782                            (setf prev value))))
783                      (alien-enum-type-from type)))))
784
785 (define-alien-type-method (enum :type=) (type1 type2)
786   (and (eq (alien-enum-type-name type1)
787            (alien-enum-type-name type2))
788        (equal (alien-enum-type-from type1)
789               (alien-enum-type-from type2))))
790
791 (define-alien-type-method (enum :lisp-rep) (type)
792   `(member ,@(mapcar #'car (alien-enum-type-from type))))
793
794 (define-alien-type-method (enum :naturalize-gen) (type alien)
795   (ecase (alien-enum-type-kind type)
796     (:vector
797      `(svref ',(alien-enum-type-to type)
798              (+ ,alien ,(alien-enum-type-offset type))))
799     (:alist
800      `(ecase ,alien
801         ,@(mapcar (lambda (mapping)
802                     `(,(car mapping) ',(cdr mapping)))
803                   (alien-enum-type-to type))))))
804
805 (define-alien-type-method (enum :deport-gen) (type value)
806   `(ecase ,value
807      ,@(mapcar (lambda (mapping)
808                  `(,(car mapping) ,(cdr mapping)))
809                (alien-enum-type-from type))))
810 \f
811 ;;;; the FLOAT types
812
813 (define-alien-type-class (float)
814   (type (missing-arg) :type symbol))
815
816 (define-alien-type-method (float :unparse) (type)
817   (alien-float-type-type type))
818
819 (define-alien-type-method (float :lisp-rep) (type)
820   (alien-float-type-type type))
821
822 (define-alien-type-method (float :alien-rep) (type context)
823   (declare (ignore context))
824   (alien-float-type-type type))
825
826 (define-alien-type-method (float :naturalize-gen) (type alien)
827   (declare (ignore type))
828   alien)
829
830 (define-alien-type-method (float :deport-gen) (type value)
831   (declare (ignore type))
832   value)
833
834 (define-alien-type-class (single-float :include (float (bits 32))
835                                        :include-args (type)))
836
837 (define-alien-type-translator single-float ()
838   (make-alien-single-float-type :type 'single-float))
839
840 (define-alien-type-method (single-float :extract-gen) (type sap offset)
841   (declare (ignore type))
842   `(sap-ref-single ,sap (/ ,offset sb!vm:n-byte-bits)))
843
844 (define-alien-type-class (double-float :include (float (bits 64))
845                                        :include-args (type)))
846
847 (define-alien-type-translator double-float ()
848   (make-alien-double-float-type :type 'double-float))
849
850 (define-alien-type-method (double-float :extract-gen) (type sap offset)
851   (declare (ignore type))
852   `(sap-ref-double ,sap (/ ,offset sb!vm:n-byte-bits)))
853
854 \f
855 ;;;; the POINTER type
856
857 (define-alien-type-class (pointer :include (alien-value (bits
858                                                          #!-alpha
859                                                          sb!vm:n-word-bits
860                                                          #!+alpha 64)))
861   (to nil :type (or alien-type null)))
862
863 (define-alien-type-translator * (to &environment env)
864   (make-alien-pointer-type :to (if (eq to t) nil (parse-alien-type to env))))
865
866 (define-alien-type-method (pointer :unparse) (type)
867   (let ((to (alien-pointer-type-to type)))
868     `(* ,(if to
869              (%unparse-alien-type to)
870              t))))
871
872 (define-alien-type-method (pointer :type=) (type1 type2)
873   (let ((to1 (alien-pointer-type-to type1))
874         (to2 (alien-pointer-type-to type2)))
875     (if to1
876         (if to2
877             (alien-type-= to1 to2)
878             nil)
879         (null to2))))
880
881 (define-alien-type-method (pointer :subtypep) (type1 type2)
882   (and (alien-pointer-type-p type2)
883        (let ((to1 (alien-pointer-type-to type1))
884              (to2 (alien-pointer-type-to type2)))
885          (if to1
886              (if to2
887                  (alien-subtype-p to1 to2)
888                  t)
889              (null to2)))))
890
891 (define-alien-type-method (pointer :deport-gen) (type value)
892   (/noshow "doing alien type method POINTER :DEPORT-GEN" type value)
893   (values
894    ;; FIXME: old version, highlighted a bug in xc optimization
895    `(etypecase ,value
896       (null
897        (int-sap 0))
898       (system-area-pointer
899        ,value)
900       ((alien ,type)
901        (alien-sap ,value)))
902    ;; new version, works around bug in xc optimization
903    #+nil
904    `(etypecase ,value
905       (system-area-pointer
906        ,value)
907       ((alien ,type)
908        (alien-sap ,value))
909       (null
910        (int-sap 0)))
911    `(or null system-area-pointer (alien ,type))))
912 \f
913 ;;;; the MEM-BLOCK type
914
915 (define-alien-type-class (mem-block :include alien-value))
916
917 (define-alien-type-method (mem-block :extract-gen) (type sap offset)
918   (declare (ignore type))
919   `(sap+ ,sap (truncate ,offset sb!vm:n-byte-bits)))
920
921 (define-alien-type-method (mem-block :deposit-gen) (type sap offset value)
922   (let ((bits (alien-mem-block-type-bits type)))
923     (unless bits
924       (error "can't deposit aliens of type ~S (unknown size)" type))
925     `(sb!kernel:system-area-ub8-copy ,value 0 ,sap
926       (truncate ,offset sb!vm:n-byte-bits)
927       ',(truncate bits sb!vm:n-byte-bits))))
928 \f
929 ;;;; the ARRAY type
930
931 (define-alien-type-class (array :include mem-block)
932   (element-type (missing-arg) :type alien-type)
933   (dimensions (missing-arg) :type list))
934
935 (define-alien-type-translator array (ele-type &rest dims &environment env)
936
937   (when dims
938     (unless (typep (first dims) '(or index null))
939       (error "The first dimension is not a non-negative fixnum or NIL: ~S"
940              (first dims)))
941     (let ((loser (find-if-not (lambda (x) (typep x 'index))
942                               (rest dims))))
943       (when loser
944         (error "A dimension is not a non-negative fixnum: ~S" loser))))
945
946   (let ((parsed-ele-type (parse-alien-type ele-type env)))
947     (make-alien-array-type
948      :element-type parsed-ele-type
949      :dimensions dims
950      :alignment (alien-type-alignment parsed-ele-type)
951      :bits (if (and (alien-type-bits parsed-ele-type)
952                     (every #'integerp dims))
953                (* (align-offset (alien-type-bits parsed-ele-type)
954                                 (alien-type-alignment parsed-ele-type))
955                   (reduce #'* dims))))))
956
957 (define-alien-type-method (array :unparse) (type)
958   `(array ,(%unparse-alien-type (alien-array-type-element-type type))
959           ,@(alien-array-type-dimensions type)))
960
961 (define-alien-type-method (array :type=) (type1 type2)
962   (and (equal (alien-array-type-dimensions type1)
963               (alien-array-type-dimensions type2))
964        (alien-type-= (alien-array-type-element-type type1)
965                      (alien-array-type-element-type type2))))
966
967 (define-alien-type-method (array :subtypep) (type1 type2)
968   (and (alien-array-type-p type2)
969        (let ((dim1 (alien-array-type-dimensions type1))
970              (dim2 (alien-array-type-dimensions type2)))
971          (and (= (length dim1) (length dim2))
972               (or (and dim2
973                        (null (car dim2))
974                        (equal (cdr dim1) (cdr dim2)))
975                   (equal dim1 dim2))
976               (alien-subtype-p (alien-array-type-element-type type1)
977                                (alien-array-type-element-type type2))))))
978 \f
979 ;;;; the RECORD type
980
981 (def!struct (alien-record-field
982              (:make-load-form-fun sb!kernel:just-dump-it-normally))
983   (name (missing-arg) :type symbol)
984   (type (missing-arg) :type alien-type)
985   (bits nil :type (or unsigned-byte null))
986   (offset 0 :type unsigned-byte))
987 (def!method print-object ((field alien-record-field) stream)
988   (print-unreadable-object (field stream :type t)
989     (format stream
990             "~S ~S~@[:~D~]"
991             (alien-record-field-type field)
992             (alien-record-field-name field)
993             (alien-record-field-bits field))))
994
995 (define-alien-type-class (record :include mem-block)
996   (kind :struct :type (member :struct :union))
997   (name nil :type (or symbol null))
998   (fields nil :type list))
999
1000 (define-alien-type-translator struct (name &rest fields &environment env)
1001   (parse-alien-record-type :struct name fields env))
1002
1003 (define-alien-type-translator union (name &rest fields &environment env)
1004   (parse-alien-record-type :union name fields env))
1005
1006 ;;; FIXME: This is really pretty horrible: we avoid creating new
1007 ;;; ALIEN-RECORD-TYPE objects when a live one is flitting around the
1008 ;;; system already. This way forward-references sans fields get
1009 ;;; "updated" for free to contain the field info. Maybe rename
1010 ;;; MAKE-ALIEN-RECORD-TYPE to %MAKE-ALIEN-RECORD-TYPE and use
1011 ;;; ENSURE-ALIEN-RECORD-TYPE instead. --NS 20040729
1012 (defun parse-alien-record-type (kind name fields env)
1013   (declare (type (or sb!kernel:lexenv null) env))
1014   (flet ((frob-type (type new-fields alignment bits)
1015            (setf (alien-record-type-fields type) new-fields
1016                  (alien-record-type-alignment type) alignment
1017                  (alien-record-type-bits type) bits)))
1018       (cond (fields
1019              (multiple-value-bind (new-fields alignment bits)
1020                  (parse-alien-record-fields kind fields env)
1021                (let* ((old (and name (auxiliary-alien-type kind name env)))
1022                       (old-fields (and old (alien-record-type-fields old))))
1023                  (when (and old-fields
1024                             (notevery #'record-fields-match-p old-fields new-fields))
1025                    (cerror "Continue, clobbering the old definition."
1026                            "Incompatible alien record type definition~%Old: ~S~%New: ~S"
1027                            (unparse-alien-type old)
1028                            `(,(unparse-alien-record-kind kind)
1029                               ,name
1030                               ,@(mapcar #'unparse-alien-record-field new-fields)))
1031                    (frob-type old new-fields alignment bits))
1032                  (if old-fields
1033                      old
1034                      (let ((type (or old (make-alien-record-type :name name :kind kind))))
1035                        (when (and name (not old))
1036                          (setf (auxiliary-alien-type kind name env) type))
1037                        (frob-type type new-fields alignment bits)
1038                        type)))))
1039             (name
1040              (or (auxiliary-alien-type kind name env)
1041                  (setf (auxiliary-alien-type kind name env)
1042                        (make-alien-record-type :name name :kind kind))))
1043             (t
1044              (make-alien-record-type :kind kind)))))
1045
1046 ;;; This is used by PARSE-ALIEN-TYPE to parse the fields of struct and union
1047 ;;; types. KIND is the kind we are paring the fields of, and FIELDS is the
1048 ;;; list of field specifications.
1049 ;;;
1050 ;;; Result is a list of field objects, overall alignment, and number of bits
1051 (defun parse-alien-record-fields (kind fields env)
1052   (declare (type list fields))
1053   (let ((total-bits 0)
1054         (overall-alignment 1)
1055         (parsed-fields nil))
1056     (dolist (field fields)
1057       (destructuring-bind (var type &key alignment bits offset) field
1058         (declare (ignore bits))
1059         (let* ((field-type (parse-alien-type type env))
1060                (bits (alien-type-bits field-type))
1061                (parsed-field
1062                 (make-alien-record-field :type field-type
1063                                          :name var)))
1064           (unless alignment
1065             (setf alignment (alien-type-alignment field-type)))
1066           (push parsed-field parsed-fields)
1067           (when (null bits)
1068             (error "unknown size: ~S" (unparse-alien-type field-type)))
1069           (when (null alignment)
1070             (error "unknown alignment: ~S" (unparse-alien-type field-type)))
1071           (setf overall-alignment (max overall-alignment alignment))
1072           (ecase kind
1073             (:struct
1074              (let ((offset (or offset (align-offset total-bits alignment))))
1075                (setf (alien-record-field-offset parsed-field) offset)
1076                (setf total-bits (+ offset bits))))
1077             (:union
1078              (setf total-bits (max total-bits bits)))))))
1079     (values (nreverse parsed-fields)
1080             overall-alignment
1081             (align-offset total-bits overall-alignment))))
1082
1083 (define-alien-type-method (record :unparse) (type)
1084   `(,(unparse-alien-record-kind (alien-record-type-kind type))
1085     ,(alien-record-type-name type)
1086     ,@(unless (member type *record-types-already-unparsed* :test #'eq)
1087         (push type *record-types-already-unparsed*)
1088         (mapcar #'unparse-alien-record-field
1089                 (alien-record-type-fields type)))))
1090
1091 (defun unparse-alien-record-kind (kind)
1092   (case kind
1093     (:struct 'struct)
1094     (:union 'union)
1095     (t '???)))
1096
1097 (defun unparse-alien-record-field (field)
1098   `(,(alien-record-field-name field)
1099      ,(%unparse-alien-type (alien-record-field-type field))
1100      ,@(when (alien-record-field-bits field)
1101              (list :bits (alien-record-field-bits field)))
1102      ,@(when (alien-record-field-offset field)
1103              (list :offset (alien-record-field-offset field)))))
1104
1105 ;;; Test the record fields. Keep a hashtable table of already compared
1106 ;;; types to detect cycles.
1107 (defun record-fields-match-p (field1 field2)
1108   (and (eq (alien-record-field-name field1)
1109            (alien-record-field-name field2))
1110        (eql (alien-record-field-bits field1)
1111             (alien-record-field-bits field2))
1112        (eql (alien-record-field-offset field1)
1113             (alien-record-field-offset field2))
1114        (alien-type-= (alien-record-field-type field1)
1115                      (alien-record-field-type field2))))
1116
1117 (defvar *alien-type-matches* nil
1118   "A hashtable used to detect cycles while comparing record types.")
1119
1120 (define-alien-type-method (record :type=) (type1 type2)
1121   (and (eq (alien-record-type-name type1)
1122            (alien-record-type-name type2))
1123        (eq (alien-record-type-kind type1)
1124            (alien-record-type-kind type2))
1125        (eql (alien-type-bits type1)
1126             (alien-type-bits type2))
1127        (eql (alien-type-alignment type1)
1128             (alien-type-alignment type2))
1129        (flet ((match-fields (&optional old)
1130                 (setf (gethash type1 *alien-type-matches*) (cons type2 old))
1131                 (every #'record-fields-match-p
1132                        (alien-record-type-fields type1)
1133                        (alien-record-type-fields type2))))
1134          (if *alien-type-matches*
1135              (let ((types (gethash type1 *alien-type-matches*)))
1136                (or (memq type2 types) (match-fields types)))
1137              (let ((*alien-type-matches* (make-hash-table :test #'eq)))
1138                (match-fields))))))
1139 \f
1140 ;;;; the FUNCTION and VALUES alien types
1141
1142 ;;; Calling-convention spec, typically one of predefined keywords.
1143 ;;; Add or remove as needed for target platform.  It makes sense to
1144 ;;; support :cdecl everywhere.
1145 ;;;
1146 ;;; Null convention is supposed to be platform-specific most-universal
1147 ;;; callout convention. For x86, SBCL calls foreign functions in a way
1148 ;;; allowing them to be either stdcall or cdecl; null convention is
1149 ;;; appropriate here, as it is for specifying callbacks that could be
1150 ;;; accepted by foreign code both in cdecl and stdcall form.
1151 (def!type calling-convention () `(or null (member :stdcall :cdecl)))
1152
1153 ;;; Convention could be a values type class, stored at result-type.
1154 ;;; However, it seems appropriate only for epilogue-related
1155 ;;; conventions, those not influencing incoming arg passing.
1156 ;;;
1157 ;;; As of x86's :stdcall and :cdecl, supported by now, both are
1158 ;;; epilogue-related, but future extensions (like :fastcall and
1159 ;;; miscellaneous non-x86 stuff) might affect incoming argument
1160 ;;; translation as well.
1161
1162 (define-alien-type-class (fun :include mem-block)
1163   (result-type (missing-arg) :type alien-type)
1164   (arg-types (missing-arg) :type list)
1165   (stub nil :type (or null function))
1166   (convention nil :type calling-convention))
1167
1168 ;;; KLUDGE: non-intrusive, backward-compatible way to allow calling
1169 ;;; convention specification for function types is unobvious.
1170 ;;;
1171 ;;; By now, `RESULT-TYPE' is allowed, but not required, to be a list
1172 ;;; starting with a convention keyword; its second item is a real
1173 ;;; result-type in this case. If convention is ever to become a part
1174 ;;; of result-type, such a syntax can be retained.
1175
1176 (define-alien-type-translator function (result-type &rest arg-types
1177                                                     &environment env)
1178   (multiple-value-bind (bare-result-type calling-convention)
1179       (typecase result-type
1180         ((cons calling-convention *)
1181            (values (second result-type) (first result-type)))
1182         (t result-type))
1183     (make-alien-fun-type
1184      :convention calling-convention
1185      :result-type (let ((*values-type-okay* t))
1186                     (parse-alien-type bare-result-type env))
1187      :arg-types (mapcar (lambda (arg-type) (parse-alien-type arg-type env))
1188                         arg-types))))
1189
1190 (define-alien-type-method (fun :unparse) (type)
1191   `(function ,(let ((result-type
1192                      (%unparse-alien-type (alien-fun-type-result-type type)))
1193                     (convention (alien-fun-type-convention type)))
1194                 (if convention (list convention result-type)
1195                     result-type))
1196              ,@(mapcar #'%unparse-alien-type
1197                        (alien-fun-type-arg-types type))))
1198
1199 (define-alien-type-method (fun :type=) (type1 type2)
1200   (and (alien-type-= (alien-fun-type-result-type type1)
1201                      (alien-fun-type-result-type type2))
1202        (eq (alien-fun-type-convention type1)
1203            (alien-fun-type-convention type2))
1204        (= (length (alien-fun-type-arg-types type1))
1205           (length (alien-fun-type-arg-types type2)))
1206        (every #'alien-type-=
1207               (alien-fun-type-arg-types type1)
1208               (alien-fun-type-arg-types type2))))
1209
1210 (define-alien-type-class (values)
1211   (values (missing-arg) :type list))
1212
1213 (define-alien-type-translator values (&rest values &environment env)
1214   (unless *values-type-okay*
1215     (error "cannot use values types here"))
1216   (let ((*values-type-okay* nil))
1217     (make-alien-values-type
1218      :values (mapcar (lambda (alien-type) (parse-alien-type alien-type env))
1219                      values))))
1220
1221 (define-alien-type-method (values :unparse) (type)
1222   `(values ,@(mapcar #'%unparse-alien-type
1223                      (alien-values-type-values type))))
1224
1225 (define-alien-type-method (values :type=) (type1 type2)
1226   (and (= (length (alien-values-type-values type1))
1227           (length (alien-values-type-values type2)))
1228        (every #'alien-type-=
1229               (alien-values-type-values type1)
1230               (alien-values-type-values type2))))
1231 \f
1232 ;;;; a structure definition needed both in the target and in the
1233 ;;;; cross-compilation host
1234
1235 ;;; information about local aliens. The WITH-ALIEN macro builds one of
1236 ;;; these structures and LOCAL-ALIEN and friends communicate
1237 ;;; information about how that local alien is represented.
1238 (def!struct (local-alien-info
1239              (:make-load-form-fun sb!kernel:just-dump-it-normally)
1240              (:constructor make-local-alien-info
1241                            (&key type force-to-memory-p
1242                             &aux (force-to-memory-p (or force-to-memory-p
1243                                                         (alien-array-type-p type)
1244                                                         (alien-record-type-p type))))))
1245   ;; the type of the local alien
1246   (type (missing-arg) :type alien-type)
1247   ;; Must this local alien be forced into memory? Using the ADDR macro
1248   ;; on a local alien will set this.
1249   (force-to-memory-p nil :type (member t nil)))
1250 (def!method print-object ((info local-alien-info) stream)
1251   (print-unreadable-object (info stream :type t)
1252     (format stream
1253             "~:[~;(forced to stack) ~]~S"
1254             (local-alien-info-force-to-memory-p info)
1255             (unparse-alien-type (local-alien-info-type info)))))
1256 \f
1257 ;;;; the ADDR macro
1258
1259 (defmacro-mundanely addr (expr &environment env)
1260   #!+sb-doc
1261   "Return an Alien pointer to the data addressed by Expr, which must be a call
1262    to SLOT or DEREF, or a reference to an Alien variable."
1263   (let ((form (%macroexpand expr env)))
1264     (or (typecase form
1265           (cons
1266            (case (car form)
1267              (slot
1268               (cons '%slot-addr (cdr form)))
1269              (deref
1270               (cons '%deref-addr (cdr form)))
1271              (%heap-alien
1272               (cons '%heap-alien-addr (cdr form)))
1273              (local-alien
1274               (let ((info (let ((info-arg (second form)))
1275                             (and (consp info-arg)
1276                                  (eq (car info-arg) 'quote)
1277                                  (second info-arg)))))
1278                 (unless (local-alien-info-p info)
1279                   (error "Something is wrong, LOCAL-ALIEN-INFO not found: ~S"
1280                          form))
1281                 (setf (local-alien-info-force-to-memory-p info) t))
1282               (cons '%local-alien-addr (cdr form)))))
1283           (symbol
1284            (let ((kind (info :variable :kind form)))
1285              (when (eq kind :alien)
1286                `(%heap-alien-addr ',(info :variable :alien-info form))))))
1287         (error "~S is not a valid L-value." form))))
1288
1289 (/show0 "host-alieneval.lisp end of file")