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