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