compiler/arm/insts: Only pick off actual condition names as conditions.
[sbcl/nyef.git] / src / compiler / arm / insts.lisp
blobb7e8474825d827b851381942cf22993107c96af6
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 (eval-when (:compile-toplevel :load-toplevel :execute)
23 (defparameter *conditions*
24 '((:eq . 0)
25 (:ne . 1)
26 (:cs . 2) (:hs . 2)
27 (:cc . 3) (:lo . 3)
28 (:mi . 4)
29 (:pl . 5)
30 (:vs . 6)
31 (:vc . 7)
32 (:hi . 8)
33 (:ls . 9)
34 (:ge . 10)
35 (:lt . 11)
36 (:gt . 12)
37 (:le . 13)
38 (:al . 14)))
39 (defparameter *condition-name-vec*
40 (let ((vec (make-array 16 :initial-element nil)))
41 (dolist (cond *conditions*)
42 (when (null (aref vec (cdr cond)))
43 (setf (aref vec (cdr cond)) (car cond))))
44 vec))
45 ) ; EVAL-WHEN
47 ;;; Set assembler parameters. (In CMU CL, this was done with
48 ;;; a call to a macro DEF-ASSEMBLER-PARAMS.)
49 (eval-when (:compile-toplevel :load-toplevel :execute)
50 (setf sb!assem:*assem-scheduler-p* nil))
52 (sb!disassem:define-arg-type condition-code
53 :printer *condition-name-vec*)
55 (defun conditional-opcode (condition)
56 (cdr (assoc condition *conditions* :test #'eq)))
58 ;;;; primitive emitters
60 ;(define-bitfield-emitter emit-word 16
61 ; (byte 16 0))
63 (define-bitfield-emitter emit-word 32
64 (byte 32 0))
66 ;;;; fixup emitters
68 (defun emit-absolute-fixup (segment fixup)
69 (note-fixup segment :absolute fixup)
70 (let ((offset (fixup-offset fixup)))
71 (if (label-p offset)
72 (emit-back-patch segment
73 4 ; FIXME: n-word-bytes
74 (lambda (segment posn)
75 (declare (ignore posn))
76 (emit-dword segment
77 (- (+ (component-header-length)
78 (or (label-position offset)
79 0))
80 other-pointer-lowtag))))
81 (emit-dword segment (or offset 0)))))
83 (defun emit-relative-fixup (segment fixup)
84 (note-fixup segment :relative fixup)
85 (emit-dword segment (or (fixup-offset fixup) 0)))
88 ;;;; miscellaneous hackery
90 (defun register-p (thing)
91 (and (tn-p thing)
92 (eq (sb-name (sc-sb (tn-sc thing))) 'registers)))
94 (defmacro with-condition-defaulted ((argvar arglist) &body body)
95 (let ((internal-emitter (gensym)))
96 `(flet ((,internal-emitter ,arglist
97 ,@body))
98 (if (assoc (car ,argvar) *conditions*)
99 (apply #',internal-emitter ,argvar)
100 (apply #',internal-emitter :al ,argvar)))))
102 (define-instruction byte (segment byte)
103 (:emitter
104 (emit-byte segment byte)))
106 ;(define-instruction word (segment word)
107 ; (:emitter
108 ; (emit-word segment word)))
110 (define-instruction word (segment word)
111 (:emitter
112 (etypecase word
113 (fixup
114 (note-fixup segment :absolute word)
115 (emit-word segment 0))
116 (integer
117 (emit-word segment word)))))
119 (defun emit-header-data (segment type)
120 (emit-back-patch segment
122 (lambda (segment posn)
123 (emit-word segment
124 (logior type
125 (ash (+ posn
126 (component-header-length))
127 (- n-widetag-bits
128 word-shift)))))))
130 (define-instruction simple-fun-header-word (segment)
131 (:emitter
132 (emit-header-data segment simple-fun-header-widetag)))
134 (define-instruction lra-header-word (segment)
135 (:emitter
136 (emit-header-data segment return-pc-header-widetag)))
138 ;;;; Addressing mode 1 support
140 ;;; Addressing mode 1 has some 11 formats. These are immediate,
141 ;;; register, and nine shift/rotate functions based on one or more
142 ;;; registers. As the mnemonics used for these functions are not
143 ;;; currently used, we simply define them as constructors for a
144 ;;; shifter-operand structure, similar to the make-ea function in the
145 ;;; x86 backend.
147 (defstruct shifter-operand
148 register
149 function-code
150 operand)
152 (defun lsl (register operand)
153 (aver (register-p register))
154 (aver (or (register-p operand)
155 (typep operand '(integer 0 31))))
157 (make-shifter-operand :register register :function-code 0 :operand operand))
159 (defun lsr (register operand)
160 (aver (register-p register))
161 (aver (or (register-p operand)
162 (typep operand '(integer 1 32))))
164 (make-shifter-operand :register register :function-code 1 :operand operand))
166 (defun asr (register operand)
167 (aver (register-p register))
168 (aver (or (register-p operand)
169 (typep operand '(integer 1 32))))
171 (make-shifter-operand :register register :function-code 2 :operand operand))
173 (defun ror (register operand)
174 ;; ROR is a special case: the encoding for ROR with an immediate
175 ;; shift of 32 (0) is actually RRX.
176 (aver (register-p register))
177 (aver (or (register-p operand)
178 (typep operand '(integer 1 31))))
180 (make-shifter-operand :register register :function-code 3 :operand operand))
182 (defun rrx (register)
183 ;; RRX is a special case: it is encoded as ROR with an immediate
184 ;; shift of 32 (0), and has no operand.
185 (aver (register-p register))
187 (make-shifter-operand :register register :function-code 3 :operand 0))
189 (define-condition cannot-encode-immediate-operand (error)
190 ((value :initarg value)))
192 (defun encode-shifter-immediate (operand)
193 ;; 32-bit immediate data is encoded as an 8-bit immediate data value
194 ;; and a 4-bit immediate shift count. The actual value is the
195 ;; immediate data rotated right by a number of bits equal to twice
196 ;; the shift count. Note that this means that there are a limited
197 ;; number of valid immediate integers and that some integers have
198 ;; multiple possible encodings. In the case of multiple encodings,
199 ;; the correct one to use is the one with the lowest shift count.
201 ;; XXX: Is it possible to determine the correct encoding in constant
202 ;; time, rather than time proportional to the final shift count? Is
203 ;; it possible to determine if a given integer is valid without
204 ;; attempting to encode it? Are such solutions cheaper (either time
205 ;; or spacewise) than simply attempting to encode it?
206 (labels ((try-immediate-encoding (value shift)
207 (unless (<= 0 shift 15)
208 (error 'cannot-encode-immediate-operand :value operand))
209 (if (typep value '(unsigned-byte 8))
210 (dpb shift (byte 4 8) value)
211 (try-immediate-encoding (dpb value (byte 30 2)
212 (ldb (byte 2 30) value))
213 (1+ shift)))))
214 (try-immediate-encoding operand 0)))
216 (defun encode-shifter-operand (operand)
217 (etypecase operand
218 (integer
219 (dpb 1 (byte 1 25) (encode-shifter-immediate operand)))
222 (cond
223 ((eq 'registers (sb-name (sc-sb (tn-sc operand))))
224 ;; For those wondering, this is LSL immediate for 0 bits.
225 (tn-offset operand))
227 ((eq 'null (sc-name (tn-sc operand)))
228 null-offset)
230 (t (error "Don't know how to encode TN ~A as a SHIFTER-OPERAND" operand))))
232 (shifter-operand
233 (let ((Rm (tn-offset (shifter-operand-register operand)))
234 (shift-code (shifter-operand-function-code operand))
235 (shift-amount (shifter-operand-operand operand)))
236 (etypecase shift-amount
237 (integer
238 (dpb shift-amount (byte 5 7)
239 (dpb shift-code (byte 2 5)
240 Rm)))
242 (dpb (tn-offset shift-amount) (byte 4 8)
243 (dpb shift-code (byte 2 5)
244 (dpb 1 (byte 1 4)
245 Rm)))))))))
247 (defmacro composite-immediate-instruction (op r x y &key fixnumize neg-op invert-y invert-r single-op-op first-op first-no-source)
248 ;; Successively applies 8-bit wide chunks of Y to X using OP storing the result in R.
250 ;; If FIXNUMIZE is true, Y is fixnumized before being used.
251 ;; If NEG-OP is given and Y is negative, NEG-OP is used instead of OP.
252 ;; If INVERT-Y is given LOGNOT is applied to Y before it being used (but after possibly
253 ;; being fixnumized.
254 ;; If INVERT-R is given R is bit wise inverted at the end.
255 ;; If SINGLE-OP-OP is given and (possibly fixnumized) Y fits into a single ARM immediate
256 ;; it is used for a single operation instead of OP.
257 ;; If FIRST-OP is given, it is used in the first iteration instead of OP.
258 ;; If FIRST-NO-SOURCE is given, there will be ne source register (X) in the first iteration.
259 (let ((bytespec (gensym "bytespec"))
260 (value (gensym "value"))
261 (transformed (gensym "transformed")))
262 (labels ((instruction (source-reg op neg-op &optional no-source)
263 `(,@(if neg-op
264 `((if (< ,y 0)
265 (inst ,neg-op ,r ,@(when (not no-source)`(,source-reg))
266 (mask-field ,bytespec ,value))
267 (inst ,op ,r ,@(when (not no-source) `(,source-reg))
268 (mask-field ,bytespec ,value))))
269 `((inst ,op ,r ,@(when (not no-source) `(,source-reg))
270 (mask-field ,bytespec ,value))))
271 (setf (ldb ,bytespec ,value) 0)))
272 (composite ()
273 `((let ((,bytespec (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))))
274 ,@(instruction x (or first-op op) neg-op first-no-source))
275 (do ((,bytespec (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))
276 (byte 8 (logandc1 1 (lowest-set-bit-index ,value)))))
277 ((zerop ,value))
278 ,@(instruction r op neg-op)
279 ,@(when invert-r
280 `((inst mvn ,r ,r)))))))
281 `(let* ((,transformed ,(if fixnumize
282 `(fixnumize ,y)
283 `,y))
284 (,value (ldb (byte 32 0)
285 ,@(if neg-op
286 `((if (< ,transformed 0) (- ,transformed) ,transformed))
287 (if invert-y
288 `((lognot ,transformed))
289 `(,transformed))))))
290 ,@(if single-op-op
291 `((handler-case
292 (progn
293 (inst ,single-op-op ,r ,x ,transformed))
294 (cannot-encode-immediate-operand ()
295 ,@(composite))))
296 (composite))))))
299 ;;;; Addressing mode 2 support
301 ;;; Addressing mode 2 ostensibly has 9 formats. These are formed from
302 ;;; a cross product of three address calculations and three base
303 ;;; register writeback modes. As one of the address calculations is a
304 ;;; scaled register calculation identical to the mode 1 register shift
305 ;;; by constant, we reuse the shifter-operand structure and its public
306 ;;; constructors.
308 (defstruct memory-operand
309 base
310 offset
311 direction
312 mode)
314 ;;; The @ macro is used to encode a memory addressing mode. The
315 ;;; parameters for the base form are a base register, an optional
316 ;;; offset (either an integer, a register tn or a shifter-operand
317 ;;; structure with a constant shift amount, optionally within a unary
318 ;;; - form), and a base register writeback mode (either :offset,
319 ;;; :pre-index, or :post-index). The alternative form uses a label as
320 ;;; the base register, and accepts only (optionally negated) integers
321 ;;; as offsets, and requires a mode of :offset.
322 (defun %@ (base offset direction mode)
323 (when (label-p base)
324 (aver (eq mode :offset))
325 (aver (integerp offset)))
327 (when (shifter-operand-p offset)
328 (aver (integerp (shifter-operand-operand offset))))
330 ;; Fix up direction with negative offsets.
331 (when (and (not (label-p base))
332 (integerp offset)
333 (< offset 0))
334 (setf offset (- offset))
335 (setf direction (if (eq direction :up) :down :up)))
337 (make-memory-operand :base base :offset offset
338 :direction direction :mode mode))
340 (defmacro @ (base &optional (offset 0) (mode :offset))
341 (let* ((direction (if (and (consp offset)
342 (eq (car offset) '-)
343 (null (cddr offset)))
344 :down
345 :up))
346 (offset (if (eq direction :down) (cadr offset) offset)))
347 `(%@ ,base ,offset ,direction ,mode)))
349 ;;;; Data-processing instructions
351 ;;; Data processing instructions have a 4-bit opcode field and a 1-bit
352 ;;; "S" field for updating condition bits. They are adjacent, so we
353 ;;; roll them into one 5-bit field for convenience.
355 (define-bitfield-emitter emit-dp-instruction 32
356 (byte 4 28) (byte 2 26) (byte 1 25) (byte 5 20)
357 (byte 4 16) (byte 4 12) (byte 12 0))
359 ;;; There are 16 data processing instructions, with a breakdown as
360 ;;; follows:
362 ;;; 1.) Two "move" instructions, with no "source" operand (they have
363 ;;; destination and shifter operands only).
365 ;;; 2.) Four "test" instructions, with no "destination" operand.
366 ;;; These instructions always have their "S" bit set, though it
367 ;;; is not specified in their mnemonics.
369 ;;; 3.) Ten "normal" instructions, with all three operands.
371 ;;; Aside from this, the instructions all have a regular encoding, so
372 ;;; we can use a single macro to define them.
374 (defmacro define-data-processing-instruction (instruction opcode dest-p src-p)
375 `(define-instruction ,instruction (segment &rest args)
376 (:emitter
377 (with-condition-defaulted (args (condition ,@(if dest-p '(dest))
378 ,@(if src-p '(src))
379 shifter-operand))
380 ,(if dest-p '(aver (register-p dest)))
381 ,(if src-p '(aver (register-p src)))
382 (let ((shifter-operand (encode-shifter-operand shifter-operand)))
383 (emit-dp-instruction segment
384 (conditional-opcode condition)
386 (ldb (byte 1 25) shifter-operand)
387 ,opcode
388 ,(if src-p '(tn-offset src) 0)
389 ,(if dest-p '(tn-offset dest) 0)
390 (ldb (byte 12 0) shifter-operand)))))))
392 (define-data-processing-instruction and #x00 t t)
393 (define-data-processing-instruction ands #x01 t t)
394 (define-data-processing-instruction eor #x02 t t)
395 (define-data-processing-instruction eors #x03 t t)
396 (define-data-processing-instruction sub #x04 t t)
397 (define-data-processing-instruction subs #x05 t t)
398 (define-data-processing-instruction rsb #x06 t t)
399 (define-data-processing-instruction rsbs #x07 t t)
400 (define-data-processing-instruction add #x08 t t)
401 (define-data-processing-instruction adds #x09 t t)
402 (define-data-processing-instruction adc #x0a t t)
403 (define-data-processing-instruction adcs #x0b t t)
404 (define-data-processing-instruction sbc #x0c t t)
405 (define-data-processing-instruction sbcs #x0d t t)
406 (define-data-processing-instruction rsc #x0e t t)
407 (define-data-processing-instruction rscs #x0f t t)
408 (define-data-processing-instruction orr #x18 t t)
409 (define-data-processing-instruction orrs #x19 t t)
410 (define-data-processing-instruction bic #x1c t t)
411 (define-data-processing-instruction bics #x1d t t)
413 (define-data-processing-instruction tst #x11 nil t)
414 (define-data-processing-instruction teq #x13 nil t)
415 (define-data-processing-instruction cmp #x15 nil t)
416 (define-data-processing-instruction cmn #x17 nil t)
418 (define-data-processing-instruction mov #x1a t nil)
419 (define-data-processing-instruction movs #x1b t nil)
420 (define-data-processing-instruction mvn #x1e t nil)
421 (define-data-processing-instruction mvns #x1f t nil)
423 ;;;; Exception-generating instructions
425 ;;; There are two exception-generating instructions. One, BKPT, is
426 ;;; ostensibly used as a breakpoint instruction, and to communicate
427 ;;; with debugging hardware. The other, SWI, is intended for use as a
428 ;;; system call interface. We need both because, at least on some
429 ;;; platforms, the only breakpoint trap that works properly is a
430 ;;; syscall.
432 (define-bitfield-emitter emit-swi-instruction 32
433 (byte 4 28) (byte 4 24) (byte 24 0))
435 (define-instruction swi (segment &rest args)
436 (:emitter
437 (with-condition-defaulted (args (condition code))
438 (emit-swi-instruction segment
439 (conditional-opcode condition)
440 #b1111 code))))
442 (define-bitfield-emitter emit-bkpt-instruction 32
443 (byte 4 28) (byte 8 20) (byte 12 8) (byte 4 4) (byte 4 0))
445 (define-instruction bkpt (segment code)
446 (:emitter
447 (emit-bkpt-instruction segment #b1110 #b00010010
448 (ldb (byte 12 4) code)
449 #b0111
450 (ldb (byte 4 0) code))))
452 ;;;; Miscellaneous arithmetic instructions
454 (define-bitfield-emitter emit-clz-instruction 32
455 (byte 4 28) (byte 12 16) (byte 4 12) (byte 8 4) (byte 4 0))
457 (define-instruction clz (segment &rest args)
458 (:emitter
459 (with-condition-defaulted (args (condition dest src))
460 (aver (register-p dest))
461 (aver (register-p src))
462 (emit-clz-instruction segment (conditional-opcode condition)
463 #b000101101111
464 (tn-offset dest)
465 #b11110001
466 (tn-offset src)))))
468 ;;;; Branch instructions
470 (define-bitfield-emitter emit-branch-instruction 32
471 (byte 4 28) (byte 4 24) (byte 24 0))
473 (defun emit-branch-back-patch (segment condition opcode dest)
474 (emit-back-patch segment 4
475 (lambda (segment posn)
476 (emit-branch-instruction segment
477 (conditional-opcode condition)
478 opcode
479 (ldb (byte 24 2)
480 (- (label-position dest)
481 (+ posn 8)))))))
483 (define-instruction b (segment &rest args)
484 (:emitter
485 (with-condition-defaulted (args (condition dest))
486 (aver (label-p dest))
487 (emit-branch-back-patch segment condition #b1010 dest))))
489 (define-instruction bl (segment &rest args)
490 (:emitter
491 (with-condition-defaulted (args (condition dest))
492 (aver (label-p dest))
493 (emit-branch-back-patch segment condition #b1011 dest))))
495 (define-bitfield-emitter emit-branch-exchange-instruction 32
496 (byte 4 28) (byte 8 20) (byte 4 16) (byte 4 12)
497 (byte 4 8) (byte 4 4) (byte 4 0))
499 (define-instruction bx (segment &rest args)
500 (:emitter
501 (with-condition-defaulted (args (condition dest))
502 (aver (register-p dest))
503 (emit-branch-exchange-instruction segment
504 (conditional-opcode condition)
505 #b00010010 #b1111 #b1111
506 #b1111 #b0001 (tn-offset dest)))))
508 (define-instruction blx (segment &rest args)
509 (:emitter
510 (with-condition-defaulted (args (condition dest))
511 (aver (register-p dest))
512 (emit-branch-exchange-instruction segment
513 (conditional-opcode condition)
514 #b00010010 #b1111 #b1111
515 #b1111 #b0011 (tn-offset dest)))))
517 ;;;; Semaphore instructions
519 (defun emit-semaphore-instruction (segment opcode condition dest value address)
520 (aver (register-p dest))
521 (aver (register-p value))
522 (aver (memory-operand-p address))
523 (aver (zerop (memory-operand-offset address)))
524 (aver (eq :offset (memory-operand-mode address)))
525 (emit-dp-instruction segment (conditional-opcode condition)
526 #b00 0 opcode (tn-offset (memory-operand-base address))
527 (tn-offset dest)
528 (dpb #b1001 (byte 4 4) (tn-offset value))))
530 (define-instruction swp (segment &rest args)
531 (:emitter
532 (with-condition-defaulted (args (condition dest value address))
533 (emit-semaphore-instruction segment #b10000
534 condition dest value address))))
536 (define-instruction swpb (segment &rest args)
537 (:emitter
538 (with-condition-defaulted (args (condition dest value address))
539 (emit-semaphore-instruction segment #b10100
540 condition dest value address))))
542 ;;;; Status-register instructions
544 (define-instruction mrs (segment &rest args)
545 (:emitter
546 (with-condition-defaulted (args (condition dest reg))
547 (aver (register-p dest))
548 (aver (member reg '(:cpsr :spsr)))
549 (emit-dp-instruction segment (conditional-opcode condition)
550 #b00 0 (if (eq reg :cpsr) #b10000 #b10100)
551 #b1111 (tn-offset dest) 0))))
553 (defun encode-status-register-fields (fields)
554 (let ((fields (string fields)))
555 (labels ((frob (mask index)
556 (let* ((field (aref fields index))
557 (field-mask (cdr (assoc field
558 '((#\C . #b0001) (#\X . #b0010)
559 (#\S . #b0100) (#\F . #b1000))
560 :test #'char=))))
561 (unless field-mask
562 (error "bad status register field desginator ~S" fields))
563 (if (< (1+ index) (length fields))
564 (frob (logior mask field-mask) (1+ index))
565 (logior mask field-mask)))))
566 (frob 0 0))))
568 (defmacro cpsr (fields)
569 (encode-status-register-fields fields))
571 (defmacro spsr (fields)
572 (logior #b10000 (encode-status-register-fields fields)))
574 (define-instruction msr (segment &rest args)
575 (:emitter
576 (with-condition-defaulted (args (condition field-mask src))
577 (aver (or (register-p src)
578 (integerp src)))
579 (let ((encoded-src (encode-shifter-operand src)))
580 (emit-dp-instruction segment (conditional-opcode condition)
581 #b00 (ldb (byte 1 25) encoded-src)
582 (if (logbitp 4 field-mask) #b10110 #b10010)
583 field-mask #b1111
584 (ldb (byte 12 0) encoded-src))))))
586 ;;;; Multiply instructions
588 (define-bitfield-emitter emit-multiply-instruction 32
589 (byte 4 28) (byte 8 20) (byte 4 16) (byte 4 12)
590 (byte 4 8) (byte 4 4) (byte 4 0))
592 (macrolet
593 ((define-multiply-instruction (name field-mapping opcode1 opcode2)
594 (let ((arglist (ecase field-mapping
595 (:dzsm '(dest src multiplicand))
596 (:dnsm '(dest src multiplicand num))
597 (:ddsm '(dest-lo dest src multiplicand)))))
598 `(define-instruction ,name (segment &rest args)
599 (:emitter
600 (with-condition-defaulted (args (condition ,@arglist))
601 ,@(loop
602 for arg in arglist
603 collect `(aver (register-p ,arg)))
604 (emit-multiply-instruction segment (conditional-opcode condition)
605 ,opcode1
606 (tn-offset dest)
607 ,(ecase field-mapping
608 (:dzsm 0)
609 (:dnsm '(tn-offset num))
610 (:ddsm '(tn-offset dest-lo)))
611 (tn-offset src)
612 ,opcode2
613 (tn-offset multiplicand))))))))
615 (define-multiply-instruction mul :dzsm #b00000000 #b1001)
616 (define-multiply-instruction muls :dzsm #b00000001 #b1001)
617 (define-multiply-instruction mla :dnsm #b00000010 #b1001)
618 (define-multiply-instruction mlas :dnsm #b00000011 #b1001)
620 (define-multiply-instruction umull :ddsm #b00001000 #b1001)
621 (define-multiply-instruction umulls :ddsm #b00001001 #b1001)
622 (define-multiply-instruction umlal :ddsm #b00001010 #b1001)
623 (define-multiply-instruction umlals :ddsm #b00001011 #b1001)
625 (define-multiply-instruction smull :ddsm #b00001100 #b1001)
626 (define-multiply-instruction smulls :ddsm #b00001101 #b1001)
627 (define-multiply-instruction smlal :ddsm #b00001110 #b1001)
628 (define-multiply-instruction smlals :ddsm #b00001111 #b1001)
630 (define-multiply-instruction smlabb :dnsm #b00010000 #b1000)
631 (define-multiply-instruction smlatb :dnsm #b00010000 #b1010)
632 (define-multiply-instruction smlabt :dnsm #b00010000 #b1100)
633 (define-multiply-instruction smlatt :dnsm #b00010000 #b1110)
635 (define-multiply-instruction smlalbb :ddsm #b00010100 #b1000)
636 (define-multiply-instruction smlaltb :ddsm #b00010100 #b1010)
637 (define-multiply-instruction smlalbt :ddsm #b00010100 #b1100)
638 (define-multiply-instruction smlaltt :ddsm #b00010100 #b1110)
640 (define-multiply-instruction smulbb :dzsm #b00010110 #b1000)
641 (define-multiply-instruction smultb :dzsm #b00010110 #b1010)
642 (define-multiply-instruction smulbt :dzsm #b00010110 #b1100)
643 (define-multiply-instruction smultt :dzsm #b00010110 #b1110)
645 (define-multiply-instruction smlawb :dnsm #b00010010 #b1000)
646 (define-multiply-instruction smlawt :dnsm #b00010010 #b1100)
648 (define-multiply-instruction smulwb :dzsm #b00010010 #b1010)
649 (define-multiply-instruction smulwt :dzsm #b00010010 #b1110))
651 ;;;; Load/store instructions
653 ;;; Emit a load/store instruction. CONDITION is a condition code
654 ;;; name, KIND is :load or :store, WIDTH is :word or :byte, DATA is a
655 ;;; register TN and ADDRESS is either a memory-operand structure or a
656 ;;; stack TN.
657 (defun emit-load/store-instruction (segment condition kind width data address)
658 (flet ((compute-opcode (direction mode)
659 (let ((opcode-bits '(:load #b00001 :store #b00000
660 :word #b00000 :byte #b00100
661 :up #b01000 :down #b00000
662 :offset #b10000
663 :pre-index #b10010
664 :post-index #b00000)))
665 (reduce #'logior (list kind width direction mode)
666 :key (lambda (value) (getf opcode-bits value))))))
667 (etypecase address
668 (memory-operand
669 (let* ((base (memory-operand-base address))
670 (offset (memory-operand-offset address))
671 (direction (memory-operand-direction address))
672 (mode (memory-operand-mode address))
673 (cond-bits (conditional-opcode condition)))
674 (cond
675 ((label-p base)
676 (emit-back-patch
677 segment 4
678 (lambda (segment posn)
679 (let* ((label-delta (- (label-position base)
680 (+ posn 8)))
681 (offset-delta (if (eq direction :up)
682 offset
683 (- offset)))
684 (overall-delta (+ label-delta
685 offset-delta))
686 (absolute-delta (abs overall-delta)))
687 (aver (typep absolute-delta '(unsigned-byte 12)))
688 (emit-dp-instruction segment cond-bits #b01 0
689 (compute-opcode (if (< overall-delta 0)
690 :down
691 :up)
692 mode)
693 pc-offset (tn-offset data)
694 absolute-delta)))))
695 ((integerp offset)
696 (aver (typep offset '(unsigned-byte 12)))
697 (emit-dp-instruction segment cond-bits #b01 0
698 (compute-opcode direction mode)
699 (tn-offset base) (tn-offset data)
700 offset))
702 (emit-dp-instruction segment cond-bits #b01 1
703 (compute-opcode direction mode)
704 (tn-offset base) (tn-offset data)
705 (encode-shifter-operand offset))))))
707 #+(or)
709 ;; FIXME: This is for stack TN references, and needs must be
710 ;; implemented.
711 ))))
713 (macrolet
714 ((define-load/store-instruction (name kind width)
715 `(define-instruction ,name (segment &rest args)
716 (:emitter
717 (with-condition-defaulted (args (condition reg address))
718 (aver (or (register-p reg)
719 ,@(when (eq :store kind)
720 '((and (tn-p reg)
721 (eq 'null (sc-name (tn-sc reg))))))))
722 (emit-load/store-instruction segment condition
723 ,kind ,width
724 (if (register-p reg) reg null-tn)
725 address))))))
726 (define-load/store-instruction ldr :load :word)
727 (define-load/store-instruction ldrb :load :byte)
728 (define-load/store-instruction str :store :word)
729 (define-load/store-instruction strb :store :byte))
731 ;;; Emit a miscellaneous load/store instruction. CONDITION is a
732 ;;; condition code name, OPCODE1 is the low bit of the first opcode
733 ;;; field, OPCODE2 is the second opcode field, DATA is a register TN
734 ;;; and ADDRESS is either a memory-operand structure or a stack TN.
735 (defun emit-misc-load/store-instruction (segment condition opcode1
736 opcode2 data address)
737 (flet ((compute-opcode (kind direction mode)
738 (let ((opcode-bits '(:register #b00000 :immediate #b00100
739 :up #b01000 :down #b00000
740 :offset #b10000
741 :pre-index #b10010
742 :post-index #b00000)))
743 (reduce #'logior (list kind direction mode)
744 :key (lambda (value) (getf opcode-bits value))))))
745 (etypecase address
746 (memory-operand
747 (let* ((base (memory-operand-base address))
748 (offset (memory-operand-offset address))
749 (direction (memory-operand-direction address))
750 (mode (memory-operand-mode address))
751 (cond-bits (conditional-opcode condition)))
752 (cond
753 ((label-p base)
754 (emit-back-patch
755 segment 4
756 (lambda (segment posn)
757 (let* ((label-delta (- (label-position base)
758 (+ posn 8)))
759 (offset-delta (if (eq direction :up)
760 offset
761 (- offset)))
762 (overall-delta (+ label-delta
763 offset-delta))
764 (absolute-delta (abs overall-delta)))
765 (aver (typep absolute-delta '(unsigned-byte 8)))
766 (emit-multiply-instruction segment cond-bits
767 (logior opcode1
768 (compute-opcode :immedaite
769 (if (< overall-delta 0)
770 :down
771 :up)
772 mode))
773 (tn-offset base) (tn-offset data)
774 (ldb (byte 4 4) absolute-delta)
775 opcode2 absolute-delta)))))
776 ((integerp offset)
777 (aver (typep offset '(unsigned-byte 8)))
778 (emit-multiply-instruction segment cond-bits
779 (logior opcode1
780 (compute-opcode :immediate direction mode))
781 (tn-offset base) (tn-offset data)
782 (ldb (byte 4 4) offset)
783 opcode2 offset))
784 ((register-p offset)
785 (emit-multiply-instruction segment cond-bits
786 (logior opcode1
787 (compute-opcode :register direction mode))
788 (tn-offset base) (tn-offset data)
789 0 opcode2 (tn-offset offset)))
791 (error "bad thing for a miscellaneous load/store address ~S"
792 address)))))
794 #+(or)
796 ;; FIXME: This is for stack TN references, and needs must be
797 ;; implemented.
798 ))))
800 (macrolet
801 ((define-misc-load/store-instruction (name opcode1 opcode2 double-width)
802 `(define-instruction ,name (segment &rest args)
803 (:emitter
804 (with-condition-defaulted (args (condition reg address))
805 (aver (register-p reg))
806 ,(when double-width '(aver (evenp (tn-offset reg))))
807 (emit-misc-load/store-instruction segment condition
808 ,opcode1 ,opcode2
809 reg address))))))
810 (define-misc-load/store-instruction strh 0 #b1011 nil)
811 (define-misc-load/store-instruction ldrd 0 #b1101 t)
812 (define-misc-load/store-instruction strd 0 #b1111 t)
814 (define-misc-load/store-instruction ldrh 1 #b1011 nil)
815 (define-misc-load/store-instruction ldrsb 1 #b1101 nil)
816 (define-misc-load/store-instruction ldrsh 1 #b1111 nil))
818 ;;;; Boxed-object computation instructions (for LRA and CODE)
820 ;;; Compute the address of a CODE object by parsing the header of a
821 ;;; nearby LRA or SIMPLE-FUN.
822 (define-instruction compute-code (segment code lip object-label temp)
823 (:vop-var vop)
824 (:emitter
825 (emit-back-patch
826 segment 12
827 (lambda (segment position)
828 (assemble (segment vop)
829 ;; Calculate the address of the code component. This is an
830 ;; exercise in excess cleverness. First, we calculate (from
831 ;; our program counter only) the address of OBJECT-LABEL plus
832 ;; OTHER-POINTER-LOWTAG. The extra two words are to
833 ;; compensate for the offset applied by ARM CPUs when reading
834 ;; the program counter.
835 (inst sub lip pc-tn (- ;; The 8 below is the displacement
836 ;; from reading the program counter.
837 (+ position 8)
838 (+ (label-position object-label)
839 other-pointer-lowtag)))
840 ;; Next, we read the function header.
841 (inst ldr temp (@ lip (- other-pointer-lowtag)))
842 ;; And finally we use the header value (a count in words),
843 ;; plus the fact that the top two bits of the widetag are
844 ;; clear (SIMPLE-FUN-HEADER-WIDETAG is #x2A and
845 ;; RETURN-PC-HEADER-WIDETAG is #x36) to compute the boxed
846 ;; address of the code component.
847 (inst sub code lip (lsr temp (- 8 word-shift))))))))
849 ;;; Compute the address of a nearby LRA object by dead reckoning from
850 ;;; the location of the current instruction.
851 (define-instruction compute-lra (segment dest lip lra-label)
852 (:vop-var vop)
853 (:emitter
854 ;; We can compute the LRA in a single instruction if the overall
855 ;; offset puts it to within an 8-bit displacement. Otherwise, we
856 ;; need to load it by parts into LIP until we're down to an 8-bit
857 ;; displacement, and load the final 8 bits into DEST. We may
858 ;; safely presume that an overall displacement may be up to 24 bits
859 ;; wide (the PPC backend has special provision for branches over 15
860 ;; bits, which implies that segments can become large, but a 16
861 ;; megabyte segment (24 bits of displacement) is ridiculous), so we
862 ;; need to cover a range of up to three octets of displacement.
863 (labels ((compute-delta (position &optional magic-value)
864 (- (+ (label-position lra-label
865 (when magic-value position)
866 magic-value)
867 other-pointer-lowtag)
868 ;; The 8 below is the displacement
869 ;; from reading the program counter.
870 (+ position 8)))
872 (load-chunk (segment delta dst src chunk)
873 (assemble (segment vop)
874 (if (< delta 0)
875 (inst sub dst src chunk)
876 (inst add dst src chunk))))
878 (three-instruction-emitter (segment position)
879 (let* ((delta (compute-delta position))
880 (absolute-delta (abs delta)))
881 (load-chunk segment delta
882 lip pc-tn (mask-field (byte 8 16) absolute-delta))
883 (load-chunk segment delta
884 lip lip (mask-field (byte 8 8) absolute-delta))
885 (load-chunk segment delta
886 dest lip (mask-field (byte 8 0) absolute-delta))))
888 (two-instruction-emitter (segment position)
889 (let* ((delta (compute-delta position))
890 (absolute-delta (abs delta)))
891 (assemble (segment vop)
892 (load-chunk segment delta
893 lip pc-tn (mask-field (byte 8 8) absolute-delta))
894 (load-chunk segment delta
895 dest lip (mask-field (byte 8 0) absolute-delta)))))
897 (one-instruction-emitter (segment position)
898 (let* ((delta (compute-delta position))
899 (absolute-delta (abs delta)))
900 (assemble (segment vop)
901 (load-chunk segment delta
902 dest pc-tn absolute-delta))))
904 (two-instruction-maybe-shrink (segment posn magic-value)
905 (let ((delta (compute-delta posn magic-value)))
906 (when (<= (integer-length delta) 8)
907 (emit-back-patch segment 4
908 #'one-instruction-emitter)
909 t)))
911 (three-instruction-maybe-shrink (segment posn magic-value)
912 (let ((delta (compute-delta posn magic-value)))
913 (when (<= (integer-length delta) 16)
914 (emit-chooser segment 8 2
915 #'two-instruction-maybe-shrink
916 #'two-instruction-emitter)
917 t))))
918 (emit-chooser
919 ;; We need to emit up to three instructions, which is 12 octets.
920 ;; This preserves a mere two bits of alignment.
921 segment 12 2
922 #'three-instruction-maybe-shrink
923 #'three-instruction-emitter))))
925 ;;; Load a register from a "nearby" LABEL by dead reckoning from the
926 ;;; location of the current instruction.
927 (define-instruction load-from-label (segment &rest args)
928 (:vop-var vop)
929 (:emitter
930 (with-condition-defaulted (args (condition dest lip label))
931 ;; We can load the word addressed by a label in a single
932 ;; instruction if the overall offset puts it to within a 12-bit
933 ;; displacement. Otherwise, we need to build an address by parts
934 ;; into LIP until we're down to a 12-bit displacement, and then
935 ;; apply the final 12 bits with LDR. For now, we'll allow up to 20
936 ;; bits of displacement, as that should be easy to implement, and a
937 ;; megabyte large code object is already a bit unwieldly. If
938 ;; neccessary, we can expand to a 28 bit displacement.
939 (labels ((compute-delta (position &optional magic-value)
940 (- (label-position label
941 (when magic-value position)
942 magic-value)
943 ;; The 8 below is the displacement
944 ;; from reading the program counter.
945 (+ position 8)))
947 (load-chunk (segment delta dst src chunk)
948 (assemble (segment vop)
949 (if (< delta 0)
950 (inst sub condition dst src chunk)
951 (inst add condition dst src chunk))))
953 (two-instruction-emitter (segment position)
954 (let* ((delta (compute-delta position))
955 (absolute-delta (abs delta)))
956 (assemble (segment vop)
957 (load-chunk segment delta
958 lip pc-tn (mask-field (byte 8 12) absolute-delta))
959 (inst ldr condition dest (@ lip (mask-field (byte 12 0) delta))))))
961 (one-instruction-emitter (segment position)
962 (let* ((delta (compute-delta position)))
963 (assemble (segment vop)
964 (inst ldr condition dest (@ pc-tn delta)))))
966 (two-instruction-maybe-shrink (segment posn magic-value)
967 (let ((delta (compute-delta posn magic-value)))
968 (when (<= (integer-length delta) 12)
969 (emit-back-patch segment 4
970 #'one-instruction-emitter)
971 t))))
972 (emit-chooser
973 ;; We need to emit up to two instructions, which is 8 octets,
974 ;; but might wish to emit only one. This preserves a mere two
975 ;; bits of alignment.
976 segment 8 2
977 #'two-instruction-maybe-shrink
978 #'two-instruction-emitter)))))
980 ;; data processing floating point instructions
981 (define-bitfield-emitter emit-fp-dp-instruction 32
982 (byte 4 28) ; cond
983 (byte 4 24) ; #b1110
984 (byte 1 23) ; p
985 (byte 1 22) ; D
986 (byte 1 21) ; q
987 (byte 1 20) ; r
988 (byte 4 16) ; Fn || extension op
989 (byte 4 12) ; Fd
990 (byte 3 9) ; #b101
991 (byte 1 8) ; double/single precission
992 (byte 1 7) ; N || extension op
993 (byte 1 6) ; s
994 (byte 1 5) ; M
995 (byte 1 4) ; #b0
996 (byte 4 0)) ; Fm
998 (defun low-bit-float-reg (reg-tn)
999 (logand 1 (tn-offset reg-tn)))
1001 (defun high-bits-float-reg (reg-tn)
1002 (ash (tn-offset reg-tn) -1))
1004 (defmacro define-binary-fp-data-processing-instruction (name precision p q r s)
1005 (let ((precision-flag (ecase precision
1006 (:single 0)
1007 (:double 1))))
1008 `(define-instruction ,name (segment &rest args)
1009 (:emitter
1010 (with-condition-defaulted (args (condition dest op-n op-m))
1011 (emit-fp-dp-instruction segment
1012 (conditional-opcode condition)
1013 #b1110
1015 (low-bit-float-reg dest)
1018 (high-bits-float-reg op-n)
1019 (high-bits-float-reg dest)
1020 #b101
1021 ,precision-flag
1022 (low-bit-float-reg op-n)
1024 (low-bit-float-reg op-m)
1026 (high-bits-float-reg op-m)))))))
1028 (defmacro define-binary-fp-data-processing-instructions (root p q r s)
1029 `(progn
1030 (define-binary-fp-data-processing-instruction ,(symbolicate root 's) :single ,p ,q ,r ,s)
1031 (define-binary-fp-data-processing-instruction ,(symbolicate root 'd) :double ,p ,q ,r ,s)))
1033 (define-binary-fp-data-processing-instructions fmac 0 0 0 0)
1034 (define-binary-fp-data-processing-instructions fnmac 0 0 0 1)
1035 (define-binary-fp-data-processing-instructions fmsc 0 0 1 0)
1036 (define-binary-fp-data-processing-instructions fnmsc 0 0 1 1)
1037 (define-binary-fp-data-processing-instructions fmul 0 1 0 0)
1038 (define-binary-fp-data-processing-instructions fnmul 0 1 0 1)
1039 (define-binary-fp-data-processing-instructions fadd 0 1 1 0)
1040 (define-binary-fp-data-processing-instructions fsub 0 1 1 1)
1041 (define-binary-fp-data-processing-instructions fdiv 1 0 0 0)
1043 (defmacro define-unary-fp-data-processing-instruction (name precision fn n)
1044 (let ((precision-flag (ecase precision
1045 (:single 0)
1046 (:double 1))))
1047 `(define-instruction ,name (segment &rest args)
1048 (:emitter
1049 (with-condition-defaulted (args (condition dest op-m))
1050 (emit-fp-dp-instruction segment
1051 (conditional-opcode condition)
1052 #b1110
1054 (low-bit-float-reg dest)
1058 (high-bits-float-reg dest)
1059 #b101
1060 ,precision-flag
1063 (low-bit-float-reg op-m)
1065 (high-bits-float-reg op-m)))))))
1067 (defmacro define-unary-fp-data-processing-instructions (root fn n)
1068 `(progn
1069 (define-unary-fp-data-processing-instruction ,(symbolicate root 's) :single ,fn ,n)
1070 (define-unary-fp-data-processing-instruction ,(symbolicate root 'd) :double ,fn ,n)))
1072 (define-unary-fp-data-processing-instructions fcpy #b0000 0)
1073 (define-unary-fp-data-processing-instructions fabs #b0000 1)
1074 (define-unary-fp-data-processing-instructions fneg #b0001 0)
1075 (define-unary-fp-data-processing-instructions fsqrt #b0001 1)
1076 (define-unary-fp-data-processing-instructions fcmp #b0100 0)
1077 (define-unary-fp-data-processing-instructions fcmpe #b0100 1)
1078 (define-unary-fp-data-processing-instructions fcmpz #b0101 0)
1079 (define-unary-fp-data-processing-instructions fcmpez #b0101 1)
1080 (define-unary-fp-data-processing-instructions fuito #b1000 0)
1081 (define-unary-fp-data-processing-instructions fsito #b1000 1)
1082 (define-unary-fp-data-processing-instructions ftoui #b1100 0)
1083 (define-unary-fp-data-processing-instructions ftouiz #b1100 1)
1084 (define-unary-fp-data-processing-instructions ftosi #b1101 0)
1085 (define-unary-fp-data-processing-instructions ftosiz #b1101 1)
1087 (define-unary-fp-data-processing-instruction fcvtds :single #b0111 1)
1088 (define-unary-fp-data-processing-instruction fcvtsd :double #b0111 1)
1090 ;;; Load/Store Float Instructions
1092 (define-bitfield-emitter emit-fp-ls-instruction 32
1093 (byte 4 28) ; cond
1094 (byte 3 25) ; #b110
1095 (byte 1 24) ; P
1096 (byte 1 23) ; U
1097 (byte 1 22) ; D
1098 (byte 1 21) ; W
1099 (byte 1 20) ; L
1100 (byte 4 16) ; Rn
1101 (byte 4 12) ; Fd
1102 (byte 3 9) ; #b101
1103 (byte 1 8) ; double/single precission
1104 (byte 8 0)) ; offset
1106 ;; Define a load/store multiple floating point instruction. PRECISION is
1107 ;; :SINGLE for single precision values and :DOUBLE for double precision values.
1108 ;; DIRECTION has to be either :LOAD or :STORE.
1109 ;; If INC-OFFSET is true, the offset part of the instruction will be incremented by 1
1110 ;; indicating in the double case a load/store unknown instruction.
1111 (defmacro define-load-store-multiple-fp-instruction (name precision direction &optional inc-offset)
1112 (let ((precision-flag (ecase precision
1113 (:single 0)
1114 (:double 1)))
1115 (direction-flag (ecase direction
1116 (:load 1)
1117 (:store 0))))
1118 `(define-instruction ,name (segment &rest args)
1119 (:emitter
1120 (with-condition-defaulted (args (condition address base-reg reg-count))
1121 (let* ((mode (cond
1122 ((consp address)
1123 (cdr address))
1124 (t :unindexed)))
1125 (p (ecase mode
1126 ((:unindexed :increment) 0)
1127 ((:decrement) 1)))
1128 (u (ecase mode
1129 ((:unindexed :increment) 1)
1130 ((:decrement) 0)))
1131 (w (ecase mode
1132 ((:unindexed) 0)
1133 ((:increment :decrement) 1))))
1134 (emit-fp-ls-instruction segment
1135 (conditional-opcode condition)
1136 #b110
1139 (low-bit-float-reg base-reg)
1141 ,direction-flag
1142 (tn-offset address)
1143 (high-bits-float-reg base-reg)
1144 #b101
1145 ,precision-flag
1146 ,(ecase precision
1147 (:single 'reg-count)
1148 (:double `(+ (* 2 reg-count)
1149 ,(if inc-offset 1 0)))))))))))
1151 ;; multiple single precision
1152 (define-load-store-multiple-fp-instruction fstms :single :store)
1153 (define-load-store-multiple-fp-instruction fldms :single :load)
1154 ;; multiple double precision
1155 (define-load-store-multiple-fp-instruction fstmd :double :store)
1156 (define-load-store-multiple-fp-instruction fldmd :double :load)
1157 ;; multiple double precision registers of unknown content (needs up to 2 * reg-count + 1 words of space)
1158 (define-load-store-multiple-fp-instruction fstmx :double :store t)
1159 (define-load-store-multiple-fp-instruction fldmx :double :load t)
1161 ;; Define a load/store one floating point instruction. PRECISION is
1162 ;; :SINGLE for single precision values and :DOUBLE for double precision values.
1163 ;; DIRECTION has to be either :LOAD or :STORE.
1164 (defmacro define-load-store-one-fp-instruction (name precision direction)
1165 (let ((precision-flag (ecase precision
1166 (:single 0)
1167 (:double 1)))
1168 (direction-flag (ecase direction
1169 (:load 1)
1170 (:store 0))))
1171 `(define-instruction ,name (segment &rest args)
1172 (:emitter
1173 (with-condition-defaulted (args (condition float-reg memory-operand))
1174 (let ((base (memory-operand-base memory-operand))
1175 (offset (memory-operand-offset memory-operand))
1176 (direction (memory-operand-direction memory-operand)))
1177 (aver (eq (memory-operand-mode memory-operand) :offset))
1178 (aver (and (integerp offset)
1179 (zerop (logand offset 3))))
1180 ;; FIXME: Should support LABEL bases.
1181 (aver (tn-p base))
1182 (emit-fp-ls-instruction segment
1183 (conditional-opcode condition)
1184 #b110
1186 (if (eq direction :up) 1 0)
1187 (low-bit-float-reg float-reg)
1189 ,direction-flag
1190 (tn-offset base)
1191 (high-bits-float-reg float-reg)
1192 #b101
1193 ,precision-flag
1194 (ash offset -2))))))))
1196 (define-load-store-one-fp-instruction fsts :single :store)
1197 (define-load-store-one-fp-instruction flds :single :load)
1198 (define-load-store-one-fp-instruction fstd :double :store)
1199 (define-load-store-one-fp-instruction fldd :double :load)
1202 ;; single register transfer instructions
1204 (define-bitfield-emitter emit-fp-srt-instruction 32
1205 (byte 4 28) ; cond
1206 (byte 4 24) ; #b1110
1207 (byte 3 21) ; opc
1208 (byte 1 20) ; L
1210 (byte 4 16) ; Fn
1211 (byte 4 12) ; Rd
1212 (byte 3 9) ; #b101
1213 (byte 1 8) ; precision
1215 (byte 1 7) ; N
1216 (byte 7 0)) ; #b0010000
1218 (defmacro define-single-reg-transfer-fp-instruction (name precision direction opcode)
1219 (let ((precision-flag (ecase precision
1220 (:single 0)
1221 (:double 1)))
1222 (direction-flag (ecase direction
1223 (:to-arm 1)
1224 (:from-arm 0))))
1225 `(define-instruction ,name (segment &rest args)
1226 (:emitter
1227 (with-condition-defaulted (args (condition ,@(if (eq direction :to-arm)
1228 '(arm-reg float-reg)
1229 '(float-reg arm-reg))))
1230 (emit-fp-srt-instruction segment
1231 (conditional-opcode condition)
1232 #b1110
1233 ,opcode
1234 ,direction-flag
1235 (high-bits-float-reg float-reg)
1236 (tn-offset arm-reg)
1237 #b101
1238 ,precision-flag
1239 (low-bit-float-reg float-reg)
1240 #b0010000))))))
1242 (define-single-reg-transfer-fp-instruction fmsr :single :from-arm #b000)
1243 (define-single-reg-transfer-fp-instruction fmrs :single :to-arm #b000)
1244 (define-single-reg-transfer-fp-instruction fmdlr :double :from-arm #b000)
1245 (define-single-reg-transfer-fp-instruction fmrdl :double :to-arm #b000)
1246 (define-single-reg-transfer-fp-instruction fmdhr :double :from-arm #b001)
1247 (define-single-reg-transfer-fp-instruction fmrdh :double :to-arm #b001)
1248 ;; for special registers fpsid (~s0), fpscr (~s2), fpexc (~s16):
1249 (define-single-reg-transfer-fp-instruction fmxr :single :from-arm #b111)
1250 (define-single-reg-transfer-fp-instruction fmrx :single :to-arm #b111)
1252 (define-bitfield-emitter emit-fp-trt-instruction 32
1253 (byte 4 28) ; cond
1254 (byte 7 21) ; #b1100010
1255 (byte 1 20) ; L
1256 (byte 4 16) ; Rn
1257 (byte 4 12) ; Rd
1258 (byte 3 9) ; #b101
1259 (byte 1 8) ; precision
1260 (byte 2 6) ; #b00
1261 (byte 1 5) ; M
1262 (byte 1 4) ; #b1
1263 (byte 4 0)) ; Fm
1265 (defmacro define-two-reg-transfer-fp-instruction (name precision direction)
1266 (let ((precision-flag (ecase precision
1267 (:single 0)
1268 (:double 1)))
1269 (direction-flag (ecase direction
1270 (:to-arm 1)
1271 (:from-arm 0))))
1272 `(define-instruction ,name (segment &rest args)
1273 (:emitter
1274 (with-condition-defaulted (args (condition float-reg arm-reg-1 arm-reg-2))
1275 (emit-fp-trt-instruction segment
1276 (conditional-opcode condition)
1277 #b1100010
1278 ,direction-flag
1279 (tn-offset arm-reg-2)
1280 (tn-offset arm-reg-1)
1281 #b101
1282 ,precision-flag
1283 #b00
1284 (low-bit-float-reg float-reg)
1286 (high-bits-float-reg float-reg)))))))
1288 (define-two-reg-transfer-fp-instruction fmsrr :single :from-arm)
1289 (define-two-reg-transfer-fp-instruction fmrrs :single :to-arm)
1290 (define-two-reg-transfer-fp-instruction fmdrr :double :from-arm)
1291 (define-two-reg-transfer-fp-instruction fmrrd :double :to-arm)