changelog shortlog graph tags branches changeset files revisions annotate raw help

Mercurial > org > blog / draft/a-bit-of-risc.org

changeset 25: f23bffbe2f4c
parent: 82bb06cbf137
child: db5ece2206cf
author: Richard Westhaver <ellis@rwest.io>
date: Thu, 04 Jul 2024 23:37:37 -0400
permissions: -rw-r--r--
description: updates
1 #+title: A Bit of RISC
2 #+date: [2024-03-11 Mon]
3 #+setupfile: ../../clean.theme
4 I recently picked up [[https://dl.acm.org/doi/10.5555/2462741][Hacker's Delight]] and having a lot of fun with
5 it. It's a collection of bit-manipulation tricks collected by hackers
6 over many years. You can flip open pretty much anywhere in the book
7 and start learn something really cool.
8 
9 There's something about seeing bit strings and assembly code in a book
10 that really catches my attention, this one goes a bit further by even
11 describing a complete RISC (Reduced Instruction Set Computer) we can
12 implement to play around with the various tricks.
13 
14 As an exercise and for fun, I'd like to employ some Lisp-fu here and
15 implement a small VM specifically designed for mangling bits.
16 
17 As a fair warning, I'm not a mathematician and I don't write proofs
18 often. If I get something wrong or there is a better way of doing
19 things, let me know!
20 
21 You can find most of the code from the book [[https://github.com/hcs0/Hackers-Delight][here]].
22 
23 * Design
24 ** Data Representation
25 We'll be sticking with a 32-bit word length as recommended in the
26 Preface. We will also represent registers as integers whenever
27 possible, instead of say a bit-vector. Without going into too much
28 detail, it's much more efficient to do bitwise ops on integers
29 instead of bit-vectors in Lisp.
30 
31 We need a minimum of 16 general purpose registers, typically of word
32 length, with R0 reserved for a constant 0. To address 16 different
33 registers we actually only need 4 bits - 5-bits if we needed 32, 6 for
34 64, etc.
35 
36 Floating-point support and special purpose registers are not required.
37 
38 ** Instructions
39 The Hacker's Delight RISC architecture is described in two tables,
40 denoted =basic RISC= and =full RISC= respectively.
41 
42 Most instructions take two source registers =RA= and =RB= with a
43 destination register =RT=. The actual general-purpose registers are
44 labelled =R0= (containg the constant 0) through =R15=.
45 
46 A 3-Address machine is assumed and some instructions take 16-bit
47 signed or unsigned immediate values - denoted =I= and =Iu=
48 respectively.
49 
50 #+tblname: Basic Instruction Set (basic RISC)
51 | Opcode Mnemonic | Operands | Description |
52 |-----------------------------------------------------------------+-----------+-----------------------------------------------------------------------------------------------------------------------------------------|
53 | add,sub,mul,div,divu,rem,remu | RT,RA,RB | RT <- (op RA RB) |
54 | addi,muli | RT,RA,I | RT <- (op RA I), I is a 16-bit signed immediate-value |
55 | addis | RT,RA,I | RT <- (+ RA (\vert\vert I 0x0000)) |
56 | and,or,xor | RT,RA,RB | RT <- (op RA RB) |
57 | andi,ori,xori | RT,RA,Iu | As above, expect the last operand is a 16-bit unsigned immediate-value |
58 | beq,bne,blt,ble,bgt,bge | RT,target | Branch to target if (op RT) |
59 | bt,bf | RT,target | Branch true/false, same as bne/beq resp |
60 | cmpeq,cmpne,cmplt,cmple,cmpgt,cmpge,cmpltu,cmpleu,cmpgtu,cmpgeu | RT,RA,RB | RT <- (if (op RA RB) 1 0) |
61 | cmpieq,cmpine,cmpilt,cmpile,cmpigt,cmpige | RT,RA,I | Like cmpeq except second comparand is a 16-bit signed immediate-value |
62 | cmpiequ,cmpineu,cmpiltu,cmpileu,cmpigtu,cmpigeu | RT,RA,I | Like cmpltu except second comparand is a 16-bit unsigned immediate-value |
63 | ldbu,ldh,ldhu,ldw | RT,d(RA) | Load an unsigned-byte, signed-halfword, unsigned-halfword, or word into RT from (+ RA d) where d is a 16-bit signed immediate-value |
64 | mulhs,mulhu | RT,RA,RB | RT gets the high-order 32 bits of (* RA RB) |
65 | not | RT,RA | RT <- bitwise one's-complement of RA |
66 | shl,shr,shrs | RT,RA,RB | RT <- RA shifted left or right by rightmost six bits of RB; 0-fill except for shrs, which is sign-fill (shift amount treated modulo 64) |
67 | shli,shri,shrsi | RT,RA,Iu | RT <- RA shifted left or right by 5-bit immediate field |
68 | stb,sth,stw | RS,d(RA) | Store a byte,halfword,word from RS into memory at location (+ RA d) where d is a 16-bit signed immediate-value |
69 
70 
71 #+name: Addition Instructions (full RISC)
72 | Opcode Mnemonic | Operands | Description |
73 |-----------------------------------------------------------------+-----------+--------------------------------------------------------------------------------------------------------|
74 | abs,nabs | RT,RA | RT <- (op RA) |
75 | andc,eqv,nand,nor,orc | RT,RA,RB | RT <- (op RA RB) |
76 | extr | RT,RA,I,L | extract bits I through I+L-1 of RA and place them right-adjusted in RT, with 0-fill |
77 | extrs | RT,RA,I,L | Like extr, but sign-fill |
78 | ins | RT,RA,I,L | Insert bits 0 through L-1 of RA into bits I through I+L-1 of RT |
79 | nlz | RT,RA | RT gets count of leading 0's in RA (0 to 32) |
80 | pop | RT,RA | RT gets the number of 1-bits in RA (0 to 32) |
81 | ldb | RT,d(RA) | Load a signed byte into RT from memory at location (+ RA d) where d is a 16-bit signed immediate value |
82 | moveq,movne,movlt,movle,movgt,movge | RT,RA,RB | RT <- RA rotate-shifted left or right by the rightmost 5-bits of RB |
83 | shlr,shrr | RT,RA,RB | RT <- RA rotate-shifted left or right by the rightmost 5-bits of RB |
84 | shlri,shrri | RT,RA,Iu | RT <- RA rotate-shifted left or right by the 5-bit immediate field |
85 | trpeq,trpne,trplt,trple,trpgt,trpge,trpltu,trpleu,trpgtu,trpgeu | RA,RB | Trap (interrupt) if (op RA RB) |
86 | trpieq,trpine,trpilt,trpile,trpigt,trpige | RA,I | Trap if (op RA I) where I is a 16-bit signed immediate-value |
87 | trpiequ,trpineu,trpiltu,trpileu,trpigtu,trpigeu | RA,Iu | Trap if (op RA Iu) where Iu is a 16-bit unsigned immediate-value |
88 
89 There is also some extensions, which are like macros that usually
90 expand to a single instruction.
91 
92 #+name: Extended Mnemonics
93 | Extended Mnemonic | Expansion | Description |
94 |-------------------+------------------+---------------------------|
95 | b target | beq R0,target | Unconditional branch |
96 | li RT,I | (addi,addis,ori) | Load immediate |
97 | mov RT,RA | ori RT,RA,0 | Move register RA to RT |
98 | neg RT,RA | sub RT,R0,RA | Negate (two's-complement) |
99 | subi RT,RA,I | addi RT,RA,-I | Subtract immediate |
100 
101 All of these instructions are available on x86,arm,riscv and the likes
102 so no real surprises. We will implement the basic set in Lisp, mapping
103 instructions directly to Lisp functions using macros.
104 
105 ** Execution Model
106 We'll build this machine in Lisp and use plenty intrinsics from
107 SBCL. As a starting point I followed Paul Khuong's excellent blog
108 post: [[https://pvk.ca/Blog/2014/03/15/sbcl-the-ultimate-assembly-code-breadboard/][SBCL: The ultimate assembly code breadboard]].
109 
110 Some things to keep in mind for our machine:
111 - every instruction requires at most two register reads and one
112  register write - good for compilers
113 - every instruction counts as a single cycle
114 - we pay no attention to instruction-level parallelism
115 
116 * The HAKMEM VM
117 :properties:
118 :header-args: :session t :results none
119 :end:
120 #+name: defpackage
121 #+begin_src lisp
122  (ql:quickload :prelude)
123  (in-package :std-user)
124  (defpackage :hakmem
125  (:use :cl :std :std-user)
126  (:import-from :sb-assem :inst)
127  (:import-from :sb-vm :immediate-constant :registers :zero :ea))
128  (in-package :hakmem)
129  ;; (in-package :sb-x86-64-asm)
130  ;; (in-readtable :std)
131  (declaim (optimize (speed 3) (safety 1)))
132 
133  (eval-always
134  (defconstant +word-size+ 32 "default word size and register length."))
135 #+end_src
136 
137 #+name: vars
138 #+begin_src lisp :package hakmem
139  (declaim (type (unsigned-byte #.+word-size+) +ro+))
140  (defconstant +r0+ 0 "constant value for register 0")
141  (defvar *stack* (make-array 8 :initial-contents (list sb-vm::r8-tn
142  sb-vm::r9-tn
143  sb-vm::r10-tn
144  sb-vm::r11-tn
145  sb-vm::r12-tn
146  sb-vm::r13-tn
147  sb-vm::r14-tn
148  sb-vm::r15-tn)))
149  (defvar *stack-pointer*)
150 
151  (defvar *rax* sb-vm::rax-tn)
152  (defvar *rbx* sb-vm::rax-tn)
153  (defvar *rcx* sb-vm::rax-tn)
154  (defvar *rdx* sb-vm::rax-tn)
155 
156  ;; (@ 0) returns the (current) register for TOS, (@ 1) returns
157  ;; the one just below, etc.
158  (defun @ (i)
159  (aref *stack* (mod (+ i *stack-pointer*) (length *stack*))))
160 
161  (defvar *code-base* sb-vm::rsi-tn)
162  (defvar *virtual-ip* sb-vm::rdi-tn)
163  (sb-x86-64-asm::get-gpr :qword 4)
164  ;; (sb-vm::immediate-constant-sc 10000)
165  ;; arena vector or list?
166  (defvar *instructions* (make-hash-table :test #'equal))
167 
168  (defvar *primitive-code-offset* (* 64 67))
169 
170  (defstruct code-page
171  (alloc 0) ;; next free byte
172  (code (make-array *primitive-code-offset* :element-type 'octet)))
173 
174  (defun emit-code (pages emitter)
175  ;; there must be as many code pages as there are stack slots
176  (assert (= (length *stack*) (length pages)))
177  ;; find the rightmost starting point, and align to 16 bytes
178  (let* ((alloc (logandc2 (+ 15 (reduce #'max pages :key #'code-page-alloc))
179  15))
180  (bytes (loop for i below (length pages)
181  for page = (elt pages i)
182  collect (let ((segment (sb-assem:make-segment))
183  (*stack-pointer* i))
184  ;; assemble the variant for this value
185  ;; of *stack-pointer* in a fresh code
186  ;; segment
187  (sb-assem:assemble (segment)
188  ;; but first, insert padding
189  (sb-vm::emit-long-nop segment (- alloc (code-page-alloc page)))
190  (funcall emitter))
191  ;; tidy up any backreference
192  (sb-assem:finalize-segment segment)
193  ;; then get the (position-independent) machine
194  ;; code as a vector of bytes
195  (sb-assem:segment-contents-as-vector segment)))))
196  ;; finally, copy each machine code sequence to the right code page
197  (map nil (lambda (page bytes)
198  (let ((alloc (code-page-alloc page)))
199  (replace (code-page-code page) bytes :start1 alloc)
200  (assert (<= (+ alloc (length bytes)) (length (code-page-code page))))
201  (setf (code-page-alloc page) (+ alloc (length bytes)))))
202  pages bytes)
203  ;; and return the offset for that code sequence
204  alloc))
205 
206  (defun emit-all-code (&rest emitters)
207  (let ((pages (loop repeat (length *stack*)
208  for page = (make-code-page)
209  ;; prefill everything with one-byte NOPs
210  do (fill (code-page-code page) #x90)
211  collect page)))
212  (values (mapcar (lambda (emitter)
213  (emit-code pages emitter))
214  emitters)
215  pages)))
216 
217  (defun next (&optional offset)
218  (setf offset (or offset 0)) ; accommodate primops that frob IP
219  (let ((rotation (mod *stack-pointer* (length *stack*))))
220  (inst movzx *rax* (make-ea :dword :base *virtual-ip*
221  :disp offset))
222  (unless (= -4 offset)
223  (inst add *virtual-ip* (+ 4 offset)))
224  (if (zerop rotation)
225  (inst add *rax* *code-base*)
226  (inst lea *rax* (make-ea :qword :base *code-base*
227  :index *rax*
228  :disp (* rotation *primitive-code-offset*))))
229  (inst jmp *rax*)))
230 
231  (defun swap ()
232  (inst xchg (@ 0) (@ 1)) ; exchange top of stack and stack[1]
233  (next))
234 
235 #+end_src
236 
237 #+name: instructions
238 #+begin_src lisp :package hakmem
239  ;; todo
240  (defun %parse-reg3 (rt ra rb))
241  (defun %parse-reg2i (rt ra i))
242  (defun %parse-reg2ui (rt ra ui))
243  (defmacro def-inst (name args &body body)
244  ;; todo: compose a function based on regs+args+body
245  `(let ((sc *scratch*)
246  (r0 +r0+)
247  (ra 0)
248  (rb 0)
249  (rt 0))
250  (declare (ignorable sc r0 ra rb rt))
251  (setf (gethash ',name *instructions*) (lambda ,args (progn ,@body)))))
252 
253  (defmacro def-prim (name op)
254  `(def-inst ,name () (setf rt (,op ra rb))))
255 #+end_src
256 
257 #+name: prims
258 #+begin_src lisp :package hakmem
259  (def-prim add +)
260  (def-prim sub -)
261  (def-prim mul *)
262  (def-prim div /)
263  ;; divu
264  (def-prim rem mod)
265  ;; remu
266  (def-prim cmpeq =)
267  (def-prim cmpne /=)
268  (def-prim cmplt <)
269  (def-prim cmple <=)
270  (def-prim cmpgt >)
271  (def-prim cmpge >=)
272  ;; ltu leu gtu geu
273  (def-inst addi (i)
274  (setf rt (+ ra i)))
275  (def-inst muli (i)
276  (setf rt (* ra i)))
277  (def-prim and logand)
278  (def-prim or logior)
279  (def-prim xor logxor)
280 
281  (defun get-inst (i) (gethash i *instructions*))
282 
283  (defmacro %inst (i &body args)
284  `(funcall (get-inst ',i) ,@args))
285 
286  (defun list-instructions (&optional (tbl *instructions*))
287  (hash-table-alist tbl))
288 
289 #+end_src
290 #+name: instruction-list
291 #+begin_src lisp :results replace :exports both :package hakmem
292  (list-instructions)
293 #+end_src
294 
295 #+RESULTS: instruction-list
296 #+begin_example
297 ((XOR . #<FUNCTION (LAMBDA ()) {101CF0367B}>)
298  (OR . #<FUNCTION (LAMBDA ()) {101CF036AB}>)
299  (AND . #<FUNCTION (LAMBDA ()) {101CF036DB}>)
300  (MULI . #<FUNCTION (LAMBDA (I)) {101CF0370B}>)
301  (ADDI . #<FUNCTION (LAMBDA (I)) {101CF0373B}>)
302  (CMPGE . #<FUNCTION (LAMBDA ()) {101CF0376B}>)
303  (CMPGT . #<FUNCTION (LAMBDA ()) {101CF0379B}>)
304  (CMPLE . #<FUNCTION (LAMBDA ()) {101CF037CB}>)
305  (CMPLT . #<FUNCTION (LAMBDA ()) {101CF037FB}>)
306  (CMPNE . #<FUNCTION (LAMBDA ()) {101CF0382B}>)
307  (CMPEQ . #<FUNCTION (LAMBDA ()) {101CF0385B}>)
308  (REM . #<FUNCTION (LAMBDA ()) {101CF0388B}>)
309  (DIV . #<FUNCTION (LAMBDA ()) {101CF038DB}>)
310  (MUL . #<FUNCTION (LAMBDA ()) {101CF0391B}>)
311  (SUB . #<FUNCTION (LAMBDA ()) {101CF0394B}>)
312  (ADD . #<FUNCTION (LAMBDA ()) {101CF0397B}>))
313 #+end_example