First cut at x86 assembler & simplest program

- add VM tracing
- bootstrap defs from file
- error messages
This commit is contained in:
Jeremy Penner 2019-10-20 01:05:26 -04:00
parent f4e8467898
commit e601535399
10 changed files with 694 additions and 65 deletions

BIN
asm.img Executable file

Binary file not shown.

65
asm.qf Executable file
View file

@ -0,0 +1,65 @@
array ops 2 allot
array optypes 2 allot
var currop
: op1 ops @ ;
: op2 ops 1 + @ ;
0 const OP_NONE
1 const OP_REG8
2 const OP_REG16
3 const OP_SREG
4 const OP_IMM
: op! ( op type ) currop @ >r optypes r@ + ! ops r@ + ! 1 r> + currop ! ;
: assembled 0 currop ! ;
: mkreg makedo , does> @ swap makedo , , does> dup @ swap 1 + @ op! ;
OP_REG8 mkreg reg8
OP_REG16 mkreg reg16
OP_SREG mkreg sreg
0 reg16 ax 0 reg8 al 4 reg8 ah
1 reg16 cx 1 reg8 cl 5 reg8 ch
2 reg16 dx 2 reg8 dl 6 reg8 dh
3 reg16 bx 3 reg8 bl 7 reg8 bh
4 reg16 sp 5 reg16 bp 6 reg16 si 7 reg16 di
0 sreg es 1 sreg cs 2 sreg ss 3 sreg ds
: # OP_IMM op! ;
: read-impl ( p -- next cp optypes )
dup @ swap
dup 1 + @ swap
2 + ;
: match-impl ( optypes opcount -- b )
begin dup > 0 while
1 - 2dup + @ over optypes + @ !=
if drop drop 0 ret then
repeat drop drop 1 ;
: inst ( opcount -- ) makedo , 0 , does>
dup @ currop @ != if 0 message yelp ret then
1 + @ begin dup while
read-impl currop @ match-impl
if execute drop assembled ret else drop then
repeat drop 1 message yelp ;
: do.data ( cp -- data ) 2 + ;
: inst-nextimpl do.data 1 + ;
: inst-opcount do.data @ ;
: impl ( [optype...] cp cpinst -- )
here >r >r ( r: impl inst )
r@ inst-nextimpl @ , ,
r@ inst-opcount begin dup while 1 - swap , repeat drop
r> inst-nextimpl r> swap ! ;
: int &hcd outb! outb! assembled ;
2 inst mov
2 inst movb
: outw! dup &hff and outb! 256 / outb! ;
OP_IMM OP_REG16 :noname &hb8 op1 + outb! op2 outw! ; ' mov impl
OP_IMM OP_REG8 :noname &hb0 op1 + outb! op2 outb! ; ' movb impl

BIN
boot.img Executable file

Binary file not shown.

66
boot.qf Executable file
View file

