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