compiler/arm/insts: Implement disassembly of data-processing instructions.
[sbcl/nyef.git] / src / compiler / arm / insts.lisp
blob3822311fe218956f65bbc0f8afc2c1d1497fcdcd
1 ;;;; that part of the description of the ARM instruction set (for
2 ;;;; ARMv5) which can live on the cross-compilation host
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.
13 (in-package "SB!VM")
14 ;;; FIXME: SB!DISASSEM: prefixes are used so widely in this file that
15 ;;; I wonder whether the separation of the disassembler from the
16 ;;; virtual machine is valid or adds value.
18 ;;; Note: In CMU CL, this used to be a call to SET-DISASSEM-PARAMS.
19 (setf sb!disassem:*disassem-inst-alignment-bytes* 4)
22 (defparameter *conditions*
23 '((:eq . 0)
24 (:ne . 1)
25 (:cs . 2) (:hs . 2)
26 (:cc . 3) (:lo . 3)
27 (:mi . 4)
28 (:pl . 5)
29 (:vs . 6)
30 (:vc . 7)
31 (:hi . 8)
32 (:ls . 9)
33 (:ge . 10)
34 (:lt . 11)
35 (:gt . 12)
36 (:le . 13)
37 (:al . 14)))
38 (defparameter *condition-name-vec*
39 (let ((vec (make-array 16 :initial-element nil)))
40 (dolist (cond *conditions*)
41 (when (null (aref vec (cdr cond)))
42 (setf (aref vec (cdr cond)) (car cond))))
43 vec))
45 ;;; Set assembler parameters. (In CMU CL, this was done with
46 ;;; a call to a macro DEF-ASSEMBLER-PARAMS.)
47 (eval-when (:compile-toplevel :load-toplevel :execute)
48 (setf sb!assem:*assem-scheduler-p* nil))
50 (defun conditional-opcode (condition)
51 (cdr (assoc condition *conditions* :test #'eq)))
53 ;;;; disassembler field definitions
55 (eval-when (:compile-toplevel :load-toplevel :execute)
56 ;; DEFINE-ARG-TYPE requires that any :PRINTER be defined at
57 ;; compile-time... Why?
59 (defun print-condition (value stream dstate)
60 (declare (type stream stream)
61 (fixnum value)
62 (ignore dstate))
63 (unless (= value 14) ;; Don't print :al
64 (princ (aref *condition-name-vec* value) stream)))
66 (defun print-reg (value stream dstate)
67 (declare (type stream stream)
68 (fixnum value)
69 (ignore dstate))
70 (princ (aref *register-names* value) stream))
72 (defun print-shift-type (value stream dstate)
73 (declare (type stream stream)
74 (fixnum value)
75 (ignore dstate))
76 (princ (aref #(lsl lsr asr ror) value) stream))
78 (defun print-immediate-shift (value stream dstate)
79 (declare (type stream stream)
80 (type (cons fixnum (cons fixnum null)))
81 (ignore dstate))
82 (destructuring-bind (amount shift) value
83 (cond
84 ((and (zerop amount)
85 (zerop shift))
86 ;; No shift
88 ((and (zerop amount)
89 (= shift 3))
90 (princ ", RRX" stream))
92 (princ ", " stream)
93 (princ (aref #(lsl lsr asr ror) shift) stream)
94 (princ " #" stream)
95 (princ amount stream)))))
97 (defun print-shifter-immediate (value stream dstate)
98 (declare (type stream stream)
99 (fixnum value)
100 (ignore dstate))
101 (let* ((rotate (ldb (byte 4 8) value))
102 (immediate (mask-field (byte 8 0) value))
103 (left (mask-field (byte 32 0)
104 (ash immediate (- 32 rotate rotate))))
105 (right (ash immediate (- 0 rotate rotate))))
106 (princ (logior left right) stream)))
107 ) ; EVAL-WHEN
109 (sb!disassem:define-arg-type condition-code
110 :printer #'print-condition)
112 (sb!disassem:define-arg-type reg
113 :printer #'print-reg)
115 (sb!disassem:define-arg-type shift-type
116 :printer #'print-shift-type)
118 (sb!disassem:define-arg-type immediate-shift
119 :printer #'print-immediate-shift)
121 (sb!disassem:define-arg-type shifter-immediate
122 :printer #'print-shifter-immediate)
124 ;;;; disassembler instruction format definitions
126 (sb!disassem:define-instruction-format
127 (dp-shift-immediate 32
128 :default-printer '(:name cond :tab rd ", " rn ", " rm shift))
129 (cond :field (byte 4 28) :type 'condition-code)
130 (opcode-8 :field (byte 8 20))
131 (rn :field (byte 4 16) :type 'reg)
132 (rd :field (byte 4 12) :type 'reg)
133 (shift :fields (list (byte 5 7) (byte 2 5)) :type 'immediate-shift)
134 (register-shift-p :field (byte 1 4) :value 0)
135 (rm :field (byte 4 0) :type 'reg))
137 (sb!disassem:define-instruction-format
138 (dp-shift-register 32
139 :default-printer '(:name cond :tab rd ", " rn ", " rm ", " shift-type " " rs))
140 (cond :field (byte 4 28) :type 'condition-code)
141 (opcode-8 :field (byte 8 20))
142 (rn :field (byte 4 16) :type 'reg)
143 (rd :field (byte 4 12) :type 'reg)
144 (rs :field (byte 4 8) :type 'reg)
145 (multiply-p :field (byte 1 7) :value 0)
146 (shift-type :field (byte 2 5) :type 'shift-type)
147 (register-shift-p :field (byte 1 4) :value 1)
148 (rm :field (byte 4 0) :type 'reg))
150 (sb!disassem:define-instruction-format
151 (dp-immediate 32
152 :default-printer '(:name cond :tab rd ", " rn ", #" immediate))
153 (cond :field (byte 4 28) :type 'condition-code)
154 (opcode-8 :field (byte 8 20))
155 (rn :field (byte 4 16) :type 'reg)
156 (rd :field (byte 4 12) :type 'reg)
157 (immediate :field (byte 12 0) :type 'shifter-immediate))
159 ;;;; primitive emitters
161 ;(define-bitfield-emitter emit-word 16
162 ; (byte 16 0))
164 (define-bitfield-emitter emit-word 32
165 (byte 32 0))
167 ;;;; fixup emitters
169 (defun emit-absolute-fixup (segment fixup)
170 (note-fixup segment :absolute fixup)
171 (let ((offset (fixup-offset fixup)))
172 (if (label-p offset)
173 (emit-back-patch segment
174 4 ; FIXME: n-word-bytes
175 (lambda (segment posn)
176 (declare (ignore posn))
177 (emit-dword segment
178 (- (+ (component-header-length)
179 (or (label-position offset)
181 other-pointer-lowtag))))
182 (emit-dword segment (or offset 0)))))
184 (defun emit-relative-fixup (segment fixup)
185 (note-fixup segment :relative fixup)
186 (emit-dword segment (or (fixup-offset fixup) 0)))
189 ;;;; miscellaneous hackery
191 (defun register-p (thing)
192 (and (tn-p thing)
193 (eq (sb-name (sc-sb (tn-sc thing))) 'registers)))
195 (defmacro with-condition-defaulted ((argvar arglist) &body body)
196 (let ((internal-emitter (gensym)))
197 `(flet ((,internal-emitter ,arglist
198 ,@body))
199 (if (assoc (car ,argvar) *conditions*)
200 (apply #',internal-emitter ,argvar)
201 (apply #',internal-emitter :al ,argvar)))))
203 (define-instruction byte (segment byte)
204 (:emitter
205 (emit-byte segment byte)))
207 ;(define-instruction word (segment word)
208 ; (:emitter
209 ; (emit-word segment word)))
211 (define-instruction word (segment word)
212 (:emitter
213 (etypecase word
214 (fixup
215 (note-fixup segment :absolute word)
216 (emit-word segment 0))
217 (integer
218 (emit-word segment word)))))
220 (defun emit-header-data (segment type)
221 (emit-back-patch segment
223 (lambda (segment posn)
224 (emit-word segment
225 (logior type
226 (ash (+ posn
227 (component-header-length))
228 (- n-widetag-bits
229 word-shift)))))))
231 (define-instruction simple-fun-header-word (segment)
232 (:emitter
233 (emit-header-data segment simple-fun-header-widetag)))
235 (define-instruction lra-header-word (segment)
236 (:emitter
237 (emit-header-data segment return-pc-header-widetag)))
239 ;;;; Addressing mode 1 support
241 ;;; Addressing mode 1 has some 11 formats. These are immediate,
242 ;;; register, and nine shift/rotate functions based on one or more
243 ;;; registers. As the mnemonics used for these functions are not
244 ;;; currently used, we simply define them as constructors for a
245 ;;; shifter-operand structure, similar to the make-ea function in the
246 ;;; x86 backend.
248 (defstruct shifter-operand
249 register
250 function-code
251 operand)
253 (defun lsl (register operand)
254 (aver (register-p register))
255 (aver (or (register-p operand)
256 (typep operand '(integer 0 31))))
258 (make-shifter-operand :register register :function-code 0 :operand operand))
260 (defun lsr (register operand)
261 (aver (register-p register))
262 (aver (or (register-p operand)
263 (typep operand '(integer 1 32))))
265 (make-shifter-operand :register register :function-code 1 :operand operand))
267 (defun asr (register operand)
268 (aver (register-p register))
269 (aver (or (register-p operand)
270 (typep operand '(integer 1 32))))
272 (make-shifter-operand :register register :function-code 2 :operand operand))
274 (defun ror (register operand)
275 ;; ROR is a special case: the encoding for ROR with an immediate
276 ;; shift of 32 (0) is actually RRX.
277 (aver (register-p register))
278 (aver (or (register-p operand)
279 (typep operand '(integer 1 31))))
281 (make-shifter-operand :register register :function-code 3 :operand operand))
283 (defun rrx (register)
284 ;; RRX is a special case: it is encoded as ROR with an immediate
285 ;; shift of 32 (0), and has no operand.
286 (aver (register-p register))
288 (make-shifter-operand :register register :function-code 3 :operand 0))
290 (define-condition cannot-encode-immediate-operand (error)
291 ((value :initarg value)))
293 (defun encode-shifter-immediate (operand)
294 ;; 32-bit immediate data is encoded as an 8-bit immediate data value
295 ;; and a 4-bit immediate shift count. The actual value is the
296 ;; immediate data rotated right by a number of bits equal to twice
297 ;; the shift count. Note that this means that there are a limited
298 ;; number of valid immediate integers and that some integers have
299 ;; multiple possible encodings. In the case of multiple encodings,
300 ;; the correct one to use is the one with the lowest shift count.
302 ;; XXX: Is it possible to determine the correct encoding in constant
303 ;; time, rather than time proportional to the final shift count? Is
304 ;; it possible to determine if a given integer is valid without
305 ;; attempting to encode it? Are such solutions cheaper (either time
306 ;; or spacewise) than simply attempting to encode it?
307 (labels ((try-immediate-encoding (value shift)
308 (unless (<= 0 shift 15)
309 (error 'cannot-encode-immediate-operand :value operand))
310 (if (typep value '(unsigned-byte 8))
311 (dpb shift (byte 4 8) value)
312 (try-immediate-encoding (dpb value (byte 30 2)
313 (ldb (byte 2 30) value))
314 (1+ shift)))))
315 (try-immediate-encoding operand 0)))
317 (defun encode-shifter-operand (operand)
318 (etypecase operand
319 (integer
320 (dpb 1 (byte 1 25) (encode-shifter-immediate operand)))
323 (cond
324 ((eq 'registers (sb-name (sc-sb (tn-sc operand))))
325 ;; For those wondering, this is LSL immediate for 0 bits.
326 (tn-offset operand))
328 ((eq 'null (sc-name (tn-sc operand)))
329 null-offset)
331 (t (error "Don't know how to encode TN ~A as a SHIFTER-OPERAND" operand))))
333 (shifter-operand
334 (let ((Rm (tn-offset (shifter-operand-register operand)))
335 (shift-code (shifter-operand-function-code operand))
336 (shift-amount (shifter-operand-operand operand)))
337 (etypecase shift-amount
338 (integer
339 (dpb shift-amount (byte 5 7)
340 (dpb shift-code (byte 2 5)
341 Rm)))
343 (dpb (tn-offset shift-amount) (byte 4 8)
344 (dpb shift-code (byte 2 5)
345 (dpb 1 (byte 1 4)
346 Rm)))))))))
348 (defmacro composite-immediate-instruction (op r x y &key fixnumize neg-op invert-y invert-r single-op-op first-op first-no-source)
349 ;; Successively applies 8-bit wide chunks of Y to X using OP storing the result in R.
351 ;; If FIXNUMIZE is true, Y is fixnumized before being used.
352 ;; If NEG-OP is given and Y is negative, NEG-OP is used instead of OP.
353 ;; If INVERT-Y is given LOGNOT is applied to Y before it being used (but after possibly
354 ;; being fixnumized.
355 ;; If INVERT-R is given R is bit wise inverted at the end.
356 ;; If SINGLE-OP-OP is given and (possibly fixnumized) Y fits into a single ARM immediate
357 ;; it is used for a single operation instead of OP.
358 ;; If FIRST-OP is given, it is used in the first iteration instead of OP.
359 ;; If FIRST-NO-SOURCE is given, there will be ne source register (X) in the first iteration.
360 (let ((bytespec (gensym "bytespec"))
361 (value (gensym "value"))
362 (transformed (gensym "transformed")))
363 (labels ((instruction (source-reg op neg-op &optional no-source)
364 `(,@(if neg-op
365 `((if (< ,y 0)
366 (inst ,neg-op ,r ,@(when (not no-source)`(,source-reg))
367 (mask-field ,bytespec ,value))
368 (inst ,op ,r ,@(when (not no-source) `(,source-reg))
369 (mask-field ,bytespec ,value))))
370 `((inst ,op ,r ,@(when (not no-source) `(,source-reg))
371 (mask-field ,bytespec ,value))))
372 (setf (ldb ,bytespec ,value) 0)))
373 (composite ()
374 `((let ((,bytespec (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))))
375 ,@(instruction x (or first-op op) neg-op first-no-source))
376 (do ((,bytespec (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))
377 (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))))
378 ((zerop ,value))
379 ,@(instruction r op neg-op)
380 ,@(when invert-r
381 `((inst mvn ,r ,r)))))))
382 `(let* ((,transformed ,(if fixnumize
383 `(fixnumize ,y)
384 `,y))
385 (,value (ldb (byte 32 0)
386 ,@(if neg-op
387 `((if (< ,transformed 0) (- ,transformed) ,transformed))
388 (if invert-y
389 `((lognot ,transformed))
390 `(,transformed))))))
391 ,@(if single-op-op
392 `((handler-case
393 (progn
394 (inst ,single-op-op ,r ,x ,transformed))
395 (cannot-encode-immediate-operand ()
396 ,@(composite))))
397 (composite))))))
400 ;;;; Addressing mode 2 support
402 ;;; Addressing mode 2 ostensibly has 9 formats. These are formed from
403 ;;; a cross product of three address calculations and three base
404 ;;; register writeback modes. As one of the address calculations is a
405 ;;; scaled register calculation identical to the mode 1 register shift
406 ;;; by constant, we reuse the shifter-operand structure and its public
407 ;;; constructors.
409 (defstruct memory-operand
410 base
411 offset
412 direction
413 mode)
415 ;;; The @ macro is used to encode a memory addressing mode. The
416 ;;; parameters for the base form are a base register, an optional
417 ;;; offset (either an integer, a register tn or a shifter-operand
418 ;;; structure with a constant shift amount, optionally within a unary
419 ;;; - form), and a base register writeback mode (either :offset,
420 ;;; :pre-index, or :post-index). The alternative form uses a label as
421 ;;; the base register, and accepts only (optionally negated) integers
422 ;;; as offsets, and requires a mode of :offset.
423 (defun %@ (base offset direction mode)
424 (when (label-p base)
425 (aver (eq mode :offset))
426 (aver (integerp offset)))
428 (when (shifter-operand-p offset)
429 (aver (integerp (shifter-operand-operand offset))))
431 ;; Fix up direction with negative offsets.
432 (when (and (not (label-p base))
433 (integerp offset)
434 (< offset 0))
435 (setf offset (- offset))
436 (setf direction (if (eq direction :up) :down :up)))
438 (make-memory-operand :base base :offset offset
439 :direction direction :mode mode))
441 (defmacro @ (base &optional (offset 0) (mode :offset))
442 (let* ((direction (if (and (consp offset)
443 (eq (car offset) '-)
444 (null (cddr offset)))
445 :down
446 :up))
447 (offset (if (eq direction :down) (cadr offset) offset)))
448 `(%@ ,base ,offset ,direction ,mode)))
450 ;;;; Data-processing instructions
452 ;;; Data processing instructions have a 4-bit opcode field and a 1-bit
453 ;;; "S" field for updating condition bits. They are adjacent, so we
454 ;;; roll them into one 5-bit field for convenience.
456 (define-bitfield-emitter emit-dp-instruction 32
457 (byte 4 28) (byte 2 26) (byte 1 25) (byte 5 20)
458 (byte 4 16) (byte 4 12) (byte 12 0))
460 ;;; There are 16 data processing instructions, with a breakdown as
461 ;;; follows:
463 ;;; 1.) Two "move" instructions, with no "source" operand (they have
464 ;;; destination and shifter operands only).
466 ;;; 2.) Four "test" instructions, with no "destination" operand.
467 ;;; These instructions always have their "S" bit set, though it
468 ;;; is not specified in their mnemonics.
470 ;;; 3.) Ten "normal" instructions, with all three operands.
472 ;;; Aside from this, the instructions all have a regular encoding, so
473 ;;; we can use a single macro to define them.
475 (defmacro define-data-processing-instruction (instruction opcode dest-p src-p)
476 `(define-instruction ,instruction (segment &rest args)
477 (:printer dp-shift-immediate ((opcode-8 ,opcode)
478 ,@(unless dest-p '((rd 0)))
479 ,@(unless src-p '((rn 0))))
480 ,@(cond
481 ((not dest-p)
482 '('(:name cond :tab rn ", " rm shift)))
483 ((not src-p)
484 '('(:name cond :tab rd ", " rm shift)))))
485 (:printer dp-shift-register ((opcode-8 ,opcode)
486 ,@(unless dest-p '((rd 0)))
487 ,@(unless src-p '((rn 0))))
488 ,@(cond
489 ((not dest-p)
490 '('(:name cond :tab rn ", " rm ", " shift-type " " rs)))
491 ((not src-p)
492 '('(:name cond :tab rd ", " rm ", " shift-type " " rs)))))
493 (:printer dp-immediate ((opcode-8 ,(logior opcode #x20))
494 ,@(unless dest-p '((rd 0)))
495 ,@(unless src-p '((rn 0))))
496 ,@(cond
497 ((not dest-p)
498 '('(:name cond :tab rn ", " immediate)))
499 ((not src-p)
500 '('(:name cond :tab rd ", " immediate)))))
501 (:emitter
502 (with-condition-defaulted (args (condition ,@(if dest-p '(dest))
503 ,@(if src-p '(src))
504 shifter-operand))
505 ,(if dest-p '(aver (register-p dest)))
506 ,(if src-p '(aver (register-p src)))
507 (let ((shifter-operand (encode-shifter-operand shifter-operand)))
508 (emit-dp-instruction segment
509 (conditional-opcode condition)
511 (ldb (byte 1 25) shifter-operand)
512 ,opcode
513 ,(if src-p '(tn-offset src) 0)
514 ,(if dest-p '(tn-offset dest) 0)
515 (ldb (byte 12 0) shifter-operand)))))))
517 (define-data-processing-instruction and #x00 t t)
518 (define-data-processing-instruction ands #x01 t t)
519 (define-data-processing-instruction eor #x02 t t)
520 (define-data-processing-instruction eors #x03 t t)
521 (define-data-processing-instruction sub #x04 t t)
522 (define-data-processing-instruction subs #x05 t t)
523 (define-data-processing-instruction rsb #x06 t t)
524 (define-data-processing-instruction rsbs #x07 t t)
525 (define-data-processing-instruction add #x08 t t)
526 (define-data-processing-instruction adds #x09 t t)
527 (define-data-processing-instruction adc #x0a t t)
528 (define-data-processing-instruction adcs #x0b t t)
529 (define-data-processing-instruction sbc #x0c t t)
530 (define-data-processing-instruction sbcs #x0d t t)
531 (define-data-processing-instruction rsc #x0e t t)
532 (define-data-processing-instruction rscs #x0f t t)
533 (define-data-processing-instruction orr #x18 t t)
534 (define-data-processing-instruction orrs #x19 t t)
535 (define-data-processing-instruction bic #x1c t t)
536 (define-data-processing-instruction bics #x1d t t)
538 (define-data-processing-instruction tst #x11 nil t)
539 (define-data-processing-instruction teq #x13 nil t)
540 (define-data-processing-instruction cmp #x15 nil t)
541 (define-data-processing-instruction cmn #x17 nil t)
543 (define-data-processing-instruction mov #x1a t nil)
544 (define-data-processing-instruction movs #x1b t nil)
545 (define-data-processing-instruction mvn #x1e t nil)
546 (define-data-processing-instruction mvns #x1f t nil)
548 ;;;; Exception-generating instructions
550 ;;; There are two exception-generating instructions. One, BKPT, is
551 ;;; ostensibly used as a breakpoint instruction, and to communicate
552 ;;; with debugging hardware. The other, SWI, is intended for use as a
553 ;;; system call interface. We need both because, at least on some
554 ;;; platforms, the only breakpoint trap that works properly is a
555 ;;; syscall.
557 (define-bitfield-emitter emit-swi-instruction 32
558 (byte 4 28) (byte 4 24) (byte 24 0))
560 (define-instruction swi (segment &rest args)
561 (:emitter
562 (with-condition-defaulted (args (condition code))
563 (emit-swi-instruction segment
564 (conditional-opcode condition)
565 #b1111 code))))
567 (define-bitfield-emitter emit-bkpt-instruction 32
568 (byte 4 28) (byte 8 20) (byte 12 8) (byte 4 4) (byte 4 0))
570 (define-instruction bkpt (segment code)
571 (:emitter
572 (emit-bkpt-instruction segment #b1110 #b00010010
573 (ldb (byte 12 4) code)
574 #b0111
575 (ldb (byte 4 0) code))))
577 ;;; It turns out that the Linux kernel decodes this particular
578 ;;; officially undefined instruction as a single-instruction SIGTRAP
579 ;;; generation instruction, or breakpoint.
580 (define-instruction debug-trap (segment)
581 (:emitter
582 (emit-word segment #xe7f001f0)))
584 ;;;; Miscellaneous arithmetic instructions
586 (define-bitfield-emitter emit-clz-instruction 32
587 (byte 4 28) (byte 12 16) (byte 4 12) (byte 8 4) (byte 4 0))
589 (define-instruction clz (segment &rest args)
590 (:emitter
591 (with-condition-defaulted (args (condition dest src))
592 (aver (register-p dest))
593 (aver (register-p src))
594 (emit-clz-instruction segment (conditional-opcode condition)
595 #b000101101111
596 (tn-offset dest)
597 #b11110001
598 (tn-offset src)))))
600 ;;;; Branch instructions
602 (define-bitfield-emitter emit-branch-instruction 32
603 (byte 4 28) (byte 4 24) (byte 24 0))
605 (defun emit-branch-back-patch (segment condition opcode dest)
606 (emit-back-patch segment 4
607 (lambda (segment posn)
608 (emit-branch-instruction segment
609 (conditional-opcode condition)
610 opcode
611 (ldb (byte 24 2)
612 (- (label-position dest)
613 (+ posn 8)))))))
615 (define-instruction b (segment &rest args)
616 (:emitter
617 (with-condition-defaulted (args (condition dest))
618 (aver (label-p dest))
619 (emit-branch-back-patch segment condition #b1010 dest))))
621 (define-instruction bl (segment &rest args)
622 (:emitter
623 (with-condition-defaulted (args (condition dest))
624 (aver (label-p dest))
625 (emit-branch-back-patch segment condition #b1011 dest))))
627 (define-bitfield-emitter emit-branch-exchange-instruction 32
628 (byte 4 28) (byte 8 20) (byte 4 16) (byte 4 12)
629 (byte 4 8) (byte 4 4) (byte 4 0))
631 (define-instruction bx (segment &rest args)
632 (:emitter
633 (with-condition-defaulted (args (condition dest))
634 (aver (register-p dest))
635 (emit-branch-exchange-instruction segment
636 (conditional-opcode condition)
637 #b00010010 #b1111 #b1111
638 #b1111 #b0001 (tn-offset dest)))))
640 (define-instruction blx (segment &rest args)
641 (:emitter
642 (with-condition-defaulted (args (condition dest))
643 (aver (register-p dest))
644 (emit-branch-exchange-instruction segment
645 (conditional-opcode condition)
646 #b00010010 #b1111 #b1111
647 #b1111 #b0011 (tn-offset dest)))))
649 ;;;; Semaphore instructions
651 (defun emit-semaphore-instruction (segment opcode condition dest value address)
652 (aver (register-p dest))
653 (aver (register-p value))
654 (aver (memory-operand-p address))
655 (aver (zerop (memory-operand-offset address)))
656 (aver (eq :offset (memory-operand-mode address)))
657 (emit-dp-instruction segment (conditional-opcode condition)
658 #b00 0 opcode (tn-offset (memory-operand-base address))
659 (tn-offset dest)
660 (dpb #b1001 (byte 4 4) (tn-offset value))))
662 (define-instruction swp (segment &rest args)
663 (:emitter
664 (with-condition-defaulted (args (condition dest value address))
665 (emit-semaphore-instruction segment #b10000
666 condition dest value address))))
668 (define-instruction swpb (segment &rest args)
669 (:emitter
670 (with-condition-defaulted (args (condition dest value address))
671 (emit-semaphore-instruction segment #b10100
672 condition dest value address))))
674 ;;;; Status-register instructions
676 (define-instruction mrs (segment &rest args)
677 (:emitter
678 (with-condition-defaulted (args (condition dest reg))
679 (aver (register-p dest))
680 (aver (member reg '(:cpsr :spsr)))
681 (emit-dp-instruction segment (conditional-opcode condition)
682 #b00 0 (if (eq reg :cpsr) #b10000 #b10100)
683 #b1111 (tn-offset dest) 0))))
685 (defun encode-status-register-fields (fields)
686 (let ((fields (string fields)))
687 (labels ((frob (mask index)
688 (let* ((field (aref fields index))
689 (field-mask (cdr (assoc field
690 '((#\C . #b0001) (#\X . #b0010)
691 (#\S . #b0100) (#\F . #b1000))
692 :test #'char=))))
693 (unless field-mask
694 (error "bad status register field desginator ~S" fields))
695 (if (< (1+ index) (length fields))
696 (frob (logior mask field-mask) (1+ index))
697 (logior mask field-mask)))))
698 (frob 0 0))))
700 (defmacro cpsr (fields)
701 (encode-status-register-fields fields))
703 (defmacro spsr (fields)
704 (logior #b10000 (encode-status-register-fields fields)))
706 (define-instruction msr (segment &rest args)
707 (:emitter
708 (with-condition-defaulted (args (condition field-mask src))
709 (aver (or (register-p src)
710 (integerp src)))
711 (let ((encoded-src (encode-shifter-operand src)))
712 (emit-dp-instruction segment (conditional-opcode condition)
713 #b00 (ldb (byte 1 25) encoded-src)
714 (if (logbitp 4 field-mask) #b10110 #b10010)
715 field-mask #b1111
716 (ldb (byte 12 0) encoded-src))))))
718 ;;;; Multiply instructions
720 (define-bitfield-emitter emit-multiply-instruction 32
721 (byte 4 28) (byte 8 20) (byte 4 16) (byte 4 12)
722 (byte 4 8) (byte 4 4) (byte 4 0))
724 (macrolet
725 ((define-multiply-instruction (name field-mapping opcode1 opcode2)
726 (let ((arglist (ecase field-mapping
727 (:dzsm '(dest src multiplicand))
728 (:dnsm '(dest src multiplicand num))
729 (:ddsm '(dest-lo dest src multiplicand)))))
730 `(define-instruction ,name (segment &rest args)
731 (:emitter
732 (with-condition-defaulted (args (condition ,@arglist))
733 ,@(loop
734 for arg in arglist
735 collect `(aver (register-p ,arg)))
736 (emit-multiply-instruction segment (conditional-opcode condition)
737 ,opcode1
738 (tn-offset dest)
739 ,(ecase field-mapping
740 (:dzsm 0)
741 (:dnsm '(tn-offset num))
742 (:ddsm '(tn-offset dest-lo)))
743 (tn-offset src)
744 ,opcode2
745 (tn-offset multiplicand))))))))
747 (define-multiply-instruction mul :dzsm #b00000000 #b1001)
748 (define-multiply-instruction muls :dzsm #b00000001 #b1001)
749 (define-multiply-instruction mla :dnsm #b00000010 #b1001)
750 (define-multiply-instruction mlas :dnsm #b00000011 #b1001)
752 (define-multiply-instruction umull :ddsm #b00001000 #b1001)
753 (define-multiply-instruction umulls :ddsm #b00001001 #b1001)
754 (define-multiply-instruction umlal :ddsm #b00001010 #b1001)
755 (define-multiply-instruction umlals :ddsm #b00001011 #b1001)
757 (define-multiply-instruction smull :ddsm #b00001100 #b1001)
758 (define-multiply-instruction smulls :ddsm #b00001101 #b1001)
759 (define-multiply-instruction smlal :ddsm #b00001110 #b1001)
760 (define-multiply-instruction smlals :ddsm #b00001111 #b1001)
762 (define-multiply-instruction smlabb :dnsm #b00010000 #b1000)
763 (define-multiply-instruction smlatb :dnsm #b00010000 #b1010)
764 (define-multiply-instruction smlabt :dnsm #b00010000 #b1100)
765 (define-multiply-instruction smlatt :dnsm #b00010000 #b1110)
767 (define-multiply-instruction smlalbb :ddsm #b00010100 #b1000)
768 (define-multiply-instruction smlaltb :ddsm #b00010100 #b1010)
769 (define-multiply-instruction smlalbt :ddsm #b00010100 #b1100)
770 (define-multiply-instruction smlaltt :ddsm #b00010100 #b1110)
772 (define-multiply-instruction smulbb :dzsm #b00010110 #b1000)
773 (define-multiply-instruction smultb :dzsm #b00010110 #b1010)
774 (define-multiply-instruction smulbt :dzsm #b00010110 #b1100)
775 (define-multiply-instruction smultt :dzsm #b00010110 #b1110)
777 (define-multiply-instruction smlawb :dnsm #b00010010 #b1000)
778 (define-multiply-instruction smlawt :dnsm #b00010010 #b1100)
780 (define-multiply-instruction smulwb :dzsm #b00010010 #b1010)
781 (define-multiply-instruction smulwt :dzsm #b00010010 #b1110))
783 ;;;; Load/store instructions
785 ;;; Emit a load/store instruction. CONDITION is a condition code
786 ;;; name, KIND is :load or :store, WIDTH is :word or :byte, DATA is a
787 ;;; register TN and ADDRESS is either a memory-operand structure or a
788 ;;; stack TN.
789 (defun emit-load/store-instruction (segment condition kind width data address)
790 (flet ((compute-opcode (direction mode)
791 (let ((opcode-bits '(:load #b00001 :store #b00000
792 :word #b00000 :byte #b00100
793 :up #b01000 :down #b00000
794 :offset #b10000
795 :pre-index #b10010
796 :post-index #b00000)))
797 (reduce #'logior (list kind width direction mode)
798 :key (lambda (value) (getf opcode-bits value))))))
799 (etypecase address
800 (memory-operand
801 (let* ((base (memory-operand-base address))
802 (offset (memory-operand-offset address))
803 (direction (memory-operand-direction address))
804 (mode (memory-operand-mode address))
805 (cond-bits (conditional-opcode condition)))
806 (cond
807 ((label-p base)
808 (emit-back-patch
809 segment 4
810 (lambda (segment posn)
811 (let* ((label-delta (- (label-position base)
812 (+ posn 8)))
813 (offset-delta (if (eq direction :up)
814 offset
815 (- offset)))
816 (overall-delta (+ label-delta
817 offset-delta))
818 (absolute-delta (abs overall-delta)))
819 (aver (typep absolute-delta '(unsigned-byte 12)))
820 (emit-dp-instruction segment cond-bits #b01 0
821 (compute-opcode (if (< overall-delta 0)
822 :down
823 :up)
824 mode)
825 pc-offset (tn-offset data)
826 absolute-delta)))))
827 ((integerp offset)
828 (aver (typep offset '(unsigned-byte 12)))
829 (emit-dp-instruction segment cond-bits #b01 0
830 (compute-opcode direction mode)
831 (tn-offset base) (tn-offset data)
832 offset))
834 (emit-dp-instruction segment cond-bits #b01 1
835 (compute-opcode direction mode)
836 (tn-offset base) (tn-offset data)
837 (encode-shifter-operand offset))))))
839 #+(or)
841 ;; FIXME: This is for stack TN references, and needs must be
842 ;; implemented.
843 ))))
845 (macrolet
846 ((define-load/store-instruction (name kind width)
847 `(define-instruction ,name (segment &rest args)
848 (:emitter
849 (with-condition-defaulted (args (condition reg address))
850 (aver (or (register-p reg)
851 ,@(when (eq :store kind)
852 '((and (tn-p reg)
853 (eq 'null (sc-name (tn-sc reg))))))))
854 (emit-load/store-instruction segment condition
855 ,kind ,width
856 (if (register-p reg) reg null-tn)
857 address))))))
858 (define-load/store-instruction ldr :load :word)
859 (define-load/store-instruction ldrb :load :byte)
860 (define-load/store-instruction str :store :word)
861 (define-load/store-instruction strb :store :byte))
863 ;;; Emit a miscellaneous load/store instruction. CONDITION is a
864 ;;; condition code name, OPCODE1 is the low bit of the first opcode
865 ;;; field, OPCODE2 is the second opcode field, DATA is a register TN
866 ;;; and ADDRESS is either a memory-operand structure or a stack TN.
867 (defun emit-misc-load/store-instruction (segment condition opcode1
868 opcode2 data address)
869 (flet ((compute-opcode (kind direction mode)
870 (let ((opcode-bits '(:register #b00000 :immediate #b00100
871 :up #b01000 :down #b00000
872 :offset #b10000
873 :pre-index #b10010
874 :post-index #b00000)))
875 (reduce #'logior (list kind direction mode)
876 :key (lambda (value) (getf opcode-bits value))))))
877 (etypecase address
878 (memory-operand
879 (let* ((base (memory-operand-base address))
880 (offset (memory-operand-offset address))
881 (direction (memory-operand-direction address))
882 (mode (memory-operand-mode address))
883 (cond-bits (conditional-opcode condition)))
884 (cond
885 ((label-p base)
886 (emit-back-patch
887 segment 4
888 (lambda (segment posn)
889 (let* ((label-delta (- (label-position base)
890 (+ posn 8)))
891 (offset-delta (if (eq direction :up)
892 offset
893 (- offset)))
894 (overall-delta (+ label-delta
895 offset-delta))
896 (absolute-delta (abs overall-delta)))
897 (aver (typep absolute-delta '(unsigned-byte 8)))
898 (emit-multiply-instruction segment cond-bits
899 (logior opcode1
900 (compute-opcode :immedaite
901 (if (< overall-delta 0)
902 :down
903 :up)
904 mode))
905 (tn-offset base) (tn-offset data)
906 (ldb (byte 4 4) absolute-delta)
907 opcode2 absolute-delta)))))
908 ((integerp offset)
909 (aver (typep offset '(unsigned-byte 8)))
910 (emit-multiply-instruction segment cond-bits
911 (logior opcode1
912 (compute-opcode :immediate direction mode))
913 (tn-offset base) (tn-offset data)
914 (ldb (byte 4 4) offset)
915 opcode2 offset))
916 ((register-p offset)
917 (emit-multiply-instruction segment cond-bits
918 (logior opcode1
919 (compute-opcode :register direction mode))
920 (tn-offset base) (tn-offset data)
921 0 opcode2 (tn-offset offset)))
923 (error "bad thing for a miscellaneous load/store address ~S"
924 address)))))
926 #+(or)
928 ;; FIXME: This is for stack TN references, and needs must be
929 ;; implemented.
930 ))))
932 (macrolet
933 ((define-misc-load/store-instruction (name opcode1 opcode2 double-width)
934 `(define-instruction ,name (segment &rest args)
935 (:emitter
936 (with-condition-defaulted (args (condition reg address))
937 (aver (register-p reg))
938 ,(when double-width '(aver (evenp (tn-offset reg))))
939 (emit-misc-load/store-instruction segment condition
940 ,opcode1 ,opcode2
941 reg address))))))
942 (define-misc-load/store-instruction strh 0 #b1011 nil)
943 (define-misc-load/store-instruction ldrd 0 #b1101 t)
944 (define-misc-load/store-instruction strd 0 #b1111 t)
946 (define-misc-load/store-instruction ldrh 1 #b1011 nil)
947 (define-misc-load/store-instruction ldrsb 1 #b1101 nil)
948 (define-misc-load/store-instruction ldrsh 1 #b1111 nil))
950 ;;;; Boxed-object computation instructions (for LRA and CODE)
952 ;;; Compute the address of a CODE object by parsing the header of a
953 ;;; nearby LRA or SIMPLE-FUN.
954 (define-instruction compute-code (segment code lip object-label temp)
955 (:vop-var vop)
956 (:emitter
957 (emit-back-patch
958 segment 12
959 (lambda (segment position)
960 (assemble (segment vop)
961 ;; Calculate the address of the code component. This is an
962 ;; exercise in excess cleverness. First, we calculate (from
963 ;; our program counter only) the address of OBJECT-LABEL plus
964 ;; OTHER-POINTER-LOWTAG. The extra two words are to
965 ;; compensate for the offset applied by ARM CPUs when reading
966 ;; the program counter.
967 (inst sub lip pc-tn (- ;; The 8 below is the displacement
968 ;; from reading the program counter.
969 (+ position 8)
970 (+ (label-position object-label)
971 other-pointer-lowtag)))
972 ;; Next, we read the function header.
973 (inst ldr temp (@ lip (- other-pointer-lowtag)))
974 ;; And finally we use the header value (a count in words),
975 ;; plus the fact that the top two bits of the widetag are
976 ;; clear (SIMPLE-FUN-HEADER-WIDETAG is #x2A and
977 ;; RETURN-PC-HEADER-WIDETAG is #x36) to compute the boxed
978 ;; address of the code component.
979 (inst sub code lip (lsr temp (- 8 word-shift))))))))
981 ;;; Compute the address of a nearby LRA object by dead reckoning from
982 ;;; the location of the current instruction.
983 (define-instruction compute-lra (segment dest lip lra-label)
984 (:vop-var vop)
985 (:emitter
986 ;; We can compute the LRA in a single instruction if the overall
987 ;; offset puts it to within an 8-bit displacement. Otherwise, we
988 ;; need to load it by parts into LIP until we're down to an 8-bit
989 ;; displacement, and load the final 8 bits into DEST. We may
990 ;; safely presume that an overall displacement may be up to 24 bits
991 ;; wide (the PPC backend has special provision for branches over 15
992 ;; bits, which implies that segments can become large, but a 16
993 ;; megabyte segment (24 bits of displacement) is ridiculous), so we
994 ;; need to cover a range of up to three octets of displacement.
995 (labels ((compute-delta (position &optional magic-value)
996 (- (+ (label-position lra-label
997 (when magic-value position)
998 magic-value)
999 other-pointer-lowtag)
1000 ;; The 8 below is the displacement
1001 ;; from reading the program counter.
1002 (+ position 8)))
1004 (load-chunk (segment delta dst src chunk)
1005 (assemble (segment vop)
1006 (if (< delta 0)
1007 (inst sub dst src chunk)
1008 (inst add dst src chunk))))
1010 (three-instruction-emitter (segment position)
1011 (let* ((delta (compute-delta position))
1012 (absolute-delta (abs delta)))
1013 (load-chunk segment delta
1014 lip pc-tn (mask-field (byte 8 16) absolute-delta))
1015 (load-chunk segment delta
1016 lip lip (mask-field (byte 8 8) absolute-delta))
1017 (load-chunk segment delta
1018 dest lip (mask-field (byte 8 0) absolute-delta))))
1020 (two-instruction-emitter (segment position)
1021 (let* ((delta (compute-delta position))
1022 (absolute-delta (abs delta)))
1023 (assemble (segment vop)
1024 (load-chunk segment delta
1025 lip pc-tn (mask-field (byte 8 8) absolute-delta))
1026 (load-chunk segment delta
1027 dest lip (mask-field (byte 8 0) absolute-delta)))))
1029 (one-instruction-emitter (segment position)
1030 (let* ((delta (compute-delta position))
1031 (absolute-delta (abs delta)))
1032 (assemble (segment vop)
1033 (load-chunk segment delta
1034 dest pc-tn absolute-delta))))
1036 (two-instruction-maybe-shrink (segment posn magic-value)
1037 (let ((delta (compute-delta posn magic-value)))
1038 (when (<= (integer-length delta) 8)
1039 (emit-back-patch segment 4
1040 #'one-instruction-emitter)
1041 t)))
1043 (three-instruction-maybe-shrink (segment posn magic-value)
1044 (let ((delta (compute-delta posn magic-value)))
1045 (when (<= (integer-length delta) 16)
1046 (emit-chooser segment 8 2
1047 #'two-instruction-maybe-shrink
1048 #'two-instruction-emitter)
1049 t))))
1050 (emit-chooser
1051 ;; We need to emit up to three instructions, which is 12 octets.
1052 ;; This preserves a mere two bits of alignment.
1053 segment 12 2
1054 #'three-instruction-maybe-shrink
1055 #'three-instruction-emitter))))
1057 ;;; Load a register from a "nearby" LABEL by dead reckoning from the
1058 ;;; location of the current instruction.
1059 (define-instruction load-from-label (segment &rest args)
1060 (:vop-var vop)
1061 (:emitter
1062 (with-condition-defaulted (args (condition dest lip label))
1063 ;; We can load the word addressed by a label in a single
1064 ;; instruction if the overall offset puts it to within a 12-bit
1065 ;; displacement. Otherwise, we need to build an address by parts
1066 ;; into LIP until we're down to a 12-bit displacement, and then
1067 ;; apply the final 12 bits with LDR. For now, we'll allow up to 20
1068 ;; bits of displacement, as that should be easy to implement, and a
1069 ;; megabyte large code object is already a bit unwieldly. If
1070 ;; neccessary, we can expand to a 28 bit displacement.
1071 (labels ((compute-delta (position &optional magic-value)
1072 (- (label-position label
1073 (when magic-value position)
1074 magic-value)
1075 ;; The 8 below is the displacement
1076 ;; from reading the program counter.
1077 (+ position 8)))
1079 (load-chunk (segment delta dst src chunk)
1080 (assemble (segment vop)
1081 (if (< delta 0)
1082 (inst sub condition dst src chunk)
1083 (inst add condition dst src chunk))))
1085 (two-instruction-emitter (segment position)
1086 (let* ((delta (compute-delta position))
1087 (absolute-delta (abs delta)))
1088 (assemble (segment vop)
1089 (load-chunk segment delta
1090 lip pc-tn (mask-field (byte 8 12) absolute-delta))
1091 (inst ldr condition dest (@ lip (mask-field (byte 12 0) delta))))))
1093 (one-instruction-emitter (segment position)
1094 (let* ((delta (compute-delta position)))
1095 (assemble (segment vop)
1096 (inst ldr condition dest (@ pc-tn delta)))))
1098 (two-instruction-maybe-shrink (segment posn magic-value)
1099 (let ((delta (compute-delta posn magic-value)))
1100 (when (<= (integer-length delta) 12)
1101 (emit-back-patch segment 4
1102 #'one-instruction-emitter)
1103 t))))
1104 (emit-chooser
1105 ;; We need to emit up to two instructions, which is 8 octets,
1106 ;; but might wish to emit only one. This preserves a mere two
1107 ;; bits of alignment.
1108 segment 8 2
1109 #'two-instruction-maybe-shrink
1110 #'two-instruction-emitter)))))
1112 ;; data processing floating point instructions
1113 (define-bitfield-emitter emit-fp-dp-instruction 32
1114 (byte 4 28) ; cond
1115 (byte 4 24) ; #b1110
1116 (byte 1 23) ; p
1117 (byte 1 22) ; D
1118 (byte 1 21) ; q
1119 (byte 1 20) ; r
1120 (byte 4 16) ; Fn || extension op
1121 (byte 4 12) ; Fd
1122 (byte 3 9) ; #b101
1123 (byte 1 8) ; double/single precission
1124 (byte 1 7) ; N || extension op
1125 (byte 1 6) ; s
1126 (byte 1 5) ; M
1127 (byte 1 4) ; #b0
1128 (byte 4 0)) ; Fm
1130 (defun low-bit-float-reg (reg-tn)
1131 (logand 1 (tn-offset reg-tn)))
1133 (defun high-bits-float-reg (reg-tn)
1134 (ash (tn-offset reg-tn) -1))
1136 (defmacro define-binary-fp-data-processing-instruction (name precision p q r s)
1137 (let ((precision-flag (ecase precision
1138 (:single 0)
1139 (:double 1))))
1140 `(define-instruction ,name (segment &rest args)
1141 (:emitter
1142 (with-condition-defaulted (args (condition dest op-n op-m))
1143 (emit-fp-dp-instruction segment
1144 (conditional-opcode condition)
1145 #b1110
1147 (low-bit-float-reg dest)
1150 (high-bits-float-reg op-n)
1151 (high-bits-float-reg dest)
1152 #b101
1153 ,precision-flag
1154 (low-bit-float-reg op-n)
1156 (low-bit-float-reg op-m)
1158 (high-bits-float-reg op-m)))))))
1160 (defmacro define-binary-fp-data-processing-instructions (root p q r s)
1161 `(progn
1162 (define-binary-fp-data-processing-instruction ,(symbolicate root 's) :single ,p ,q ,r ,s)
1163 (define-binary-fp-data-processing-instruction ,(symbolicate root 'd) :double ,p ,q ,r ,s)))
1165 (define-binary-fp-data-processing-instructions fmac 0 0 0 0)
1166 (define-binary-fp-data-processing-instructions fnmac 0 0 0 1)
1167 (define-binary-fp-data-processing-instructions fmsc 0 0 1 0)
1168 (define-binary-fp-data-processing-instructions fnmsc 0 0 1 1)
1169 (define-binary-fp-data-processing-instructions fmul 0 1 0 0)
1170 (define-binary-fp-data-processing-instructions fnmul 0 1 0 1)
1171 (define-binary-fp-data-processing-instructions fadd 0 1 1 0)
1172 (define-binary-fp-data-processing-instructions fsub 0 1 1 1)
1173 (define-binary-fp-data-processing-instructions fdiv 1 0 0 0)
1175 (defmacro define-unary-fp-data-processing-instruction (name precision fn n)
1176 (let ((precision-flag (ecase precision
1177 (:single 0)
1178 (:double 1))))
1179 `(define-instruction ,name (segment &rest args)
1180 (:emitter
1181 (with-condition-defaulted (args (condition dest op-m))
1182 (emit-fp-dp-instruction segment
1183 (conditional-opcode condition)
1184 #b1110
1186 (low-bit-float-reg dest)
1190 (high-bits-float-reg dest)
1191 #b101
1192 ,precision-flag
1195 (low-bit-float-reg op-m)
1197 (high-bits-float-reg op-m)))))))
1199 (defmacro define-unary-fp-data-processing-instructions (root fn n)
1200 `(progn
1201 (define-unary-fp-data-processing-instruction ,(symbolicate root 's) :single ,fn ,n)
1202 (define-unary-fp-data-processing-instruction ,(symbolicate root 'd) :double ,fn ,n)))
1204 (define-unary-fp-data-processing-instructions fcpy #b0000 0)
1205 (define-unary-fp-data-processing-instructions fabs #b0000 1)
1206 (define-unary-fp-data-processing-instructions fneg #b0001 0)
1207 (define-unary-fp-data-processing-instructions fsqrt #b0001 1)
1208 (define-unary-fp-data-processing-instructions fcmp #b0100 0)
1209 (define-unary-fp-data-processing-instructions fcmpe #b0100 1)
1210 (define-unary-fp-data-processing-instructions fcmpz #b0101 0)
1211 (define-unary-fp-data-processing-instructions fcmpez #b0101 1)
1212 (define-unary-fp-data-processing-instructions fuito #b1000 0)
1213 (define-unary-fp-data-processing-instructions fsito #b1000 1)
1214 (define-unary-fp-data-processing-instructions ftoui #b1100 0)
1215 (define-unary-fp-data-processing-instructions ftouiz #b1100 1)
1216 (define-unary-fp-data-processing-instructions ftosi #b1101 0)
1217 (define-unary-fp-data-processing-instructions ftosiz #b1101 1)
1219 (define-unary-fp-data-processing-instruction fcvtds :single #b0111 1)
1220 (define-unary-fp-data-processing-instruction fcvtsd :double #b0111 1)
1222 ;;; Load/Store Float Instructions
1224 (define-bitfield-emitter emit-fp-ls-instruction 32
1225 (byte 4 28) ; cond
1226 (byte 3 25) ; #b110
1227 (byte 1 24) ; P
1228 (byte 1 23) ; U
1229 (byte 1 22) ; D
1230 (byte 1 21) ; W
1231 (byte 1 20) ; L
1232 (byte 4 16) ; Rn
1233 (byte 4 12) ; Fd
1234 (byte 3 9) ; #b101
1235 (byte 1 8) ; double/single precission
1236 (byte 8 0)) ; offset
1238 ;; Define a load/store multiple floating point instruction. PRECISION is
1239 ;; :SINGLE for single precision values and :DOUBLE for double precision values.
1240 ;; DIRECTION has to be either :LOAD or :STORE.
1241 ;; If INC-OFFSET is true, the offset part of the instruction will be incremented by 1
1242 ;; indicating in the double case a load/store unknown instruction.
1243 (defmacro define-load-store-multiple-fp-instruction (name precision direction &optional inc-offset)
1244 (let ((precision-flag (ecase precision
1245 (:single 0)
1246 (:double 1)))
1247 (direction-flag (ecase direction
1248 (:load 1)
1249 (:store 0))))
1250 `(define-instruction ,name (segment &rest args)
1251 (:emitter
1252 (with-condition-defaulted (args (condition address base-reg reg-count))
1253 (let* ((mode (cond
1254 ((consp address)
1255 (cdr address))
1256 (t :unindexed)))
1257 (p (ecase mode
1258 ((:unindexed :increment) 0)
1259 ((:decrement) 1)))
1260 (u (ecase mode
1261 ((:unindexed :increment) 1)
1262 ((:decrement) 0)))
1263 (w (ecase mode
1264 ((:unindexed) 0)
1265 ((:increment :decrement) 1))))
1266 (emit-fp-ls-instruction segment
1267 (conditional-opcode condition)
1268 #b110
1271 (low-bit-float-reg base-reg)
1273 ,direction-flag
1274 (tn-offset address)
1275 (high-bits-float-reg base-reg)
1276 #b101
1277 ,precision-flag
1278 ,(ecase precision
1279 (:single 'reg-count)
1280 (:double `(+ (* 2 reg-count)
1281 ,(if inc-offset 1 0)))))))))))
1283 ;; multiple single precision
1284 (define-load-store-multiple-fp-instruction fstms :single :store)
1285 (define-load-store-multiple-fp-instruction fldms :single :load)
1286 ;; multiple double precision
1287 (define-load-store-multiple-fp-instruction fstmd :double :store)
1288 (define-load-store-multiple-fp-instruction fldmd :double :load)
1289 ;; multiple double precision registers of unknown content (needs up to 2 * reg-count + 1 words of space)
1290 (define-load-store-multiple-fp-instruction fstmx :double :store t)
1291 (define-load-store-multiple-fp-instruction fldmx :double :load t)
1293 ;; Define a load/store one floating point instruction. PRECISION is
1294 ;; :SINGLE for single precision values and :DOUBLE for double precision values.
1295 ;; DIRECTION has to be either :LOAD or :STORE.
1296 (defmacro define-load-store-one-fp-instruction (name precision direction)
1297 (let ((precision-flag (ecase precision
1298 (:single 0)
1299 (:double 1)))
1300 (direction-flag (ecase direction
1301 (:load 1)
1302 (:store 0))))
1303 `(define-instruction ,name (segment &rest args)
1304 (:emitter
1305 (with-condition-defaulted (args (condition float-reg memory-operand))
1306 (let ((base (memory-operand-base memory-operand))
1307 (offset (memory-operand-offset memory-operand))
1308 (direction (memory-operand-direction memory-operand)))
1309 (aver (eq (memory-operand-mode memory-operand) :offset))
1310 (aver (and (integerp offset)
1311 (zerop (logand offset 3))))
1312 ;; FIXME: Should support LABEL bases.
1313 (aver (tn-p base))
1314 (emit-fp-ls-instruction segment
1315 (conditional-opcode condition)
1316 #b110
1318 (if (eq direction :up) 1 0)
1319 (low-bit-float-reg float-reg)
1321 ,direction-flag
1322 (tn-offset base)
1323 (high-bits-float-reg float-reg)
1324 #b101
1325 ,precision-flag
1326 (ash offset -2))))))))
1328 (define-load-store-one-fp-instruction fsts :single :store)
1329 (define-load-store-one-fp-instruction flds :single :load)
1330 (define-load-store-one-fp-instruction fstd :double :store)
1331 (define-load-store-one-fp-instruction fldd :double :load)
1334 ;; single register transfer instructions
1336 (define-bitfield-emitter emit-fp-srt-instruction 32
1337 (byte 4 28) ; cond
1338 (byte 4 24) ; #b1110
1339 (byte 3 21) ; opc
1340 (byte 1 20) ; L
1342 (byte 4 16) ; Fn
1343 (byte 4 12) ; Rd
1344 (byte 3 9) ; #b101
1345 (byte 1 8) ; precision
1347 (byte 1 7) ; N
1348 (byte 7 0)) ; #b0010000
1350 (defun system-reg-encoding (float-reg)
1351 (ecase float-reg
1352 (:fpsid #b0000)
1353 (:fpscr #b0001)
1354 (:fpexc #b1000)))
1356 (defmacro define-single-reg-transfer-fp-instruction (name precision direction opcode &optional system-reg)
1357 (let ((precision-flag (ecase precision
1358 (:single 0)
1359 (:double 1)))
1360 (direction-flag (ecase direction
1361 (:to-arm 1)
1362 (:from-arm 0))))
1363 `(define-instruction ,name (segment &rest args)
1364 (:emitter
1365 (with-condition-defaulted (args (condition ,@(if (eq direction :to-arm)
1366 '(arm-reg float-reg)
1367 '(float-reg arm-reg))))
1368 (emit-fp-srt-instruction segment
1369 (conditional-opcode condition)
1370 #b1110
1371 ,opcode
1372 ,direction-flag
1373 ,(if system-reg
1374 '(system-reg-encoding float-reg)
1375 '(high-bits-float-reg float-reg))
1376 (tn-offset arm-reg)
1377 #b101
1378 ,precision-flag
1379 ,(if system-reg
1381 '(low-bit-float-reg float-reg))
1382 #b0010000))))))
1384 (define-single-reg-transfer-fp-instruction fmsr :single :from-arm #b000)
1385 (define-single-reg-transfer-fp-instruction fmrs :single :to-arm #b000)
1386 (define-single-reg-transfer-fp-instruction fmdlr :double :from-arm #b000)
1387 (define-single-reg-transfer-fp-instruction fmrdl :double :to-arm #b000)
1388 (define-single-reg-transfer-fp-instruction fmdhr :double :from-arm #b001)
1389 (define-single-reg-transfer-fp-instruction fmrdh :double :to-arm #b001)
1390 (define-single-reg-transfer-fp-instruction fmxr :single :from-arm #b111 t)
1391 (define-single-reg-transfer-fp-instruction fmrx :single :to-arm #b111 t)
1393 (define-bitfield-emitter emit-fp-trt-instruction 32
1394 (byte 4 28) ; cond
1395 (byte 7 21) ; #b1100010
1396 (byte 1 20) ; L
1397 (byte 4 16) ; Rn
1398 (byte 4 12) ; Rd
1399 (byte 3 9) ; #b101
1400 (byte 1 8) ; precision
1401 (byte 2 6) ; #b00
1402 (byte 1 5) ; M
1403 (byte 1 4) ; #b1
1404 (byte 4 0)) ; Fm
1406 (defmacro define-two-reg-transfer-fp-instruction (name precision direction)
1407 (let ((precision-flag (ecase precision
1408 (:single 0)
1409 (:double 1)))
1410 (direction-flag (ecase direction
1411 (:to-arm 1)
1412 (:from-arm 0))))
1413 `(define-instruction ,name (segment &rest args)
1414 (:emitter
1415 (with-condition-defaulted (args (condition float-reg arm-reg-1 arm-reg-2))
1416 (emit-fp-trt-instruction segment
1417 (conditional-opcode condition)
1418 #b1100010
1419 ,direction-flag
1420 (tn-offset arm-reg-2)
1421 (tn-offset arm-reg-1)
1422 #b101
1423 ,precision-flag
1424 #b00
1425 (low-bit-float-reg float-reg)
1427 (high-bits-float-reg float-reg)))))))
1429 (define-two-reg-transfer-fp-instruction fmsrr :single :from-arm)
1430 (define-two-reg-transfer-fp-instruction fmrrs :single :to-arm)
1431 (define-two-reg-transfer-fp-instruction fmdrr :double :from-arm)
1432 (define-two-reg-transfer-fp-instruction fmrrd :double :to-arm)