1
0
mirror of https://github.com/hsoft/collapseos.git synced 2024-11-26 16:28:05 +11:00

Compare commits

..

No commits in common. "aca9bc9058d60539ba37bd4a7bfeabfbe045308c" and "3383a000404eabfe18cf79599effbf4d6d991f8e" have entirely different histories.

34 changed files with 134 additions and 102 deletions

View File

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

21
blk/085
View File

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

14
blk/086
View File

@ -1,13 +1,13 @@
3: DOES>. This word is created by "DOES>" and is followed
0x2b: doesWord. This word is created by "DOES>" and is followed
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 word. Upon execution, after having pushed its cell
addr to PSP, it executes its reference exactly like a
compiled word.
addr to PSP, it execute its reference exactly like a
compiledWord.
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,12 +3,14 @@
: BJP, BIN( @ + JPnn, ;
: BJPcc, BIN( @ + JPccnn, ;
VARIABLE lblchkPS
: chkPS, lblchkPS @ CALLnn, ; ( chkPS, B305 )
CREATE lblnext 0x1a , ( stable ABI until set in B300 )
: JPNEXT, lblnext @ JPnn, ;
: JPNEXT, 26 BJP, ; ( 26 == next )
: chkPS, L4 @ CALLnn, ; ( chkPS, B305 )
: CODE ( same as CREATE, but with native word )
(entry) 0 C, ( 0 == native ) ;
(entry)
23 C, ( 23 == nativeWord )
;
: ;CODE JPNEXT, ;

View File

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

View File

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

View File

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

28
blk/283
View File

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

View File

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

View File

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

16
blk/289 Normal file
View File

@ -0,0 +1,16 @@
( 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 Normal file
View File

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

View File

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

View File

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

View File

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

16
blk/299
View File

@ -1,16 +0,0 @@
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 @@
lblnext BSET PC ORG @ 0x1b + ! ( next )
PC ORG @ 0x1b + ! ( next )
( 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
it by 2 before jumping. )
( Before we continue: are stacks within bounds? )
( PS ) HL PS_ADDR LDddnn,
SP SUBHLss,
JRC, lblofl BWR ( abortUnderflow-B298 )
JRC, L2 BWR ( abortUnderflow-B298 )
( RS ) IX PUSHqq, HL POPqq,
DE RS_ADDR LDddnn,
DE SUBHLss,
JRC, lblofl BWR ( IX < RS_ADDR? abortUnderflow-B298 )
JRC, L2 BWR ( IX < RS_ADDR? abortUnderflow-B298 )
E 0 IY+ LDrIXY,
D 1 IY+ LDrIXY,
IY INCss, IY INCss,

17
blk/301
View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

14
blk/812
View File

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

View File

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

View File

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

View File

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

View File

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

Binary file not shown.