Compare commits

...

7 Commits

Author SHA1 Message Date
Virgil Dupras aca9bc9058 z80: small optimization in cell execution 2020-06-18 08:02:45 -04:00
Virgil Dupras 035532acf7 z80: remove remaining indirections in execute calls
We now have a stable ABI that is pretty cleared up...
2020-06-18 07:50:20 -04:00
Virgil Dupras 42818d25be z80: remove layers of indirection of find calls 2020-06-18 07:40:20 -04:00
Virgil Dupras 76e698157c z80: remove layer of indirection in most "next" calls
The only calls still using the stable ABI indirection are those
made before the next routine is created.
2020-06-18 07:24:47 -04:00
Virgil Dupras eba83fa9a9 z80: use named labels for boot routines
The usage of numerotated labels for this was becoming severly
confusing.
2020-06-18 07:16:40 -04:00
Virgil Dupras eed817b517 pcat: adapt to word type change 2020-06-18 06:50:32 -04:00
Virgil Dupras 3d2dc041fb Make word routines into word types
Instead of having wordref point to core word routines, I made them
into word 4 word types. It liberates space into the stable ABI and
should make porting to other arches easier.

I'm also thinking of combining word type with the namelen field
for precious bytes saving, but not now...
2020-06-17 21:41:01 -04:00
34 changed files with 102 additions and 134 deletions

View File

@ -2,7 +2,7 @@ Implementation notes
71 Execution model 73 Executing a word 71 Execution model 73 Executing a word
75 Stack management 77 Dictionary 75 Stack management 77 Dictionary
80 System variables 85 Word routines 80 System variables 85 Word types
89 Initialization sequence 89 Initialization sequence

21
blk/085
View File

@ -1,16 +1,15 @@
Word routines Word types
This is the description of all word routine you can encounter There are 4 word types in Collapse OS. Whenever you have a
in this Forth implementation. That is, a wordref will always wordref, it's pointing to a byte with numbers 0 to 3. This
point to a memory offset containing one of these numbers. number is the word type and the word's behavior depends on it.
0x17: nativeWord. This words PFA contains native binary code 0: native. This words PFA contains native binary code and is
and is jumped to directly. jumped to directly.
0x0e: compiledWord. This word's PFA contains an atom list and 1: compiled. This word's PFA contains an atom list and its
its execution is described in "EXECUTION MODEL" above. execution is described in "EXECUTION MODEL" above.
0x0b: cellWord. This word is usually followed by a 2-byte value 2: cell. This word is usually followed by a 2-byte value in its
in its PFA. Upon execution, the *address* of the PFA is pushed PFA. Upon execution, the address of the PFA is pushed to PS.
to PS.
(cont.) (cont.)

14
blk/086
View File

@ -1,13 +1,13 @@
0x2b: doesWord. This word is created by "DOES>" and is followed 3: DOES>. This word is created by "DOES>" and is followed
by a 2-byte value as well as the address where "DOES>" was by a 2-byte value as well as the address where "DOES>" was
compiled. At that address is an atom list exactly like in a compiled. At that address is an atom list exactly like in a
compiled word. Upon execution, after having pushed its cell compiled word. Upon execution, after having pushed its cell
addr to PSP, it execute its reference exactly like a addr to PSP, it executes its reference exactly like a
compiledWord. compiled word.
Also note that word routines references in wordrefs are 1b.
This means that all word routine reference must live below
0x100 in boot binary.

12
blk/243
View File

