Make INFO's compiler-macro more forgiving.
[sbcl.git] / src / code / alpha-vm.lisp
bloba9c5939e5497157f81c71682254d8a7b0f449e4d
1 ;;;; Alpha-specific implementation stuff
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB!VM")
14 ;;; See x86-vm.lisp for a description of this.
15 (define-alien-type os-context-t (struct os-context-t-struct))
17 ;;;; MACHINE-TYPE
19 (defun machine-type ()
20 "Return a string describing the type of the local machine."
21 "Alpha")
23 (defun fixup-code-object (code offset value kind)
24 (unless (zerop (rem offset n-word-bytes))
25 (error "Unaligned instruction? offset=#x~X." offset))
26 (without-gcing
27 (let ((sap (%primitive code-instructions code)))
28 (ecase kind
29 (:jmp-hint
30 (aver (zerop (ldb (byte 2 0) value)))
31 #+nil
32 (setf (sap-ref-16 sap offset)
33 (logior (sap-ref-16 sap offset)
34 (ldb (byte 14 0) (ash value -2)))))
35 (:bits-63-48
36 (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
37 (value (if (logbitp 31 value) (+ value (ash 1 32)) value))
38 (value (if (logbitp 47 value) (+ value (ash 1 48)) value)))
39 (setf (sap-ref-8 sap offset) (ldb (byte 8 48) value))
40 (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 56) value))))
41 (:bits-47-32
42 (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
43 (value (if (logbitp 31 value) (+ value (ash 1 32)) value)))
44 (setf (sap-ref-8 sap offset) (ldb (byte 8 32) value))
45 (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 40) value))))
46 (:ldah
47 (let ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)))
48 (setf (sap-ref-8 sap offset) (ldb (byte 8 16) value))
49 (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 24) value))))
50 (:lda
51 (setf (sap-ref-8 sap offset) (ldb (byte 8 0) value))
52 (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 8) value)))))))
54 ;;;; "sigcontext" access functions, cut & pasted from x86-vm.lisp then
55 ;;;; hacked for types.
56 ;;;;
57 ;;;; KLUDGE: The alpha has 64-bit registers, so these potentially
58 ;;;; return 64 bit numbers (which means bignums ... ew) We think that
59 ;;;; 99 times of 100 (i.e. unless something is badly wrong) we'll get
60 ;;;; answers that fit in 32 bits anyway. Which probably won't help us
61 ;;;; stop passing bignums around as the compiler can't prove they fit
62 ;;;; in 32 bits. But maybe the stuff it does on x86 to unbox 32-bit
63 ;;;; constants happens magically for 64-bit constants here. Just
64 ;;;; maybe. -- Dan Barlow, ca. 2001-05-05
65 ;;;;
66 ;;;; See also x86-vm for commentary on signed vs unsigned.
68 (define-alien-routine ("os_context_pc_addr" context-pc-addr) (* unsigned-long)
69 (context (* os-context-t)))
71 (defun context-pc (context)
72 (declare (type (alien (* os-context-t)) context))
73 (int-sap (deref (context-pc-addr context))))
75 (define-alien-routine ("os_context_register_addr" context-register-addr)
76 (* unsigned-long)
77 (context (* os-context-t))
78 (index int))
80 ;;; FIXME: Should this and CONTEXT-PC be INLINE to reduce consing?
81 ;;; (Are they used in anything time-critical, or just the debugger?)
82 (defun context-register (context index)
83 (declare (type (alien (* os-context-t)) context))
84 (deref (the (alien (* unsigned-long))
85 (context-register-addr context index))))
87 (defun %set-context-register (context index new)
88 (declare (type (alien (* os-context-t)) context))
89 (setf (deref (the (alien (* unsigned-long))
90 (context-register-addr context index)))
91 new))
93 ;;; This is like CONTEXT-REGISTER, but returns the value of a float
94 ;;; register. FORMAT is the type of float to return.
96 ;;; FIXME: Whether COERCE actually knows how to make a float out of a
97 ;;; long is another question. This stuff still needs testing.
98 (define-alien-routine ("os_context_float_register_addr"
99 context-float-register-addr)
100 (* long)
101 (context (* os-context-t))
102 (index int))
103 (defun context-float-register (context index format)
104 (declare (type (alien (* os-context-t)) context))
105 (coerce (deref (context-float-register-addr context index)) format))
106 (defun %set-context-float-register (context index format new)
107 (declare (type (alien (* os-context-t)) context))
108 (setf (deref (context-float-register-addr context index))
109 (coerce new format)))
111 ;;; This sets the software fp_control word, which is not the same
112 ;;; thing as the hardware fpcr. We have to do this so that OS FPU
113 ;;; completion works properly
115 ;;; Note that this means we can't set rounding modes; we'd have to do
116 ;;; that separately. That said, almost everybody seems to agree that
117 ;;; changing the rounding mode is rarely a good idea, because it upsets
118 ;;; libm functions. So adding that is not a priority. Sorry.
119 ;;; -dan 2001.02.06
121 (define-alien-routine
122 ("arch_get_fp_control" floating-point-modes) (unsigned 64))
124 (define-alien-routine
125 ("arch_set_fp_control" %floating-point-modes-setter) void (fp (unsigned 64)))
127 (defun (setf floating-point-modes) (val) (%floating-point-modes-setter val))
129 ;;; Given a signal context, return the floating point modes word in
130 ;;; the same format as returned by FLOATING-POINT-MODES.
131 (define-alien-routine ("os_context_fp_control" context-floating-point-modes)
132 (unsigned 64) (context (* os-context-t)))
135 ;;;; INTERNAL-ERROR-ARGS
137 ;;; Given a (POSIX) signal context, extract the internal error
138 ;;; arguments from the instruction stream. This is e.g.
139 ;;; 4 23 254 240 2 0 0 0
140 ;;; | ~~~~~~~~~~~~~~~~~~~~~~~~~
141 ;;; length data (everything is an octet)
142 ;;; (pc)
143 ;;; (example from undefined_tramp: "(gdb) x/40ub 0x10148" for yourself
144 ;;; to replicate)
145 (defun internal-error-args (context)
146 (declare (type (alien (* os-context-t)) context))
147 (let ((pc (context-pc context)))
148 (declare (type system-area-pointer pc))
149 ;; pc is a SAP pointing at - or actually, shortly after -
150 ;; the instruction that got us into this mess in the first place
151 (let* ((length (sap-ref-8 pc 4))
152 (vector (make-array length :element-type '(unsigned-byte 8))))
153 (declare (type (unsigned-byte 8) length)
154 (type (simple-array (unsigned-byte 8) (*)) vector))
155 (copy-ub8-from-system-area pc 5 vector 0 length)
156 (let* ((index 0)
157 (error-number (sb!c:read-var-integer vector index)))
158 (collect ((sc-offsets))
159 (loop
160 (when (>= index length)
161 (return))
162 (sc-offsets (sb!c:read-var-integer vector index)))
163 (values error-number (sc-offsets)))))))