b309cf82fa34cce50a3e2fe2e94aff11e98ee5b3
[sbcl.git] / src / code / alpha-vm.lisp
1 ;;;; Alpha-specific implementation stuff
2
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.
11
12 (in-package "SB!VM")
13 \f
14 (defvar *number-of-signals* 64)
15 (defvar *bits-per-word* 64)
16
17 ;;; See x86-vm.lisp for a description of this.
18 (def-alien-type os-context-t (struct os-context-t-struct))
19 \f
20 ;;;; MACHINE-TYPE and MACHINE-VERSION
21
22 (defun machine-type ()
23   "Return a string describing the type of the local machine."
24   "Alpha")
25 (defun machine-version ()
26   "Return a string describing the version of the local machine."
27   "Alpha")
28 \f
29 (defun fixup-code-object (code offset value kind)
30   (unless (zerop (rem offset word-bytes))
31     (error "Unaligned instruction?  offset=#x~X." offset))
32   (sb!sys:without-gcing
33    (let ((sap (truly-the system-area-pointer
34                          (%primitive sb!kernel::code-instructions code))))
35      (ecase kind
36        (:jmp-hint
37         (assert (zerop (ldb (byte 2 0) value)))
38         #+nil
39         (setf (sap-ref-16 sap offset)
40               (logior (sap-ref-16 sap offset) (ldb (byte 14 0) (ash value -2)))))
41        (:bits-63-48
42         (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
43                (value (if (logbitp 31 value) (+ value (ash 1 32)) value))
44                (value (if (logbitp 47 value) (+ value (ash 1 48)) value)))
45           (setf (sap-ref-8 sap offset) (ldb (byte 8 48) value))
46           (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 56) value))))
47        (:bits-47-32
48         (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
49                (value (if (logbitp 31 value) (+ value (ash 1 32)) value)))
50           (setf (sap-ref-8 sap offset) (ldb (byte 8 32) value))
51           (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 40) value))))
52        (:ldah
53         (let ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)))
54           (setf (sap-ref-8 sap offset) (ldb (byte 8 16) value))
55           (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 24) value))))
56        (:lda
57         (setf (sap-ref-8 sap offset) (ldb (byte 8 0) value))
58         (setf (sap-ref-8 sap (1+ offset)) (ldb (byte 8 8) value)))))))
59 \f
60 ;;;; "Sigcontext" access functions, cut & pasted from x86-vm.lisp then
61 ;;;; hacked for types.
62 ;;;;
63 ;;;; KLUDGE: The alpha has 64-bit registers, so these potentially
64 ;;;; return 64 bit numbers (which means bignums ... ew) We think that
65 ;;;; 99 times of 100 (i.e. unless something is badly wrong) we'll get
66 ;;;; answers that fit in 32 bits anyway. Which probably won't help us
67 ;;;; stop passing bignums around as the compiler can't prove they fit
68 ;;;; in 32 bits. But maybe the stuff it does on x86 to unbox 32-bit
69 ;;;; constants happens magically for 64-bit constants here. Just
70 ;;;; maybe. -- Dan Barlow, ca. 2001-05-05
71 ;;;;
72 ;;;; See also x86-vm for commentary on signed vs unsigned.
73
74 (def-alien-routine ("os_context_pc_addr" context-pc-addr) (* unsigned-long)
75   (context (* os-context-t)))
76
77 (defun context-pc (context)
78   (declare (type (alien (* os-context-t)) context))
79   (int-sap (deref (context-pc-addr context))))
80
81 (def-alien-routine ("os_context_register_addr" context-register-addr)
82   (* unsigned-long)
83   (context (* os-context-t))
84   (index int))
85
86 ;;; FIXME: Should this and CONTEXT-PC be INLINE to reduce consing?
87 ;;; (Are they used in anything time-critical, or just the debugger?)
88 (defun context-register (context index)
89   (declare (type (alien (* os-context-t)) context))
90   (deref (context-register-addr context index)))
91
92 (defun %set-context-register (context index new)
93 (declare (type (alien (* os-context-t)) context))
94 (setf (deref (context-register-addr context index))
95       new))
96
97 ;;; This is like CONTEXT-REGISTER, but returns the value of a float
98 ;;; register. FORMAT is the type of float to return.
99
100 ;;; FIXME: Whether COERCE actually knows how to make a float out of a
101 ;;; long is another question. This stuff still needs testing.
102 (def-alien-routine ("os_context_fpregister_addr" context-float-register-addr)
103   (* long)
104   (context (* os-context-t))
105   (index int))
106 (defun context-float-register (context index format)
107   (declare (type (alien (* os-context-t)) context))
108   (coerce (deref (context-float-register-addr context index)) format))
109 (defun %set-context-float-register (context index format new)
110   (declare (type (alien (* os-context-t)) context))
111   (setf (deref (context-float-register-addr context index))
112         (coerce new format)))
113
114 ;;; Given a signal context, return the floating point modes word in
115 ;;; the same format as returned by FLOATING-POINT-MODES.
116 (defun context-floating-point-modes (context)
117   ;; FIXME: As of sbcl-0.6.7 and the big rewrite of signal handling for
118   ;; POSIXness and (at the Lisp level) opaque signal contexts,
119   ;; this is stubified. It needs to be rewritten as an
120   ;; alien function.
121   (warn "stub CONTEXT-FLOATING-POINT-MODES")
122
123   ;; old code for Linux:
124   #+nil
125   (let ((cw (slot (deref (slot context 'fpstate) 0) 'cw))
126         (sw (slot (deref (slot context 'fpstate) 0) 'sw)))
127     ;;(format t "cw = ~4X~%sw = ~4X~%" cw sw)
128     ;; NOT TESTED -- Clear sticky bits to clear interrupt condition.
129     (setf (slot (deref (slot context 'fpstate) 0) 'sw) (logandc2 sw #x3f))
130     ;;(format t "new sw = ~X~%" (slot (deref (slot context 'fpstate) 0) 'sw))
131     ;; Simulate floating-point-modes VOP.
132     (logior (ash (logand sw #xffff) 16) (logxor (logand cw #xffff) #x3f)))
133
134   0)
135 \f
136 ;;;; INTERNAL-ERROR-ARGUMENTS
137
138 ;;; Given a (POSIX) signal context, extract the internal error
139 ;;; arguments from the instruction stream.  This is e.g.
140 ;;; 4       23      254     240     2       0       0       0 
141 ;;; |       ~~~~~~~~~~~~~~~~~~~~~~~~~
142 ;;; length         data              (everything is an octet)
143 ;;;  (pc)
144 ;;; (example from undefined_tramp: "(gdb) x/40ub 0x10148" for yourself
145 ;;; to replicate)
146 (defun internal-error-arguments (context)
147   (declare (type (alien (* os-context-t)) context))
148   (sb!int::/show0 "entering INTERNAL-ERROR-ARGUMENTS")
149   (let ((pc (context-pc context)))
150     (declare (type system-area-pointer pc))
151     ;; pc is a SAP pointing at - or actually, shortly after -
152     ;; the instruction that got us into this mess in the first place
153     (let* ((length (sap-ref-8 pc 4))
154            (vector (make-array length :element-type '(unsigned-byte 8))))
155       (declare (type (unsigned-byte 8) length)
156                (type (simple-array (unsigned-byte 8) (*)) vector))
157       (copy-from-system-area pc (* sb!vm:byte-bits 5)
158                              vector (* sb!vm:word-bits
159                                        sb!vm:vector-data-offset)
160                              (* length sb!vm:byte-bits))
161       (let* ((index 0)
162              (error-number (sb!c::read-var-integer vector index)))
163         (collect ((sc-offsets))
164                  (loop
165                   (when (>= index length)
166                     (return))
167                   (sc-offsets (sb!c::read-var-integer vector index)))
168                  (values error-number (sc-offsets)))))))
169 \f
170 ;;; The loader uses this to convert alien names to the form they
171 ;;; occure in the symbol table (for example, prepending an
172 ;;; underscore). On the Alpha we don't do anything.
173 (defun extern-alien-name (name)
174   (declare (type simple-base-string name))
175   name)
176 \f
177 ;;;; Do whatever is necessary to make the given code component
178 ;;;; executable.
179 ;;;;
180 ;;;; XXX do we really not have to flush caches or something here? I
181 ;;;; need an architecture manual
182 (defun sanctify-for-execution (component)
183   (declare (ignore component))
184   nil)