@ -3,14 +3,12 @@
: BJP, BIN( @ + JPnn, ; : BJP, BIN( @ + JPnn, ;
: BJPcc, BIN( @ + JPccnn, ; : BJPcc, BIN( @ + JPccnn, ;
: JPNEXT, 26 BJP, ; ( 26 == next ) VARIABLE lblchkPS
: chkPS, lblchkPS @ CALLnn, ; ( chkPS, B305 )
: chkPS, L4 @ CALLnn, ; ( chkPS, B305 ) CREATE lblnext 0x1a , ( stable ABI until set in B300 )
: JPNEXT, lblnext @ JPnn, ;
: CODE ( same as CREATE, but with native word ) : CODE ( same as CREATE, but with native word )
(entry) (entry) 0 C, ( 0 == native ) ;
23 C, ( 23 == nativeWord )
;
: ;CODE JPNEXT, ; : ;CODE JPNEXT, ;

View File

@ -2,7 +2,7 @@ VARIABLE XCURRENT
: XCON XCURRENT CURRENT* ! ; : XCON XCURRENT CURRENT* ! ;
: XCOFF 0x02 RAM+ CURRENT* ! ; : XCOFF 0x02 RAM+ CURRENT* ! ;
: (xentry) XCON (entry) XCOFF ; : (xentry) XCON (entry) XCOFF ;
: XCREATE (xentry) 11 C, ; : XCREATE (xentry) 2 C, ;
: XCODE XCON CODE XCOFF ; : XCODE XCON CODE XCOFF ;
: XIMM XCON IMMEDIATE XCOFF ; : XIMM XCON IMMEDIATE XCOFF ;
: _xapply ( a -- a-off ) : _xapply ( a -- a-off )

View File

@ -1,5 +1,5 @@
: X: : X:
(xentry) [ 0x0e LITN ] C, (xentry) 1 ( compiled ) C,
BEGIN WORD BEGIN WORD
XCURRENT @ SWAP ( xcur w ) _find ( a f ) XCURRENT @ SWAP ( xcur w ) _find ( a f )
IF ( a ) IF ( a )

View File

@ -1,3 +1,5 @@
VARIABLE lblofl VARIABLE lblpushRS VARIABLE lblexec
VARIABLE lblfind
1 53 LOADR+ 1 53 LOADR+
@ -9,8 +11,3 @@

28
blk/283
View File

@ -1,16 +1,14 @@
H@ ORG ! H@ ORG !
0 JPnn, ( 00, main ) 0 JPnn, ( 03, find ) 0 JPnn, ( 00, main ) NOP, NOP, NOP, ( unused )
NOP, NOP, ( 06, unused ) NOP, NOP, ( 08, LATEST ) NOP, NOP, ( unused ) NOP, NOP, ( 08, LATEST )
NOP, ( 0a, unused ) NOP, NOP, NOP, NOP, NOP, NOP, NOP, ( 0a, unused )
( 0b cellWord, push PFA ) DE PUSHqq, JR, 0x0c A, ( next ) 0 JPnn, ( 11, pushRS ) 0 JPnn, ( 14, popRS )
0 JPnn, ( 0e, compiledWord ) 0 JPnn, ( 11, pushRS ) NOP, NOP, NOP, ( unused )
0 JPnn, ( 14, popRS ) 0 JPnn, ( 1a, next ) NOP, NOP, NOP, ( unused )
EXDEHL, JP(HL), NOP, ( 17, nativeWord ) NOP, NOP, NOP, NOP, ( unused )
0 JPnn, ( 1a, next ) 0 JPnn, ( unused ) NOP, NOP, NOP, NOP, ( unused )
NOP, NOP, NOP, NOP, ( 20, unused ) 0 JPnn, ( RST 28 )
NOP, NOP, NOP, NOP, ( 24, unused ) NOP, NOP, NOP, NOP, NOP, ( unused )
0 JPnn, ( RST 28 ) 0 JPnn, ( RST 30 )
0 JPnn, ( 2b, doesWord ) NOP, NOP, ( 2e, unused ) NOP, NOP, NOP, NOP, NOP, ( unused )
0 JPnn, ( RST 30 ) 0 JPnn, ( RST 38 )
0 JPnn, ( 33, execute ) NOP, NOP, ( unused )
0 JPnn, ( RST 38 )

View File

@ -5,7 +5,7 @@
0 A,, ( prev ) 0 A,, ( prev )
4 A, 4 A,
H@ XCURRENT ! ( set current tip of dict, 0x42 ) H@ XCURRENT ! ( set current tip of dict, 0x42 )
0x17 A, ( nativeWord ) 0 A, ( native )
0x14 BCALL, ( popRS ) 0x14 BCALL, ( popRS )
HL PUSHqq, IY POPqq, ( --> IP ) HL PUSHqq, IY POPqq, ( --> IP )
JPNEXT, JPNEXT,

View File

@ -6,7 +6,7 @@ CODE (?br) ( 0x67 )
( True, skip next 2 bytes and don't branch ) ( True, skip next 2 bytes and don't branch )
IY INCss, IY INCss, IY INCss, IY INCss,
JPNEXT, NOP, NOP, NOP, JPNEXT, NOP, NOP, NOP,
CODE (loop) ( 0x77 ) CODE (loop) ( 0x80 )
0 IX+ INC(IXY+), IFZ, 1 IX+ INC(IXY+), THEN, ( I++ ) 0 IX+ INC(IXY+), IFZ, 1 IX+ INC(IXY+), THEN, ( I++ )
( Jump if I <> I' ) ( Jump if I <> I' )
A 0 IX+ LDrIXY, 2 IX- CP(IXY+), JRNZ, L2 BWR ( branch ) A 0 IX+ LDrIXY, 2 IX- CP(IXY+), JRNZ, L2 BWR ( branch )

16
blk/289
View File

@ -1,16 +0,0 @@
( Name of BOOT word )
L1 BSET 4 A, 'B' A, 'O' A, 'O' A, 'T' A,
PC ORG @ 1 + ! ( main )
( STACK OVERFLOW PROTECTION: See B76 )
SP PS_ADDR LDddnn,
IX RS_ADDR LDddnn,
( HERE begins at RAMEND )
HL RAMSTART 0x80 + LDddnn,
RAMSTART 0x04 + LD(nn)HL, ( RAM+04 == HERE )
( LATEST is a label to the latest entry of the dict. It is
written at offset 0x08 by the process or person building
Forth. )
BIN( @ 0x08 + LDHL(nn),
RAMSTART 0x02 + LD(nn)HL, ( RAM+02 == CURRENT cont. )

16
blk/290
View File

@ -1,16 +0,0 @@
EXDEHL,
HL L1 @ LDddnn,
0x03 BCALL, ( 03 == find )
0x33 BJP, ( 33 == execute )

View File

@ -1,4 +1,4 @@
PC ORG @ 4 + ! ( find ) lblfind BSET
( Find the entry corresponding to word name where (HL) points ( Find the entry corresponding to word name where (HL) points
to in dictionary having its tip at DE and sets DE to point to in dictionary having its tip at DE and sets DE to point
to that entry. Z if found, NZ if not. ) to that entry. Z if found, NZ if not. )

View File

@ -1,4 +1,4 @@
L4 BSET PC ORG @ 0x12 + ! ( pushRS ) lblpushRS BSET PC ORG @ 0x12 + ! ( pushRS )
IX INCss, IX INCss,
IX INCss, IX INCss,
0 IX+ L LDIXYr, 0 IX+ L LDIXYr,

View File

@ -1,9 +1,9 @@
6 A, '(' A, 'u' A, 'f' A, 'l' A, 'w' A, ')' A, 6 A, '(' A, 'u' A, 'f' A, 'l' A, 'w' A, ')' A,
L2 BSET ( abortUnderflow ) lblofl BSET ( abortUnderflow )
HL PC 7 - LDddnn, HL PC 7 - LDddnn,
DE RAMSTART 0x02 + LDdd(nn), ( RAM+02 == CURRENT ) DE RAMSTART 0x02 + LDdd(nn), ( RAM+02 == CURRENT )
0x03 BCALL, ( find ) lblfind @ CALLnn,
0x33 BJP, ( 33 == execute ) JR, L2 FWR ( execute, B301 )

16
blk/299
View File

@ -0,0 +1,16 @@
L1 BSET 4 A, 'B' A, 'O' A, 'O' A, 'T' A,
PC ORG @ 1 + ! ( main )
( STACK OVERFLOW PROTECTION: See B76 )
SP PS_ADDR LDddnn, IX RS_ADDR LDddnn,
( HERE begins at RAMEND )
HL RAMSTART 0x80 + LDddnn,
RAMSTART 0x04 + LD(nn)HL, ( RAM+04 == HERE )
( LATEST is a label to the latest entry of the dict. It is
written at offset 0x08 by the process or person building
Forth. )
BIN( @ 0x08 + LDHL(nn),
RAMSTART 0x02 ( CURRENT ) + LD(nn)HL,
EXDEHL,
HL L1 @ LDddnn,
lblfind @ CALLnn,
JR, L1 FWR ( execute, B301 )

View File

@ -1,15 +1,15 @@
PC ORG @ 0x1b + ! ( next ) lblnext BSET PC ORG @ 0x1b + ! ( next )
( This routine is jumped to at the end of every word. In it, ( This routine is jumped to at the end of every word. In it,
we jump to current IP, but we also take care of increasing we jump to current IP, but we also take care of increasing
it by 2 before jumping. ) it by 2 before jumping. )
( Before we continue: are stacks within bounds? ) ( Before we continue: are stacks within bounds? )
( PS ) HL PS_ADDR LDddnn, ( PS ) HL PS_ADDR LDddnn,
SP SUBHLss, SP SUBHLss,
JRC, L2 BWR ( abortUnderflow-B298 ) JRC, lblofl BWR ( abortUnderflow-B298 )
( RS ) IX PUSHqq, HL POPqq, ( RS ) IX PUSHqq, HL POPqq,
DE RS_ADDR LDddnn, DE RS_ADDR LDddnn,
DE SUBHLss, DE SUBHLss,
JRC, L2 BWR ( IX < RS_ADDR? abortUnderflow-B298 ) JRC, lblofl BWR ( IX < RS_ADDR? abortUnderflow-B298 )
E 0 IY+ LDrIXY, E 0 IY+ LDrIXY,
D 1 IY+ LDrIXY, D 1 IY+ LDrIXY,
IY INCss, IY INCss, IY INCss, IY INCss,

17
blk/301
View File

@ -1,14 +1,13 @@
L3 BSET PC ORG @ 0x34 + ! ( execute. DE -> wordref ) lblexec BSET L1 FSET ( B299 ) L2 FSET ( B298 )
( DE -> wordref )
( We don't apply BIN( reliably on stable ABI stuff, we ( We don't apply BIN( reliably on stable ABI stuff, we
might need to adjust addr. Ugly, but well... ) might need to adjust addr. Ugly, but well... )
BIN( @ [IF] BIN( @ [IF]
A XORr, D ORr, IFZ, D BIN( @ 256 / LDrn, THEN, A XORr, D ORr, IFZ, D BIN( @ 256 / LDrn, THEN,
[THEN] [THEN]
LDA(DE), LDA(DE), DE INCss,
L A LDrr, A ORr, IFZ, EXDEHL, JP(HL), THEN,
H BIN( @ 256 / LDrn, A DECr, JRZ, L1 FWR ( compiled B303 )
DE INCss, ( cell or does. push PFA ) DE PUSHqq,
( DE points to PFA ) A DECr, JRZ, lblnext BWR ( cell )
JP(HL), ( continue to does, B302 )

View File

@ -1,11 +1,9 @@
PC ORG @ 0x2c + ! ( doesWord ) ( does. The word was spawned from a definition word that has a
( The word was spawned from a definition word that has a
DOES>. PFA+2 (right after the actual cell) is a link to the DOES>. PFA+2 (right after the actual cell) is a link to the
slot right after that DOES>. Therefore, what we need to do slot right after that DOES>. Therefore, what we need to do
push the cell addr like a regular cell, then follow the push the cell addr like a regular cell, then follow the
linkfrom the PFA, and then continue as a regular linkfrom the PFA, and then continue as a regular
compiledWord. ) compiledWord. )
DE PUSHqq, ( like a regular cell )
EXDEHL, EXDEHL,
HL INCss, HL INCss,
HL INCss, HL INCss,

View File

@ -1,16 +1,15 @@
PC ORG @ 0x0f + ! ( compiledWord ) ( compiled word ) L1 FSET ( execute B301 )
( 1. Push current IP to RS ( 1. Push current IP to RS
2. Set new IP to the second atom of the list 2. Set new IP to the second atom of the list
3. Execute the first atom of the list. ) 3. Execute the first atom of the list. )
IY PUSHqq, HL POPqq, ( <-- IP ) IY PUSHqq, HL POPqq, ( <-- IP )
L4 @ ( pushRS ) CALLnn, lblpushRS @ ( pushRS ) CALLnn,
EXDEHL, ( HL points to PFA ) EXDEHL, ( HL points to PFA )
( While we inc, dereference into DE for execute call later. ) ( While we inc, dereference into DE for execute call later. )
LDDE(HL), LDDE(HL),
HL INCss, HL INCss,
HL PUSHqq, IY POPqq, ( --> IP ) HL PUSHqq, IY POPqq, ( --> IP )
JR, L3 BWR ( execute-B301 ) JR, lblexec BWR ( execute-B301 )

View File

@ -1,4 +1,4 @@
L4 BSET ( chkPS ) lblchkPS BSET ( chkPS )
( Note that you only need to call this in words that push ( Note that you only need to call this in words that push
back to PSP. If they don't, calling chkPS is redundant with back to PSP. If they don't, calling chkPS is redundant with
check in next ) check in next )
@ -9,7 +9,7 @@ L4 BSET ( chkPS )
SP SUBHLss, SP SUBHLss,
EXX, EXX,
CNC RETcc, ( PS_ADDR >= SP? good ) CNC RETcc, ( PS_ADDR >= SP? good )
JR, L2 BWR ( abortUnderflow-B298 ) JR, lblofl BWR ( abortUnderflow-B298 )

View File

@ -5,7 +5,7 @@
CODE EXECUTE CODE EXECUTE
DE POPqq, DE POPqq,
chkPS, chkPS,
JR, L3 BWR ( execute-B301 ) JR, lblexec BWR ( execute-B301 )
( a b c -- b c a ) ( a b c -- b c a )
CODE ROT CODE ROT

View File

@ -10,7 +10,7 @@ CODE PICK
EXDEHL, EXDEHL,
HL PS_ADDR LDddnn, HL PS_ADDR LDddnn,
DE SUBHLss, DE SUBHLss,
CC L2 @ JPccnn, ( abortUnderflow-B298 ) CC lblofl @ JPccnn, ( abortUnderflow-B298 )
BC PUSHqq, BC PUSHqq,
;CODE ;CODE

View File

@ -2,8 +2,7 @@ CODE _find ( cur w -- a f )
HL POPqq, ( w ) HL POPqq, ( w )
DE POPqq, ( cur ) DE POPqq, ( cur )
chkPS, chkPS,
( 3 == find ) lblfind @ CALLnn,
3 BCALL,
IFNZ, IFNZ,
( not found ) ( not found )
HL PUSHqq, HL PUSHqq,

View File

@ -6,7 +6,7 @@
H@ CURRENT ! H@ CURRENT !
; ;
: (entry) WORD [entry] ; : (entry) WORD [entry] ;
: CREATE (entry) 11 ( 11 == cellWord ) C, ; : CREATE (entry) 2 ( cellWord ) C, ;
: VARIABLE CREATE 2 ALLOT ; : VARIABLE CREATE 2 ALLOT ;

View File

@ -1,7 +1,6 @@
: DOES> : DOES>
( Overwrite cellWord in CURRENT ) ( Overwrite cellWord in CURRENT )
( 43 == doesWord ) 3 ( does ) CURRENT @ C!
43 CURRENT @ C!
( When we have a DOES>, we forcefully place HERE to 4 ( When we have a DOES>, we forcefully place HERE to 4
bytes after CURRENT. This allows a DOES word to use "," bytes after CURRENT. This allows a DOES word to use ","
and "C," without messing everything up. ) and "C," without messing everything up. )

View File

@ -7,8 +7,7 @@
( gets its name at the very end. can't comment afterwards ) ( gets its name at the very end. can't comment afterwards )
: _ BEGIN LIT< ) WORD S= UNTIL ; IMMEDIATE : _ BEGIN LIT< ) WORD S= UNTIL ; IMMEDIATE
: _ ( : will get its name almost at the very end ) : _ ( : will get its name almost at the very end )
(entry) (entry) 1 ( compiled ) C,
[ 14 ( == compiledWord ) LITN ] C,
BEGIN BEGIN
WORD FIND WORD FIND
IF ( is word ) DUP IMMED? IF EXECUTE ELSE , THEN IF ( is word ) DUP IMMED? IF EXECUTE ELSE , THEN

View File

@ -1,4 +1,3 @@
: CODE ( same as CREATE, but with native word ) : CODE ( same as CREATE, but with native word )
(entry) (entry) 0 ( native ) C, ;
23 C, ( 23 == nativeWord ) ;
: ;CODE JMPn, 0x1a ( next ) RPCn, ; : ;CODE JMPn, 0x1a ( next ) RPCn, ;

14
blk/812
View File

@ -1,15 +1,15 @@
H@ ORG ! H@ ORG !
JMPn, 0 A,, ( 00, main ) JMPn, 0 A,, ( 03, find ) JMPn, 0 A,, ( 00, main ) JMPn, 0 A,, ( 03, find )
0 A,, ( 06, unused ) 0 A,, ( 08, LATEST ) 0 A,, ( 06, unused ) 0 A,, ( 08, LATEST )
0 A, ( 0a, unused ) JMPn, 0 A,, ( 0b, cellWord ) 0 A, ( 0a, unused ) 0 A, 0 A,, ( 0b, unused )
JMPn, 0 A,, ( 0e compiledWord ) JMPn, 0 A,, ( 11, pushRS ) 0 A, 0 A,, ( 0e, unused ) JMPn, 0 A,, ( 11, pushRS )
JMPn, 0 A,, ( 14, popRS ) JMPn, 0 A,, ( 14, popRS )
DI JMPr, ( 17, nativeWord ) 0 A, 0 A, 0 A,, ( 17, unused )
JMPn, 0 A,, ( 1a, next ) JMPn, 0 A,, ( 1d, unused ) JMPn, 0 A,, ( 1a, next ) 0 A, 0 A,, ( 1d, unused )
0 A, 0 A, ( 20, numberWord ) 0 A, 0 A, ( 22, litWord ) 0 A, 0 A, ( 20, unused ) 0 A, 0 A, ( 22, unused )
0 A, 0 A, ( 24, addrWord ) 0 A, 0 A, ( 26, unused ) 0 A, 0 A, ( 24, unused ) 0 A, 0 A, ( 26, unused )
0 A, 0 A,, ( unused ) 0 A, 0 A,, ( unused )
JMPn, 0 A,, ( 2b, doesWord ) 0 A, 0 A, ( 2e, unused ) 0 A, 0 A,, ( 2b, unused ) 0 A, 0 A, ( 2e, unused )
0 A, 0 A,, ( unused ) 0 A, 0 A,, ( unused )
JMPn, 0 A,, ( 33, execute ) 0 A, 0 A, ( unused ) JMPn, 0 A,, ( 33, execute ) 0 A, 0 A, ( unused )
0 A, 0 A,, ( unused ) 0 A, 0 A,, ( unused )

View File

@ -3,7 +3,7 @@
the "stable ABI" ) the "stable ABI" )
'E' A, 'X' A, 'I' A, 'T' A, 0 A,, ( prev ) 4 A, ( len ) 'E' A, 'X' A, 'I' A, 'T' A, 0 A,, ( prev ) 4 A, ( len )
H@ XCURRENT ! ( set current tip of dict, 0x42 ) H@ XCURRENT ! ( set current tip of dict, 0x42 )
0x17 A, ( nativeWord ) 0 A, ( native )
DX [BP] 0 MOVx[]+, BP DECx, BP DECx, ( popRS ) DX [BP] 0 MOVx[]+, BP DECx, BP DECx, ( popRS )
;CODE NOP, ;CODE NOP,
CODE (br) ( 0x53 ) L2 BSET ( used in br? ) CODE (br) ( 0x53 ) L2 BSET ( used in br? )

View File

@ -1,5 +1,5 @@
PC ORG @ 0x20 + ! ( numberWord ) ORG @ 0xb9 + HERE !
PC ORG @ 0x24 + ! ( addrWord ) ( see B287 for comments ) CODE (n) ( 0xbf, number literal )
DI DX MOVxx, DI [DI] MOVx[], DI PUSHx, DI DX MOVxx, DI [DI] MOVx[], DI PUSHx,
DX INCx, DX INCx, DX INCx, DX INCx,
;CODE ;CODE

View File

@ -3,11 +3,11 @@ PC 0x1d - ORG @ 0x1b + ! ( next )
DI [DI] MOVx[], ( wordref ) DI [DI] MOVx[], ( wordref )
( continue to execute ) ( continue to execute )
L1 BSET PC 0x36 - ORG @ 0x34 + ! ( execute -- DI -> wordref ) L1 BSET PC 0x36 - ORG @ 0x34 + ! ( execute -- DI -> wordref )
AH AH XORrr, AL [DI] MOVr[], AL [DI] MOVr[], DI INCx, ( PFA )
DI INCx, ( PFA ) AL AL ORrr, IFZ, DI JMPr, THEN, ( native )
AX JMPr, ( continue to compiled )
PC 0x11 - ORG @ 0x0f + ! ( compiledWord -- DI -> PFA ) PC 0x11 - ORG @ 0x0f + ! ( compiled -- DI -> PFA )
BP INCx, BP INCx, [BP] 0 DX MOV[]+x, ( pushRS ) BP INCx, BP INCx, [BP] 0 DX MOV[]+x, ( pushRS )
DX DI MOVxx, DX INCx, DX INCx, ( --> IP ) DX DI MOVxx, DX INCx, DX INCx, ( --> IP )
DI [DI] MOVx[], DI [DI] MOVx[],

View File

@ -2,7 +2,7 @@ CODE BYE BEGIN, JMPs, AGAIN, ;CODE
CODE EMIT CODE EMIT
AX POPx, AH 0x0e MOVri, ( print char ) 0x10 INT, AX POPx, AH 0x0e MOVri, ( print char ) 0x10 INT,
;CODE CODE 0 AX AX XORxx, AX PUSHx, ;CODE ;CODE CODE 0 AX AX XORxx, AX PUSHx, ;CODE
: FOO 'X' EMIT ; : BAR 0 IF FOO THEN FOO BYE ; : FOO 'F' EMIT ; : BAR 0 IF FOO THEN FOO BYE ;
L3 BSET 3 A, 'B' A, 'A' A, 'R' A, L3 BSET 3 A, 'B' A, 'A' A, 'R' A,
PC 3 - ORG @ 1+ ! ( main ) PC 3 - ORG @ 1+ ! ( main )
SP PS_ADDR MOVxI, SP PS_ADDR MOVxI,

Binary file not shown.