1
0
mirror of https://github.com/hsoft/collapseos.git synced 2024-11-02 06:30:55 +11:00

Compare commits

..

No commits in common. "863540f7c6ad4913f222fded5ec674802631ce0c" and "f2817870aa4fa9cc215da15a852614d3e027a8b9" have entirely different histories.

66 changed files with 271 additions and 269 deletions

View File

@ -5,7 +5,7 @@ MASTER INDEX
120 Linker 140 Addressed devices
150 Extra words
200 Z80 assembler 260 Cross compilation
280 Z80 boot code 350 Core words
280 Z80 boot code 390 Cross-compiled core
490 TRS-80 Recipe 520 Fonts
550 TI-84+ Recipe 580 RC2014 Recipe
620 Sega Master System Recipe

16
blk/350
View File

@ -1,16 +0,0 @@
Core words
This section contains arch-independent core words of Collapse
OS. Those words are written in a way that make them entirely
cross-compilable (see B260). When building Collapse OS, these
words come right after the boot binary (B280).
Because this unit is designed to be cross-compiled, things are
a little weird. It is compiling in the context of a full
Forth interpreter with all bells and whistles (and z80
assembler), but it has to obey strict rules:
1. Although it cannot compile a word that isn't defined yet,
it can still execute an immediate from the host system.
(cont.)

16
blk/351
View File

@ -1,16 +0,0 @@
2. Immediate words that have been cross compiled *cannot* be
used. Only immediates from the host system can be used.
3. If an immediate word compiles words, it can only be words
that are part of the stable ABI.
All of this is because when cross compiling, all atom ref-
erences are offsetted to the target system and are thus
unusable directly. For the same reason, any reference to a word
in the host system will obviously be wrong in the target
system. More details in B260.
(cont.)

View File

@ -1,9 +0,0 @@
This unit is loaded in two "low" and "high" parts. The low part
is the biggest chunk and has the most definitions. The high
part is the "sensitive" chunk and contains "LITN", ":" and ";"
definitions which, once defined, kind of make any more defs
impossible.
The gap between these 2 parts is the ideal place to put device
driver code. Load the low part with "353 LOAD", the high part
with "380 LOAD"

13
blk/353
View File