@ -0,0 +1,66 @@
: debug word@ yelp ;
: here 0 @ ;
: here! 0 ! ;
: != not = ;
: if ' jz_ , here 0 , ; immediate
: then here over - swap ! ; immediate
: else ' jmp_ , here >r 0 , [ ' then , ] r> ; immediate
: begin here ; immediate
: while [ ' if , ] ; immediate
: repeat ' jmp_ , swap here - , [ ' then , ] ; immediate
: again ' jmp_ , here - , ; immediate
: until ' jz_ , here - , ; immediate
: ( begin in@ [ in@ ) lit ] = until ; immediate
: \ begin in@ 0 < until ; immediate
: const word@ create ' $const , , ;
: array word@ create ' $var , ;
: var, array , ;
: var 0 var, ;
: allot here + here! ;
: nip swap drop ;
: negate 0 swap - ;
: abs dup 0 < if negate then ;
: :noname here ] ;
: :| here 4 + lit ' jmp_ , here 0 , ; immediate
: |; ' ret , [ ' then , ] ; immediate
: $do r> dup 1 + swap @ >r ;
var does.patch
: makedo word@ create ' $do , here does.patch ! -1 , ;
: does> here 3 + lit :| does.patch @ ! rdrop |; , ; immediate
: $defer r> @ >r ;
: defer word@ create ' $defer , :| |; , ;
: redef 1 + ! ;
: +towards ( from to -- from+-1 )
over > if 1 + else 1 - then ;
: for ( from to -- )
' >r , [ ' begin , ] ( from r: to )
' dup , ' r@ , ' != , [ ' while , ]
' >r , ; immediate ( r: to from )
: i ' r@ , ; immediate
: next
' r> , ' r@ , ' +towards , ( from+1 r: to )
[ ' repeat , ] ' drop , ' rdrop , ; immediate
: yield rswap ;
: done rdrop 0 >r rswap ;
: ;done ' done , [ ' [ , ] ; immediate
: each [ ' begin , ] ' r@ , [ ' while , ] ; immediate
: more ' yield , [ ' repeat , ] ' rdrop , ; immediate
: break rswap rdrop :| yield done |; execute rswap ;
: links begin yield @ dup not until drop ;done
: min ( x y -- x|y ) 2dup > if swap then drop ;
: max ( x y -- x|y ) 2dup < if swap then drop ;

2
build.bat Executable file
View file

@ -0,0 +1,2 @@
qbasic /run qf.bas

6
in.asm Executable file
View file

@ -0,0 +1,6 @@
\ The simplest possible COM file: just return 1
\ 1 trace
\ mov \ should fail and yelp
ax &h4c01 # mov
&h21 int

3
messages.txt Executable file
View file

@ -0,0 +1,3 @@
Operand count doesn't match
No matching instruction

1
out.com Executable file
View file

@ -0,0 +1 @@
<EFBFBD>L<>!

270
qf.bas
View file

@ -1,3 +1,9 @@
DECLARE FUNCTION lookupop$ (op%)
DECLARE FUNCTION guessdef$ (ptr%)
DECLARE FUNCTION loadimg! (filename$)
DECLARE SUB bootstrap ()
DECLARE SUB saveimg (filename$)
DECLARE SUB loadfile (filename$)
DECLARE SUB vm () DECLARE SUB vm ()
DECLARE SUB interpret (st$) DECLARE SUB interpret (st$)
DECLARE SUB execute (op%) DECLARE SUB execute (op%)
@ -17,18 +23,29 @@ TYPE word
df AS INTEGER df AS INTEGER
i AS INTEGER i AS INTEGER
END TYPE END TYPE
DIM SHARED words(256) AS word CONST WORDCOUNT = 256
CONST memcount = 10000
DIM SHARED words(WORDCOUNT) AS word
DIM SHARED strings$(32) DIM SHARED strings$(32)
DIM SHARED mem(10000) AS INTEGER DIM SHARED messages$(32)
DIM SHARED mem(memcount) AS INTEGER
DIM SHARED stack(64) AS INTEGER DIM SHARED stack(64) AS INTEGER
DIM SHARED rstack(64) AS INTEGER DIM SHARED rstack(64) AS INTEGER
COMMON SHARED sp AS INTEGER, rsp AS INTEGER, w AS INTEGER, ip AS INTEGER COMMON SHARED sp AS INTEGER, rsp AS INTEGER, w AS INTEGER, ip AS INTEGER
COMMON SHARED in$ COMMON SHARED tracevm
COMMON SHARED in$, inline%
COMMON SHARED interpretcp AS INTEGER COMMON SHARED interpretcp AS INTEGER
COMMON SHARED trace% COMMON SHARED trace%
inline% = -1
interpretcp = -1 interpretcp = -1
trace% = 0 trace% = 10 ' 10
OPEN "messages.txt" FOR INPUT AS #1
FOR i = 0 TO 31
IF EOF(1) = 0 THEN LINE INPUT #1, messages$(i)
NEXT
CLOSE #1
OPEN "out.com" FOR OUTPUT AS #1 OPEN "out.com" FOR OUTPUT AS #1
CLOSE #1 CLOSE #1
@ -66,65 +83,29 @@ CONST O.EQ = -25
CONST O.JMP = -26 CONST O.JMP = -26
CONST O.YELP = -27 CONST O.YELP = -27
CONST O.IMMEDIATE = -28 CONST O.IMMEDIATE = -28
CONST O.RDROP = -29
CONST O.RTOP = -30
CONST O.RSWAP = -31
CONST O.BITAND = -32
CONST O.BITOR = -33
CONST O.MESSAGE = -34
CONST O.TRACE = -35
CONST P.HERE = 0 CONST P.HERE = 0
CONST P.LATEST = 1 CONST P.LATEST = 1
CONST P.NEXTSTR = 2 CONST P.NEXTSTR = 2
mem(P.LATEST) = -1
mem(P.HERE) = 3
CALL opcode("ret", O.RET) IF loadimg("asm.img") = 0 THEN
CALL opcode("dup", O.DUP) IF loadimg("boot.img") = 0 THEN
CALL opcode("swap", O.SWAP) PRINT "Bootstrapping"
CALL opcode(">rot", O.ROT) CALL bootstrap
CALL opcode("@", O.GET) CALL saveimg("boot.img")
CALL opcode("!", O.SET) END IF
CALL opcode("create", O.CREATE) CALL loadfile("asm.qf")
CALL opcode("in@", O.IN) CALL saveimg("asm.img")
CALL opcode("out!", O.OUT) END IF
CALL opcode("immediate", O.IMMEDIATE)
CALL opcode("drop", O.DROP)
CALL opcode("execute", O.EXEC)
CALL opcode("lookup", O.LOOKUP)
CALL opcode("word@", O.WORD)
CALL opcode("number", O.NUMBER)
CALL opcode("lit_", O.LIT)
CALL opcode("+", O.ADD)
CALL opcode("-", O.SUB)
CALL opcode("*", O.MUL)
CALL opcode("/", O.DIV)
CALL opcode("<", O.LT)
CALL opcode("=", O.EQ)
CALL opcode("jz_", O.JZ)
CALL opcode("jmp_", O.JMP)
CALL opcode(">r", O.RPUSH)
CALL opcode("r>", O.RPOP)
CALL opcode(",", O.COMMA)
CALL opcode("yelp", O.YELP)
CALL assemble("<rot", ">rot >rot ret") CALL loadfile("in.asm")
CALL assemble("over", "swap dup >rot ret")
CALL assemble("2dup", "over over ret")
CALL assemble("$var", "r> ret")
CALL assemble("$const", "r> @ ret")
CALL assemble("not", "jz_ 3 lit_ 0 ret lit_ 1 ret")
CALL assemble("and", "jz_ 4 jz_ 3 jmp_ 4 drop lit_ 0 ret lit_ 1 ret")
CALL assemble("or", "not swap not and not ret")
CALL assemble(">=", "< not ret")
CALL assemble("<=", "2dup < >rot = or ret")
CALL assemble(">", "<= not ret")
CALL assemble("state", "$var 0")
CALL assemble("doword", "state @ not or jz_ 2 execute ret , ret")
CALL assemble("donum", "state @ jz_ 4 lit_ lit_ , , ret")
CALL assemble("donext", "lookup jz_ 2 doword ret number jz_ 2 donum ret yelp ret")
CALL assemble("interpret", "word@ dup lit_ 0 >= jz_ 3 donext jmp_ -10 drop ret")
CALL assemble("[", "lit_ 0 state ! ret"): CALL execute(O.IMMEDIATE)
CALL assemble("]", "lit_ 1 state ! ret")
CALL assemble(":", "word@ create ] ret")
CALL assemble(";", "lit_ ret , [ ret"): CALL execute(O.IMMEDIATE)
CALL interpret("65 out! 66 out! 0 out! 67 out! 7 out! 254 out! 10 out! 13 out!")
SUB assemble (name$, asm$) SUB assemble (name$, asm$)
in$ = asm$ in$ = asm$
@ -159,11 +140,75 @@ SUB assemble (name$, asm$)
WEND WEND
END SUB END SUB
SUB bootstrap
mem(P.LATEST) = -1
mem(P.HERE) = 3
CALL opcode("ret", O.RET)
CALL opcode("dup", O.DUP)
CALL opcode("swap", O.SWAP)
CALL opcode(">rot", O.ROT)
CALL opcode("@", O.GET)
CALL opcode("!", O.SET)
CALL opcode("create", O.CREATE)
CALL opcode("in@", O.IN)
CALL opcode("outb!", O.OUT)
CALL opcode("immediate", O.IMMEDIATE)
CALL opcode("drop", O.DROP)
CALL opcode("execute", O.EXEC)
CALL opcode("lookup", O.LOOKUP)
CALL opcode("word@", O.WORD)
CALL opcode("number", O.NUMBER)
CALL opcode("lit_", O.LIT)
CALL opcode("+", O.ADD)
CALL opcode("-", O.SUB)
CALL opcode("*", O.MUL)
CALL opcode("/", O.DIV)
CALL opcode("<", O.LT)
CALL opcode("=", O.EQ)
CALL opcode("jz_", O.JZ)
CALL opcode("jmp_", O.JMP)
CALL opcode(">r", O.RPUSH)
CALL opcode("r>", O.RPOP)
CALL opcode("r@", O.RTOP)
CALL opcode("rdrop", O.RDROP)
CALL opcode("rswap", O.RSWAP)
CALL opcode(",", O.COMMA)
CALL opcode("message", O.MESSAGE)
CALL opcode("yelp", O.YELP)
CALL opcode("trace", O.TRACE)
CALL assemble("<rot", ">rot >rot ret")
CALL assemble("over", "swap dup >rot ret")
CALL assemble("2dup", "over over ret")
CALL assemble("$var", "r> ret")
CALL assemble("$const", "r> @ ret")
CALL assemble("not", "jz_ 4 lit_ 0 ret lit_ 1 ret")
CALL assemble("and", "jz_ 5 jz_ 4 jmp_ 5 drop lit_ 0 ret lit_ 1 ret")
CALL assemble("or", "not swap not and not ret")
CALL assemble(">=", "< not ret")
CALL assemble("<=", "2dup < >rot = or ret")
CALL assemble(">", "<= not ret")
CALL assemble("state", "$var 0")
CALL assemble("doword", "state @ not or jz_ 3 execute ret , ret")
CALL assemble("donum", "state @ jz_ 5 lit_ lit_ , , ret")
CALL assemble("donext", "lookup jz_ 3 doword ret number jz_ 3 donum ret yelp ret")
CALL assemble("interpret", "word@ dup lit_ 0 >= jz_ 4 donext jmp_ -9 drop ret")
CALL assemble("[", "lit_ 0 state ! ret"): CALL execute(O.IMMEDIATE)
CALL assemble("]", "lit_ 1 state ! ret")
CALL assemble(":", "word@ create ] ret")
CALL assemble(";", "lit_ ret , [ ret"): CALL execute(O.IMMEDIATE)
CALL assemble("lit", "lit_ lit_ , , ret")
CALL assemble("'", "word@ lookup drop drop state @ jz_ 2 lit ret"): CALL execute(O.IMMEDIATE)
CALL loadfile("boot.qf")
END SUB
SUB execute (op%) SUB execute (op%)
IF trace% > 0 THEN IF trace% > 0 AND tracevm THEN
tp$ = "NA" tp$ = "N/A"
IF sp > 0 THEN tp$ = STR$(top) IF sp > 0 THEN tp$ = STR$(top)
PRINT #trace%, "ip:"; ip; " op:"; op%; " sp:"; sp; " tp:"; tp$; " rsp:"; rsp PRINT #trace%, "ip:"; ip; " sp:"; sp; " rp:"; rsp; " tp:"; tp$; " fn:"; guessdef$(ip); " op:"; lookupop$(op%);
END IF END IF
SELECT CASE op% SELECT CASE op%
CASE IS >= 0 CASE IS >= 0
@ -226,6 +271,9 @@ SUB execute (op%)
CASE O.WORD CASE O.WORD
word$ = nextword$ word$ = nextword$
IF word$ <> "" THEN IF word$ <> "" THEN
IF trace% > 0 THEN
PRINT #trace%, "read: "; word$
END IF
CALL push(mkstr(word$)) CALL push(mkstr(word$))
ELSE ELSE
CALL push(-1) CALL push(-1)
@ -267,6 +315,15 @@ SUB execute (op%)
l = pop l = pop
CALL push(l / r) CALL push(l / r)
CASE O.BITAND
r = pop
l = pop
CALL push(l AND r)
CASE O.BITOR
r = pop
l = pop
CALL push(l OR r)
CASE O.LT CASE O.LT
r = pop r = pop
l = pop l = pop
@ -281,29 +338,57 @@ SUB execute (op%)
END IF END IF
CASE O.JZ CASE O.JZ
IF pop = 0 THEN IF pop = 0 THEN
ip = ip + mem(ip) + 1 ip = ip + mem(ip)
ELSE ELSE
ip = ip + 1 ip = ip + 1
END IF END IF
CASE O.JMP CASE O.JMP
ip = ip + mem(ip) + 1 ip = ip + mem(ip)
CASE O.RPUSH CASE O.RPUSH
CALL rpush(pop) CALL rpush(pop)
CASE O.RPOP CASE O.RPOP
CALL push(rpop) CALL push(rpop)
CASE O.RDROP
z = rpop
CASE O.RSWAP
x% = rpop
y% = rpop
CALL rpush(x%)
CALL rpush(y%)
CASE O.RTOP
CALL push(rpeek)
CASE O.COMMA CASE O.COMMA
here = mem(P.HERE) here = mem(P.HERE)
mem(here) = pop mem(here) = pop
mem(P.HERE) = here + 1 mem(P.HERE) = here + 1
CASE O.YELP CASE O.YELP
PRINT strings$(pop); "?" PRINT strings$(pop); "? line "; inline%
CASE O.TRACE
tracevm = pop
CASE O.MESSAGE
CALL push(mkstr(messages$(pop)))
CASE ELSE CASE ELSE
PRINT "Unknown op "; op% PRINT "Unknown op "; op%
ip = -1 ip = -1
END SELECT END SELECT
END SUB END SUB
FUNCTION guessdef$ (ptr%)
guessdef$ = "???"
IF ptr% < 0 THEN
guessdef$ = "**INJECTED**"
ELSE
FOR i = mem(P.LATEST) - 1 TO 0 STEP -1
IF words(i).df < ptr% THEN
guessdef$ = RTRIM$(words(i).nm)
GOTO doneguessdef
END IF
NEXT
END IF
doneguessdef:
END FUNCTION
SUB interpret (st$) SUB interpret (st$)
IF interpretcp < 0 THEN IF interpretcp < 0 THEN
CALL push(mkstr("interpret")) CALL push(mkstr("interpret"))
@ -318,6 +403,35 @@ SUB interpret (st$)
CALL vm CALL vm
END SUB END SUB
SUB loadfile (filename$)
inline% = 0
OPEN filename$ FOR INPUT AS #2
WHILE EOF(2) = 0
LINE INPUT #2, line$
inline% = inline% + 1
CALL interpret(line$)
WEND
CLOSE #2
inline% = -1
END SUB
FUNCTION loadimg (filename$)
OPEN filename$ FOR BINARY AS #3
IF LOF(3) > 0 THEN
FOR i = 0 TO WORDCOUNT - 1
GET #3, , words(i)
NEXT
filememsize = LOF(3) - SEEK(3)
FOR i = 0 TO filememsize / 2
GET #3, , mem(i)
NEXT
loadimg = 1
ELSE
loadimg = 0
END IF
CLOSE #3
END FUNCTION
FUNCTION lookup (w$) FUNCTION lookup (w$)
lookup = -1 lookup = -1
FOR i = 0 TO mem(P.LATEST) FOR i = 0 TO mem(P.LATEST)
@ -329,6 +443,21 @@ FUNCTION lookup (w$)
found: found:
END FUNCTION END FUNCTION
FUNCTION lookupop$ (op%)
lookupop$ = STR$(op%)
FOR i = 0 TO mem(P.LATEST)
IF words(i).df = op% THEN
lookupop$ = RTRIM$(words(i).nm)
GOTO lookupopdone
ELSEIF op% < 0 AND words(i).df > 0 THEN
GOTO lookupopdone
ELSEIF op% > 0 AND words(i).df > op% THEN
GOTO lookupopdone
END IF
NEXT
lookupopdone:
END FUNCTION
FUNCTION mkstr% (st$) FUNCTION mkstr% (st$)
istr = mem(P.NEXTSTR) istr = mem(P.NEXTSTR)
mem(P.NEXTSTR) = (istr + 1) MOD 32 mem(P.NEXTSTR) = (istr + 1) MOD 32
@ -355,7 +484,7 @@ FUNCTION nextword$
foundword: foundword:
IF wordstart <> 0 THEN IF wordstart <> 0 THEN
nextword$ = MID$(in$, wordstart, length) nextword$ = MID$(in$, wordstart, length)
in$ = MID$(in$, wordstart + length) in$ = MID$(in$, wordstart + length + 1) ' consume the space
END IF END IF
END FUNCTION END FUNCTION
@ -390,6 +519,17 @@ SUB rpush (v%)
rsp = rsp + 1 rsp = rsp + 1
END SUB END SUB
SUB saveimg (filename$)
OPEN filename$ FOR BINARY AS #3
FOR i = 0 TO WORDCOUNT - 1
PUT #3, , words(i)
NEXT
FOR i = 0 TO mem(P.HERE)
PUT #3, , mem(i)
NEXT
CLOSE #3
END SUB
FUNCTION top FUNCTION top
top = stack(sp - 1) top = stack(sp - 1)
END FUNCTION END FUNCTION

346
trace.txt Executable file
View file

@ -0,0 +1,346 @@
read: array
read: ops
read: 2
read: allot
read: array
read: optypes
read: 2
read: allot
read: var
read: currop
read: :
read: op1
read: ops
read: @
read: ;
read: :
read: op2
read: ops
read: 1
read: +
read: @
read: ;
read: 0
read: const
read: OP_NONE
read: 1
read: const
read: OP_REG8
read: 2
read: const
read: OP_REG16
read: 3
read: const
read: OP_SREG
read: 4
read: const
read: OP_IMM
read: :
read: op!
read: (
read: currop
read: @
read: >r
read: optypes
read: r@
read: +
read: !
read: ops
read: r@
read: +
read: !
read: 1
read: r>
read: +
read: currop
read: !
read: ;
read: :
read: assembled
read: 0
read: currop
read: !
read: ;
read: :
read: mkreg
read: makedo
read: ,
read: does>
read: @
read: swap
read: makedo
read: ,
read: ,
read: does>
read: dup
read: @
read: swap
read: 1
read: +
read: @
read: op!
read: ;
read: OP_REG8
read: mkreg
read: reg8
read: OP_REG16
read: mkreg
read: reg16
read: OP_SREG
read: mkreg
read: sreg
read: 0
read: reg16
read: ax
read: 0
read: reg8
read: al
read: 4
read: reg8
read: ah
read: 1
read: reg16
read: cx
read: 1
read: reg8
read: cl
read: 5
read: reg8
read: ch
read: 2
read: reg16
read: dx
read: 2
read: reg8
read: dl
read: 6
read: reg8
read: dh
read: 3
read: reg16
read: bx
read: 3
read: reg8
read: bl
read: 7
read: reg8
read: bh
read: 4
read: reg16
read: sp
read: 5
read: reg16
read: bp
read: 6
read: reg16
read: si
read: 7
read: reg16
read: di
read: 0
read: sreg
read: es
read: 1
read: sreg
read: cs
read: 2
read: sreg
read: ss
read: 3
read: sreg
read: ds
read: :
read: #
read: OP_IMM
read: op!
read: ;
read: :
read: read-impl
read: (
read: dup
read: @
read: swap
read: dup
read: 1
read: +
read: @
read: swap
read: 2
read: +
read: ;
read: :
read: match-impl
read: (
read: begin
read: dup
read: >
read: 0
read: while
read: 1
read: -
read: 2dup
read: +
read: @
read: over
read: optypes
read: +
read: @
read: !=
read: if
read: drop
read: drop
read: 0
read: ret
read: then
read: repeat
read: drop
read: drop
read: 1
read: ;
read: :
read: inst
read: (
read: makedo
read: ,
read: 0
read: ,
read: does>
read: dup
read: @
read: currop
read: @
read: !=
read: if
read: 0
read: message
read: yelp
read: ret
read: then
read: 1
read: +
read: @
read: begin
read: dup
read: while
read: read-impl
read: currop
read: @
read: match-impl
read: if
read: execute
read: drop
read: assembled
read: ret
read: else
read: drop
read: then
read: repeat
read: drop
read: 1
read: message
read: yelp
read: ;
read: :
read: do.data
read: (
read: 2
read: +
read: ;
read: :
read: inst-nextimpl
read: do.data
read: 1
read: +
read: ;
read: :
read: inst-opcount
read: do.data
read: @
read: ;
read: :
read: impl
read: (
read: here
read: >r
read: >r
read: (
read: r@
read: inst-nextimpl
read: @
read: ,
read: ,
read: r@
read: inst-opcount
read: begin
read: dup
read: while
read: 1
read: -
read: swap
read: ,
read: repeat
read: drop
read: r>
read: inst-nextimpl
read: r>
read: swap
read: !
read: ;
read: :
read: int
read: &hcd
read: outb!
read: outb!
read: assembled
read: ;
read: 2
read: inst
read: mov
read: 2
read: inst
read: movb
read: :
read: outw!
read: dup
read: &hff
read: and
read: outb!
read: 256
read: /
read: outb!
read: ;
read: OP_IMM
read: OP_REG16
read: :noname
read: &hb8
read: op1
read: +
read: outb!
read: op2
read: outw!
read: ;
read: '
read: mov
read: impl
read: OP_IMM
read: OP_REG8
read: :noname
read: &hb0
read: op1
read: +
read: outb!
read: op2
read: outb!
read: ;
read: '
read: movb
read: impl
read: \
read: \
read: \
read: ax
read: &h4c01
read: #
read: mov
read: &h21
read: int