@ -1,13 +0,0 @@
: RAM+ [ RAMSTART LITN ] + ;
: BIN+ [ BIN( @ LITN ] + ;
: HERE 0x04 RAM+ ;
: CURRENT* 0x51 RAM+ ;
: CURRENT CURRENT* @ ;
: H@ HERE @ ;
: FIND ( w -- a f ) CURRENT @ SWAP _find ;
: QUIT
(resRS)
0 0x08 RAM+ ! ( 08 == C<* override )
LIT< (main) FIND DROP EXECUTE
;
1 25 LOADR+ ( xcomp core low )

12
blk/354
View File

@ -1,12 +0,0 @@
: ABORT (resSP) QUIT ;
: ERR LIT< (print) FIND IF EXECUTE THEN ABORT ;
: = CMP NOT ; : < CMP -1 = ; : > CMP 1 = ;
: 0< 32767 > ; : >= < NOT ; : <= > NOT ; : 0>= 0< NOT ;
: >< ( n l h -- f ) 2 PICK > ( n l f ) ROT ROT > AND ;
: =><= 2 PICK >= ( n l f ) ROT ROT >= AND ;
: MIN ( n n - n ) 2DUP > IF SWAP THEN DROP ;
: MAX ( n n - n ) 2DUP < IF SWAP THEN DROP ;
: C@+ ( a -- a+1 c ) DUP C@ SWAP 1+ SWAP ;
: C!+ ( c a -- a+1 ) SWAP OVER C! 1+ ;
: C@- ( a -- a-1 c ) DUP C@ SWAP 1- SWAP ;
: C!- ( c a -- a-1 ) SWAP OVER C! 1- ;

11
blk/356
View File

@ -1,11 +0,0 @@
( parsed is tight, all comments ahead. We read the first char
outside of the loop because it *has* to be nonzero, which
means _pdacc *has* to return 0.
Then, we check for '-'. If we get it, we advance by one,
recurse and invert result.
We loop until _pdacc is nonzero, which means either WS or
non-digit. 1 means WS, which means parsing was a success.
-1 means non-digit, which means we have a non-decimal. )

16
blk/357
View File

@ -1,16 +0,0 @@
: (parsed) ( a -- n f )
DUP C@ ( a c )
DUP '-' = IF
DROP 1+ ( a+1 ) (parsed) 0 ROT ( f 0 n )
- SWAP EXIT ( 0-n f )
THEN
0 SWAP _pdacc ( a r f )
DUP IF 2DROP 0 EXIT THEN
BEGIN ( a r 0 )
DROP SWAP 1+ ( r a+1 )
DUP C@ ( r a c )
ROT SWAP ( a r c )
_pdacc ( a r f )
DUP UNTIL
1 = ( a r f )
ROT DROP ( r f ) ;

11
blk/358
View File

@ -1,11 +0,0 @@
( strings being sent to parse routines are always null
terminated )
: (parsec) ( a -- n f )
( apostrophe is ASCII 39 )
DUP C@ 39 = OVER 2+ C@ 39 = AND ( a f )
NOT IF 0 EXIT THEN ( a 0 )
( surrounded by apos, good, return )
1+ C@ 1 ( n 1 )
;

View File

@ -1,8 +0,0 @@
( returns negative value on error )
: _ ( c -- n )
DUP '0' '9' =><= IF '0' - EXIT THEN
DUP 'a' 'f' =><= IF 0x57 ( 'a' - 10 ) - EXIT THEN
DROP -1 ( bad )
;

15
blk/360
View File

@ -1,15 +0,0 @@
: (parseh) ( a -- n f )
( '0': ASCII 0x30 'x': 0x78 0x7830: 30768 )
DUP @ 30768 = NOT IF 0 EXIT THEN ( a 0 )
( We have "0x" prefix )
2+
0 ( a r )
BEGIN
SWAP C@+ ( r a+1 c )
DUP NOT IF 2DROP 1 EXIT THEN ( r, 1 )
_ ( r a n )
DUP 0< IF ROT 2DROP 0 EXIT THEN ( a 0 )
ROT 16 * + ( a r*16+n )
AGAIN
;

10
blk/368
View File

@ -1,10 +0,0 @@
: [entry] ( w -- )
H@ SWAP SCPY ( h )
H@ SWAP - ( sz )
( write prev value )
H@ CURRENT @ - ,
C, ( write size )
H@ CURRENT !
;
: (entry) WORD [entry] ;

23
blk/390
View File

@ -1,11 +1,14 @@
( Initializes the readln subsystem )
: RDLN$
H@ 0x32 ( IN(* ) RAM+ !
( plus 2 for extra bytes after buffer: 1 for
the last typed 0x0a and one for the following NULL. )
IN) IN( - ALLOT
(infl)
['] RDLN< 0x0c RAM+ !
1 0x06 RAM+ ! ( 06 == C<? )
;
Cross-compiled core
This units contains core Collapse OS that are cross-compiled.
During building, these come right after the boot binary (B280).
Because this unit is designed to be cross-compiled, things are
a little weird. It is compiling in the context of a full
Forth interpreter with all bells and whistles (and z80
assembler), but it has to obey strict rules:
1. It cannot compile a word from higher layers. Immediates are
fine.
(cont.)

27
blk/391
View File

@ -1,13 +1,16 @@
: .2 DUP 10 < IF SPC THEN . ;
: EOL? ( c -- f ) DUP 0xd = SWAP NOT OR ;
: LIST
BLK@
16 0 DO
I 1+ .2 SPC
64 I * BLK( + DUP 64 + SWAP DO
I C@ DUP EOL? IF DROP LEAVE ELSE EMIT THEN
LOOP
NL
LOOP
;
2. Immediate words that have been cross compiled *cannot* be
used. Only immediates from the host system can be used.
3. If an immediate word compiles words, it can only be words
that are part of the stable ABI.
All of this is because when cross compiling, all atom ref-
erences are offsetted to the target system and are thus
unusable directly. For the same reason, any reference to a word
in the host system will obviously be wrong in the target
system. More details in B260.
(cont.)

24
blk/392
View File

@ -1,15 +1,9 @@
: INTERPRET
BEGIN
WORD DUP C@ EOT? IF DROP EXIT THEN
FIND NOT IF (parse) ELSE EXECUTE THEN
C<? NOT IF SPC LIT< ok (print) NL THEN
AGAIN ;
( Read from BOOT C< PTR and inc it. )
: (boot<)
( 2e == BOOT C< PTR )
0x2e ( BOOT C< PTR ) RAM+ @ DUP C@ ( a c )
SWAP 1 + 0x2e RAM+ ! ( c ) ;
( pre-comment for tight LOAD: The 0x08==I check after INTERPRET
is to check whether we're restoring to "_", the word above.
if yes, then we're in a nested load. Also, the 1 in 0x06 is
to avoid tons of "ok" displays. )
This unit is loaded in two "low" and "high" parts. The low part
is the biggest chunk and has the most definitions. The high
part is the "sensitive" chunk and contains "LITN", ":" and ";"
definitions which, once defined, kind of make any more defs
impossible.
The gap between these 2 parts is the ideal place to put device
driver code. Load the low part with "393 LOAD", the high part
with "415 LOAD"

31
blk/393
View File

@ -1,16 +1,15 @@
: LOAD
BLK> @ >R ( save restorable variables to RSP )
0x08 RAM+ @ >R ( 08 == C<* override )
0x06 RAM+ @ >R ( C<? )
0x2e RAM+ @ >R ( boot ptr )
BLK@
BLK( 0x2e RAM+ ! ( Point to beginning of BLK )
['] (boot<) 0x08 RAM+ !
1 0x06 RAM+ ! ( 06 == C<? )
INTERPRET
R> 0x2e RAM+ ! R> 0x06 RAM+ !
I 0x08 RAM+ @ = IF ( nested load )
R> DROP ( C<* ) R> BLK@
ELSE ( not nested )
R> 0x08 RAM+ ! R> DROP ( BLK> )
THEN ;
: RAM+ [ RAMSTART LITN ] + ;
: BIN+ [ BIN( @ LITN ] + ;
: HERE 0x04 RAM+ ;
: CURRENT* 0x51 RAM+ ;
: CURRENT CURRENT* @ ;
( w -- a f )
: FIND CURRENT @ SWAP _find ;
: QUIT
(resRS)
0 0x08 RAM+ ! ( 08 == C<* override )
LIT< (main) FIND DROP EXECUTE
;
1 25 LOADR+ ( xcomp core low )

16
blk/394
View File

@ -1,4 +1,12 @@
: LOAD+ BLK> @ + LOAD ;
( b1 b2 -- )
: LOADR 1+ SWAP DO I DUP . NL LOAD LOOP ;
: LOADR+ BLK> @ + SWAP BLK> @ + SWAP LOADR ;
: ABORT (resSP) QUIT ;
: ERR LIT< (print) FIND IF EXECUTE THEN ABORT ;
: = CMP NOT ; : < CMP -1 = ; : > CMP 1 = ;
: 0< 32767 > ; : >= < NOT ; : <= > NOT ; : 0>= 0< NOT ;
: >< ( n l h -- f ) 2 PICK > ( n l f ) ROT ROT > AND ;
: =><= 2 PICK >= ( n l f ) ROT ROT >= AND ;
: MIN ( n n - n ) 2DUP > IF SWAP THEN DROP ;
: MAX ( n n - n ) 2DUP < IF SWAP THEN DROP ;
: C@+ ( a -- a+1 c ) DUP C@ SWAP 1+ SWAP ;
: C!+ ( c a -- a+1 ) SWAP OVER C! 1+ ;
: C@- ( a -- a-1 c ) DUP C@ SWAP 1- SWAP ;
: C!- ( c a -- a-1 ) SWAP OVER C! 1- ;

View File

25
blk/396
View File

@ -1,14 +1,11 @@
: (main) INTERPRET BYE ;
: BOOT
0x02 RAM+ CURRENT* !
CURRENT @ 0x2e RAM+ ! ( 2e == BOOT C< PTR )
0 0x08 RAM+ ! ( 08 == C<* override )
0 0x53 RAM+ ! ( 53 == (emit) override )
0 0x55 RAM+ ! ( 55 == (key) override )
0 0x0a RAM+ ! ( NLPTR )
( 0c == C<* )
['] (boot<) 0x0c RAM+ !
( boot< always has a char waiting. 06 == C<?* )
1 0x06 RAM+ ! INTERPRET
RDLN$ LIT< _sys [entry]
LIT< CollapseOS (print) NL (main) ;
( parsed is tight, all comments ahead. We read the first char
outside of the loop because it *has* to be nonzero, which
means _pdacc *has* to return 0.
Then, we check for '-'. If we get it, we advance by one,
recurse and invert result.
We loop until _pdacc is nonzero, which means either WS or
non-digit. 1 means WS, which means parsing was a success.
-1 means non-digit, which means we have a non-decimal. )

31
blk/397
View File

@ -1,15 +1,16 @@
( Now we have "as late as possible" stuff )
: DO COMPILE 2>R H@ ; IMMEDIATE
: LOOP COMPILE (loop) H@ - , ; IMMEDIATE
( LEAVE is implemented in low xcomp )
: LITN 32 , , ( 32 == NUMBER ) ;
( 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)
[ 14 ( == compiledWord ) LITN ] C,
BEGIN
WORD FIND
IF ( is word ) DUP IMMED? IF EXECUTE ELSE , THEN
ELSE ( maybe number ) (parse) LITN THEN
AGAIN ;
: (parsed) ( a -- n f )
DUP C@ ( a c )
DUP '-' = IF
DROP 1+ ( a+1 ) (parsed) 0 ROT ( f 0 n )
- SWAP EXIT ( 0-n f )
THEN
0 SWAP _pdacc ( a r f )
DUP IF 2DROP 0 EXIT THEN
BEGIN ( a r 0 )
DROP SWAP 1+ ( r a+1 )
DUP C@ ( r a c )
ROT SWAP ( a r c )
_pdacc ( a r f )
DUP UNTIL
1 = ( a r f )
ROT DROP ( r f ) ;

23
blk/398
View File

@ -1,14 +1,11 @@
: IF ( -- a | a: br cell addr )
COMPILE (?br) H@ 2 ALLOT ( br cell allot )
; IMMEDIATE
: THEN ( a -- | a: br cell addr )
DUP H@ -^ SWAP ( a-H a ) !
; IMMEDIATE
: ELSE ( a1 -- a2 | a1: IF cell a2: ELSE cell )
COMPILE (br)
2 ALLOT
DUP H@ -^ SWAP ( a-H a )
!
H@ 2- ( push a. -2 for allot offset )
; IMMEDIATE
( strings being sent to parse routines are always null
terminated )
: (parsec) ( a -- n f )
( apostrophe is ASCII 39 )
DUP C@ 39 = OVER 2+ C@ 39 = AND ( a f )
NOT IF 0 EXIT THEN ( a 0 )
( surrounded by apos, good, return )
1+ C@ 1 ( n 1 )
;

17
blk/399
View File

@ -1,9 +1,8 @@
: BEGIN H@ ; IMMEDIATE
: AGAIN COMPILE (br) H@ - , ; IMMEDIATE
: UNTIL COMPILE (?br) H@ - , ; IMMEDIATE
: [ INTERPRET ; IMMEDIATE
: ] R> DROP ;
: LIT< WORD 34 , SCPY 0 C, ; IMMEDIATE
: LITA 36 , , ;
: COMPILE ' LITA ['] , , ; IMMEDIATE
: [COMPILE] ' , ; IMMEDIATE
( returns negative value on error )
: _ ( c -- n )
DUP '0' '9' =><= IF '0' - EXIT THEN
DUP 'a' 'f' =><= IF 0x57 ( 'a' - 10 ) - EXIT THEN
DROP -1 ( bad )
;

26
blk/400
View File

@ -1,11 +1,15 @@
( ';' can't have its name right away because, when created, it
is not an IMMEDIATE yet and will not be treated properly by
xcomp. )
: _
['] EXIT ,
R> DROP ( exit : )
; IMMEDIATE
: ['] ' LITA ; IMMEDIATE
';' X' _ 4 - C! ( give ; its name )
':' X' _ 4 - C! ( give : its name )
'(' X' _ 4 - C!
: (parseh) ( a -- n f )
( '0': ASCII 0x30 'x': 0x78 0x7830: 30768 )
DUP @ 30768 = NOT IF 0 EXIT THEN ( a 0 )
( We have "0x" prefix )
2+
0 ( a r )
BEGIN
SWAP C@+ ( r a+1 c )
DUP NOT IF 2DROP 1 EXIT THEN ( r, 1 )
_ ( r a n )
DUP 0< IF ROT 2DROP 0 EXIT THEN ( a 0 )
ROT 16 * + ( a r*16+n )
AGAIN
;

View File

View File

View File

View File

@ -4,8 +4,8 @@
DUP NOT IF DROP 0x0c RAM+ @ THEN ( 0c == C<* )
EXECUTE
;
: , H@ ! H@ 2+ HERE ! ;
: C, H@ C! H@ 1+ HERE ! ;
: , HERE @ ! HERE @ 2+ HERE ! ;
: C, HERE @ C! HERE @ 1+ HERE ! ;
: BIT@ ( bit addr -- f ) C@ SWAP RSHIFT 0x01 AND ;
: BIT! ( f bit addr -- )
SWAP 0x01 SWAP LSHIFT ROT ( addr mask f )

View File

View File

View File

11
blk/408 Normal file
View File

@ -0,0 +1,11 @@
: [entry]
HERE @ ( w h )
SWAP SCPY ( h )
HERE @ SWAP - ( sz )
( write prev value )
HERE @ CURRENT @ - ,
C, ( write size )
HERE @ CURRENT !
;
: (entry) WORD [entry] ;

View File

@ -1,6 +1,7 @@
( Words here until the end of the low part, unlike words
preceeding them, aren't immediately needed for boot. But its
better to have as many words as possible in the xcomp part. )
: H@ HERE @ ;
: IMMEDIATE
CURRENT @ 1-
DUP C@ 128 OR SWAP C! ;

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

View File

11
blk/430 Normal file
View File

@ -0,0 +1,11 @@
( Initializes the readln subsystem )
: RDLN$
H@ 0x32 ( IN(* ) RAM+ !
( plus 2 for extra bytes after buffer: 1 for
the last typed 0x0a and one for the following NULL. )
IN) IN( - ALLOT
(infl)
['] RDLN< 0x0c RAM+ !
1 0x06 RAM+ ! ( 06 == C<? )
;

13
blk/431 Normal file
View File

@ -0,0 +1,13 @@
: .2 DUP 10 < IF SPC THEN . ;
: EOL? ( c -- f ) DUP 0xd = SWAP NOT OR ;
: LIST
BLK@
16 0 DO
I 1+ .2 SPC
64 I * BLK( + DUP 64 + SWAP DO
I C@ DUP EOL? IF DROP LEAVE ELSE EMIT THEN
LOOP
NL
LOOP
;

15
blk/432 Normal file
View File

@ -0,0 +1,15 @@
: INTERPRET
BEGIN
WORD DUP C@ EOT? IF DROP EXIT THEN
FIND NOT IF (parse) ELSE EXECUTE THEN
C<? NOT IF SPC LIT< ok (print) NL THEN
AGAIN ;
( Read from BOOT C< PTR and inc it. )
: (boot<)
( 2e == BOOT C< PTR )
0x2e ( BOOT C< PTR ) RAM+ @ DUP C@ ( a c )
SWAP 1 + 0x2e RAM+ ! ( c ) ;
( pre-comment for tight LOAD: The 0x08==I check after INTERPRET
is to check whether we're restoring to "_", the word above.
if yes, then we're in a nested load. Also, the 1 in 0x06 is
to avoid tons of "ok" displays. )

16
blk/433 Normal file
View File

@ -0,0 +1,16 @@
: LOAD
BLK> @ >R ( save restorable variables to RSP )
0x08 RAM+ @ >R ( 08 == C<* override )
0x06 RAM+ @ >R ( C<? )
0x2e RAM+ @ >R ( boot ptr )
BLK@
BLK( 0x2e RAM+ ! ( Point to beginning of BLK )
['] (boot<) 0x08 RAM+ !
1 0x06 RAM+ ! ( 06 == C<? )
INTERPRET
R> 0x2e RAM+ ! R> 0x06 RAM+ !
I 0x08 RAM+ @ = IF ( nested load )
R> DROP ( C<* ) R> BLK@
ELSE ( not nested )
R> 0x08 RAM+ ! R> DROP ( BLK> )
THEN ;

4
blk/434 Normal file
View File

@ -0,0 +1,4 @@
: LOAD+ BLK> @ + LOAD ;
( b1 b2 -- )
: LOADR 1+ SWAP DO I DUP . NL LOAD LOOP ;
: LOADR+ BLK> @ + SWAP BLK> @ + SWAP LOADR ;

14
blk/436 Normal file
View File

@ -0,0 +1,14 @@
: (main) INTERPRET BYE ;
: BOOT
0x02 RAM+ CURRENT* !
CURRENT @ 0x2e RAM+ ! ( 2e == BOOT C< PTR )
0 0x08 RAM+ ! ( 08 == C<* override )
0 0x53 RAM+ ! ( 53 == (emit) override )
0 0x55 RAM+ ! ( 55 == (key) override )
0 0x0a RAM+ ! ( NLPTR )
( 0c == C<* )
['] (boot<) 0x0c RAM+ !
( boot< always has a char waiting. 06 == C<?* )
1 0x06 RAM+ ! INTERPRET
RDLN$ LIT< _sys [entry]
LIT< CollapseOS (print) NL (main) ;

15
blk/437 Normal file
View File

@ -0,0 +1,15 @@
( Now we have "as late as possible" stuff )
: DO COMPILE 2>R H@ ; IMMEDIATE
: LOOP COMPILE (loop) H@ - , ; IMMEDIATE
( LEAVE is implemented in low xcomp )
: LITN 32 , , ( 32 == NUMBER ) ;
( 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)
[ 14 ( == compiledWord ) LITN ] C,
BEGIN
WORD FIND
IF ( is word ) DUP IMMED? IF EXECUTE ELSE , THEN
ELSE ( maybe number ) (parse) LITN THEN
AGAIN ;

14
blk/438 Normal file
View File

@ -0,0 +1,14 @@
: IF ( -- a | a: br cell addr )
COMPILE (?br) H@ 2 ALLOT ( br cell allot )
; IMMEDIATE
: THEN ( a -- | a: br cell addr )
DUP H@ -^ SWAP ( a-H a ) !
; IMMEDIATE
: ELSE ( a1 -- a2 | a1: IF cell a2: ELSE cell )
COMPILE (br)
2 ALLOT
DUP H@ -^ SWAP ( a-H a )
!
H@ 2- ( push a. -2 for allot offset )
; IMMEDIATE

9
blk/439 Normal file
View File

@ -0,0 +1,9 @@
: BEGIN H@ ; IMMEDIATE
: AGAIN COMPILE (br) H@ - , ; IMMEDIATE
: UNTIL COMPILE (?br) H@ - , ; IMMEDIATE
: [ INTERPRET ; IMMEDIATE
: ] R> DROP ;
: LIT< WORD 34 , SCPY 0 C, ; IMMEDIATE
: LITA 36 , , ;
: COMPILE ' LITA ['] , , ; IMMEDIATE
: [COMPILE] ' , ; IMMEDIATE

11
blk/440 Normal file
View File

@ -0,0 +1,11 @@
( ';' can't have its name right away because, when created, it
is not an IMMEDIATE yet and will not be treated properly by
xcomp. )
: _
['] EXIT ,
R> DROP ( exit : )
; IMMEDIATE
: ['] ' LITA ; IMMEDIATE
';' X' _ 4 - C! ( give ; its name )
':' X' _ 4 - C! ( give : its name )
'(' X' _ 4 - C!

View File

@ -6,9 +6,9 @@
RAMSTART 0x70 + CONSTANT ACIA_MEM
212 LOAD ( z80 assembler )
262 LOAD ( xcomp ) 270 LOAD ( xcomp overrides )
282 LOAD ( boot.z80 ) 353 LOAD ( xcomp core low )
282 LOAD ( boot.z80 ) 393 LOAD ( xcomp core low )
582 LOAD ( acia )
380 LOAD ( xcomp core high )
420 LOAD ( xcomp core high )
(entry) _
( Update LATEST )
PC ORG @ 8 + !

Binary file not shown.

View File

@ -6,7 +6,7 @@
270 LOAD ( xcomp overrides )
282 LOAD ( boot.z80 )
353 LOAD ( xcomp core low )
393 LOAD ( xcomp core low )
: (emit) 0 PC! ;
: (key) 0 PC@ ;
: EFS@
@ -23,7 +23,7 @@
LOOP
;
380 LOAD ( xcomp core high )
420 LOAD ( xcomp core high )
(entry) _
( Update LATEST )
PC ORG @ 8 + !

View File

@ -23,11 +23,11 @@ RETN, 0x98 ZFILL, ( 0x100 )
CURRENT @ XCURRENT !
0x100 BIN( !
282 LOAD ( boot.z80 )
353 LOAD ( xcomp core low )
393 LOAD ( xcomp core low )
CREATE ~FNT CPFNT7x7
623 628 LOADR ( VDP )
632 637 LOADR ( PAD )
380 LOAD ( xcomp core high )
420 LOAD ( xcomp core high )
(entry) _
( Update LATEST )
PC ORG @ 8 + !

View File

@ -60,11 +60,11 @@ CURRENT @ XCURRENT !
0x100 BIN( !
282 LOAD ( boot.z80 )
353 LOAD ( xcomp core low )
393 LOAD ( xcomp core low )
CREATE ~FNT CPFNT3x5
555 560 LOADR ( LCD low )
566 570 LOADR ( KBD low )
380 LOAD ( xcomp core high )
420 LOAD ( xcomp core high )
(entry) _
( Update LATEST )
PC ORG @ 8 + !

View File

@ -7,9 +7,9 @@ RS_ADDR 0x80 - CONSTANT RAMSTART
0x3000 BIN( !
282 LOAD ( boot.z80 )
353 LOAD ( xcomp core low )
393 LOAD ( xcomp core low )
492 LOAD ( trs80 )
380 LOAD ( xcomp core high )
420 LOAD ( xcomp core high )
(entry) _
( Update LATEST )
PC ORG @ 8 + !