Compare commits

...

4 Commits

Author SHA1 Message Date
Virgil Dupras 7eeec67ff5 Add extra words WIPED? and FREEBLKS? 2020-06-23 07:21:33 -04:00
Virgil Dupras 9ab5cda397 ed: rename I to i
Shadowing core "I" is too messy. As soon as ed is loaded in memory,
nothing else that isn't "i-aware" can be loaded anymore.

I guess that's why "contexts" exist in Starting Forth, but adding
this concept just for allowing the shadowing of core words seems
overkill to me. Renaming I to i in ed seems better.
2020-06-23 07:08:21 -04:00
Virgil Dupras af339d8c6a VE: properly make buffer dirty on E and X 2020-06-23 06:53:30 -04:00
Virgil Dupras 2d9a07d215 blkunpack: don't include trailing empty lines
This was becoming heavy to manage.
2020-06-23 06:52:34 -04:00
257 changed files with 28 additions and 1365 deletions

View File

@ -11,6 +11,3 @@ MASTER INDEX
620 Sega Master System Recipe 620 Sega Master System Recipe
650 AVR assembler 730 8086 assembler 650 AVR assembler 730 8086 assembler
800 8086 boot code 830 PC/AT recipe 800 8086 boot code 830 PC/AT recipe

14
blk/004
View File

@ -1,16 +1,2 @@
21 How blocks are organized 22 Addressed devices 21 How blocks are organized 22 Addressed devices
23 Branching 23 Branching

View File

@ -9,8 +9,3 @@ are hexadecimals (example "0x12ef"), "0b" prefixes indicate
binary (example "0b1010"), char literals are single characters binary (example "0b1010"), char literals are single characters
surrounded by ' (example 'X'). Char literals can't be used for surrounded by ' (example 'X'). Char literals can't be used for
whitespaces. whitespaces.

View File

@ -12,5 +12,3 @@ writes that number as a literal, followed by a reference to
Example: ": foo [COMPILE] bar;" is the equivalent of ": foo bar Example: ": foo [COMPILE] bar;" is the equivalent of ": foo bar
;" if bar is not an immediate. However, ": foo COMPILE bar ;" ;" if bar is not an immediate. However, ": foo COMPILE bar ;"
is the equivalent of ": foo ['] bar , ;". Got it? is the equivalent of ": foo ['] bar , ;". Got it?

10
blk/009
View File

@ -4,13 +4,3 @@ prompt control to a RS-232 device instead of the keyboard.
Interpreter output is unbuffered and only has EMIT. This Interpreter output is unbuffered and only has EMIT. This
word can also be overriden, mostly as a companion to the word can also be overriden, mostly as a companion to the
raison d'etre of your KEY override. raison d'etre of your KEY override.

View File

@ -7,10 +7,3 @@ support the "-" prefix, but under the hood, it's all unsigned.
This leads to some oddities. For example, "-1 0 <" is false. This leads to some oddities. For example, "-1 0 <" is false.
To compare whether something is negative, use the "0<" word To compare whether something is negative, use the "0<" word
which is the equivalent to "0x7fff >". which is the equivalent to "0x7fff >".

View File

@ -13,4 +13,3 @@ At compile time, colon definition stops processing words when
reaching the DOES>. reaching the DOES>.
Example: ": CONSTANT CREATE HERE @ ! DOES> @ ;" Example: ": CONSTANT CREATE HERE @ ! DOES> @ ;"

View File

@ -6,11 +6,3 @@ Although the usage of absolute LOAD calls are minimally used
(relative LOADs are preferred), they are sometimes unavoidable. (relative LOADs are preferred), they are sometimes unavoidable.
When you span Collapse OS over multiple disks, don't forget to When you span Collapse OS over multiple disks, don't forget to
adjust those absolute LOADs. adjust those absolute LOADs.

View File

@ -11,6 +11,3 @@ try to strive towards a few goals:
4. B200-B500 are for bootstrapping 4. B200-B500 are for bootstrapping
5. The rest is for recipes. 5. The rest is for recipes.
6. I'm not sure yet how I'll organize multiple arches. 6. I'm not sure yet how I'll organize multiple arches.

10
blk/022
View File

@ -4,13 +4,3 @@ A@ and A! are the indirect versions of C@ and C!. Their target
word is controlled through A@* and A!* and by default point to word is controlled through A@* and A!* and by default point to
C@ and C*. There is also a AMOVE word that is the same as MOVE C@ and C*. There is also a AMOVE word that is the same as MOVE
but using A@ and A!. but using A@ and A!.

View File

@ -9,8 +9,3 @@ The reasoning behind this intentional limit is that huge
branches are generally a indicator that a logic ought to be branches are generally a indicator that a logic ought to be
simplified. So here's one more constraint for you to help you simplified. So here's one more constraint for you to help you
towards simplicity. towards simplicity.

View File

@ -10,7 +10,3 @@ and Extra words (B150).
52 Addressed devices 54 Arithmetic / Bits 52 Addressed devices 54 Arithmetic / Bits
56 Logic 58 Strings 56 Logic 58 Strings
60 I/O 64 Disk 60 I/O 64 Disk

View File

@ -7,10 +7,3 @@ Words between "()" are "support words" that aren't really meant
to be used directly, but as part of another word. to be used directly, but as part of another word.
"*I*" in description indicates an IMMEDIATE word. "*I*" in description indicates an IMMEDIATE word.

13
blk/035
View File

@ -1,16 +1,3 @@
(cont.) (cont.)
~ - Container for native code. Usually not an executable word. ~ - Container for native code. Usually not an executable word.
? - Is it ...? (example: IMMED?) ? - Is it ...? (example: IMMED?)

11
blk/038
View File

@ -3,14 +3,3 @@ FORGET x -- Rewind the dictionary (both CURRENT and HERE)
up to x's previous entry. up to x's previous entry.
PREV a -- a Return a wordref's previous entry. PREV a -- a Return a wordref's previous entry.
WORD( a -- a Get wordref's beginning addr. WORD( a -- a Get wordref's beginning addr.

11
blk/044
View File

@ -3,14 +3,3 @@ INTERPRET -- Get a line from stdin, compile it in tmp memory,
then execute the compiled contents. then execute the compiled contents.
LEAVE -- In a DO..LOOP, exit at the next LOOP call. LEAVE -- In a DO..LOOP, exit at the next LOOP call.
QUIT -- Return to interpreter prompt immediately QUIT -- Return to interpreter prompt immediately

10
blk/047
View File

@ -4,13 +4,3 @@ PICK Pick nth item from stack. "0 PICK" = DUP,
"1 PICK" = OVER. "1 PICK" = OVER.
ROLL Rotate PSP over n items. "1 ROLL" = SWAP, ROLL Rotate PSP over n items. "1 ROLL" = SWAP,
"2 ROLL" = ROT. 0 is noop. "2 ROLL" = ROT. 0 is noop.

View File

@ -7,10 +7,3 @@ R> R:n -- n Pops RS and push to PS
I -- n Copy RS TOS to PS I -- n Copy RS TOS to PS
I' -- n Copy RS second item to PS I' -- n Copy RS second item to PS
J -- n Copy RS third item to PS J -- n Copy RS third item to PS

View File

@ -8,9 +8,3 @@ MOVE a1 a2 u -- Copy u bytes from a1 to a2, starting
MOVE- a1 a2 u -- Copy u bytes from a1 to a2, starting MOVE- a1 a2 u -- Copy u bytes from a1 to a2, starting
with a1+u, going down. with a1+u, going down.
MOVE, a u -- Copy u bytes from a to HERE. MOVE, a u -- Copy u bytes from a to HERE.

View File

@ -8,9 +8,3 @@ A! c a -- Indirect C!
A@* -- a Address for A@ word A@* -- a Address for A@ word
A!* -- a Address for A! word A!* -- a Address for A! word
AMOVE src dst u -- Same as MOVE, but with A@ and A! AMOVE src dst u -- Same as MOVE, but with A@ and A!

View File

@ -10,7 +10,3 @@ CMP n1 n2 -- n Compare n1 and n2 and set n to -1, 0, or 1.
MIN a b -- n Returns the lowest of a and b MIN a b -- n Returns the lowest of a and b
MAX a b -- n Returns the highest of a and b MAX a b -- n Returns the highest of a and b
NOT f -- f Push the logical opposite of f NOT f -- f Push the logical opposite of f

View File

@ -5,12 +5,3 @@ LIT -- Write a LIT entry. You're expected to write
LIT< x -- Read following word and write to HERE as a LIT< x -- Read following word and write to HERE as a
string literal. string literal.
S= a1 a2 -- f Returns whether string a1 == a2. S= a1 a2 -- f Returns whether string a1 == a2.

View File

@ -7,10 +7,3 @@ BS CR LF SPC CRLF
NL is an indirect word (see B80) that aliases to CRLF by NL is an indirect word (see B80) that aliases to CRLF by
default and that should generally be used when we want to emit default and that should generally be used when we want to emit
a newline. a newline.

View File

@ -5,6 +5,7 @@ BLK( -- a Beginning addr of blk buf.
BLK) -- a Ending addr of blk buf. BLK) -- a Ending addr of blk buf.
COPY s d -- Copy contents of s block to d block. COPY s d -- Copy contents of s block to d block.
FLUSH -- Write current block to disk if dirty. FLUSH -- Write current block to disk if dirty.
FREEBLKS? a b -- List free blocks between blocks a and b.
LIST n -- Prints the contents of the block n on screen LIST n -- Prints the contents of the block n on screen
in the form of 16 lines of 64 columns. in the form of 16 lines of 64 columns.
LOAD n -- Interprets Forth code from block n LOAD n -- Interprets Forth code from block n
@ -12,5 +13,4 @@ LOAD+ n -- Relative load. Loads active block + n.
LOADR n1 n2 -- Load block range between n1 and n2, inclusive. LOADR n1 n2 -- Load block range between n1 and n2, inclusive.
LOADR+ n1 n2 -- Relative ranged load. LOADR+ n1 n2 -- Relative ranged load.
WIPE -- Empties current block WIPE -- Empties current block
WIPED? -- f Whether current block is empty

10
blk/070
View File

@ -4,13 +4,3 @@ Implementation notes
75 Stack management 77 Dictionary 75 Stack management 77 Dictionary
80 System variables 85 Word types 80 System variables 85 Word types
89 Initialization sequence 89 Initialization sequence

View File

@ -9,8 +9,3 @@ it. As a general rule, we go like this:
4. Is it a number? 4. Is it a number?
5. If yes, push that number to PS, goto 1 5. If yes, push that number to PS, goto 1
6. Error: undefined word. 6. Error: undefined word.

10
blk/076
View File

@ -4,13 +4,3 @@ prohibitive in terms of costs), PS_ADDR should be set to
at least 6 bytes before its actual limit. 6 bytes because we at least 6 bytes before its actual limit. 6 bytes because we
seldom have words requiring more than 3 items from the stack. seldom have words requiring more than 3 items from the stack.
Then, at each "exit" call we check for stack underflow. Then, at each "exit" call we check for stack underflow.

View File

@ -10,7 +10,3 @@ chain). There are also "special words", for example NUMBER,
LIT, FBR, that have a slightly different structure. They're LIT, FBR, that have a slightly different structure. They're
also a pointer to an executable, but as for the other fields, also a pointer to an executable, but as for the other fields,
the only one they have is the "flags" field. the only one they have is the "flags" field.

View File

@ -12,5 +12,3 @@ BLK* see B416.
FUTURE USES section is unused for now. FUTURE USES section is unused for now.
DRIVERS section is reserved for recipe-specific drivers. DRIVERS section is reserved for recipe-specific drivers.

10
blk/086
View File

@ -4,13 +4,3 @@ 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 executes its reference exactly like a addr to PSP, it executes its reference exactly like a
compiled word. compiled word.

View File

@ -8,9 +8,3 @@
In RAM-only environment, we will typically have a In RAM-only environment, we will typically have a
"CURRENT @ HERE !" line during init to have HERE begin at the "CURRENT @ HERE !" line during init to have HERE begin at the
end of the binary instead of RAMEND. end of the binary instead of RAMEND.

View File

@ -10,7 +10,7 @@ P xxx: put typed IBUF on selected line.
U xxx: insert typed IBUF on selected line. U xxx: insert typed IBUF on selected line.
F xxx: find typed FBUF in block, starting from current F xxx: find typed FBUF in block, starting from current
position+1. If not found, don't move. position+1. If not found, don't move.
I xxx: insert typed IBUF at cursor. "I" shadows core word. Use i xxx: insert typed IBUF at cursor. "i" is to avoid shadowing
"i" to access it. core word "I".
Y: Copy n characters after cursor into IBUF, n being length of Y: Copy n characters after cursor into IBUF, n being length of
FBUF. (cont.) FBUF. (cont.)

14
blk/102
View File

@ -1,16 +1,2 @@
X ( n -- ): Delete X chars after cursor and place in IBUF. X ( n -- ): Delete X chars after cursor and place in IBUF.
E: Run X with n = length of FBUF. E: Run X with n = length of FBUF.

View File

@ -12,5 +12,3 @@
ENDCASE ENDCASE
AGAIN AGAIN
; ;

View File

@ -8,9 +8,3 @@ CREATE ACC 0 ,
: L BLK> @ _LIST ; : L BLK> @ _LIST ;
: B BLK> @ 1- BLK@ L ; : B BLK> @ 1- BLK@ L ;
: N BLK> @ 1+ BLK@ L ; : N BLK> @ 1+ BLK@ L ;

View File

@ -11,6 +11,3 @@ CREATE FBUF 64 ALLOT0
EMIT EMIT
LOOP ( lno ) 1+ . ; LOOP ( lno ) 1+ . ;
: _zbuf 64 0 FILL ; ( buf -- ) : _zbuf 64 0 FILL ; ( buf -- )

View File

@ -10,7 +10,3 @@
: _mvln- ( ln -- move ln 1 line up ) : _mvln- ( ln -- move ln 1 line up )
DUP 14 > IF DROP 15 _lpos _zbuf DUP 14 > IF DROP 15 _lpos _zbuf
ELSE 1+ _lpos DUP 64 - 64 MOVE THEN ; ELSE 1+ _lpos DUP 64 - 64 MOVE THEN ;

11
blk/109
View File

@ -3,14 +3,3 @@
14 I - _mvln+ 14 I - _mvln+
LOOP ; LOOP ;
: U _U P ; : U _U P ;

View File

@ -8,9 +8,3 @@
UNTIL ( a1 a2 ) UNTIL ( a1 a2 )
DUP BLK) < IF BLK( - FBUF + -^ EDPOS ! ELSE DROP THEN ; DUP BLK) < IF BLK( - FBUF + -^ EDPOS ! ELSE DROP THEN ;
: F FBUF _type _F EDPOS @ 64 / _pln ; : F FBUF _type _F EDPOS @ 64 / _pln ;

View File

@ -2,15 +2,11 @@
DUP BEGIN C@+ 0x20 < UNTIL -^ 1- ; DUP BEGIN C@+ 0x20 < UNTIL -^ 1- ;
: _rbufsz ( size of linebuf to the right of curpos ) : _rbufsz ( size of linebuf to the right of curpos )
EDPOS @ 64 MOD 63 -^ ; EDPOS @ 64 MOD 63 -^ ;
: i COMPILE I ; IMMEDIATE ( save overshadowed ) : _i ( i without _pln and _type. used in VE )
: _I ( I without _pln and _type. used in VE )
_rbufsz IBUF _blen 2DUP > IF _rbufsz IBUF _blen 2DUP > IF
TUCK - ( ilen chars-to-move ) TUCK - ( ilen chars-to-move )
SWAP EDPOS @ _cpos 2DUP + ( ctm ilen a a+ilen ) SWAP EDPOS @ _cpos 2DUP + ( ctm ilen a a+ilen )
3 PICK MOVE- ( ctm ilen ) NIP ( ilen ) 3 PICK MOVE- ( ctm ilen ) NIP ( ilen )
ELSE DROP 1+ ( ilen becomes rbuffsize+1 ) THEN ELSE DROP 1+ ( ilen becomes rbuffsize+1 ) THEN
DUP IBUF EDPOS @ _cpos ROT MOVE ( ilen ) EDPOS +! BLK!! ; DUP IBUF EDPOS @ _cpos ROT MOVE ( ilen ) EDPOS +! BLK!! ;
: I IBUF _type _I EDPOS @ 64 / _pln ; : i IBUF _type _i EDPOS @ 64 / _pln ;

View File

@ -5,12 +5,7 @@
SWAP _rbufsz MOVE ( n ) SWAP _rbufsz MOVE ( n )
( get to next line - n ) ( get to next line - n )
DUP EDPOS @ 0xffc0 AND 0x40 + -^ _cpos ( n a ) DUP EDPOS @ 0xffc0 AND 0x40 + -^ _cpos ( n a )
SWAP 0 FILL SWAP 0 FILL BLK!!
EDPOS @ 64 / _pln ; EDPOS @ 64 / _pln ;
: E FBUF _blen X ; : E FBUF _blen X ;
: Y FBUF _blen icpy ; : Y FBUF _blen icpy ;

View File

@ -13,4 +13,3 @@
'D' deletes "modifier" lines at the cursor. The first of those 'D' deletes "modifier" lines at the cursor. The first of those
lines is copied to IBUF. lines is copied to IBUF.
(cont.) (cont.)

View File

@ -8,9 +8,3 @@ be sure, then press 'E'.
'R' goes into replace mode at current cursor position. 'R' goes into replace mode at current cursor position.
Following keystrokes replace current character and advance Following keystrokes replace current character and advance
cursor. Press return to return to normal mode. cursor. Press return to return to normal mode.

13
blk/125
View File

@ -1,16 +1,3 @@
'? UPPER NOT [IF] 33 LOAD+ [THEN] DROP ( B158 ) '? UPPER NOT [IF] 33 LOAD+ [THEN] DROP ( B158 )
-20 LOAD+ ( B105, block editor ) -20 LOAD+ ( B105, block editor )
1 6 LOADR+ 1 6 LOADR+

View File

@ -4,13 +4,11 @@ CREATE PREVPOS 0 , CREATE PREVBLK 0 ,
: num ACC @ SWAP _pdacc IF DROP ELSE ACC ! THEN ; : num ACC @ SWAP _pdacc IF DROP ELSE ACC ! THEN ;
: nspcs ( n -- , spit n space ) 0 DO SPC LOOP ; : nspcs ( n -- , spit n space ) 0 DO SPC LOOP ;
: aty 0 SWAP AT-XY ; : aty 0 SWAP AT-XY ;
: clrscr LINES 0 DO i aty COLS nspcs LOOP ; : clrscr LINES 0 DO I aty COLS nspcs LOOP ;
: gutter ( ln n ) OVER + SWAP DO 67 i AT-XY '|' EMIT LOOP ; : gutter ( ln n ) OVER + SWAP DO 67 I AT-XY '|' EMIT LOOP ;
: status 0 aty ." BLK" SPC BLK> ? SPC ACC ? : status 0 aty ." BLK" SPC BLK> ? SPC ACC ?
SPC EDPOS @ 64 /MOD . ',' EMIT . SPC SPC EDPOS @ 64 /MOD . ',' EMIT . SPC
BLKDTY @ IF '*' EMIT THEN 10 nspcs ; BLKDTY @ IF '*' EMIT THEN 10 nspcs ;
: contents 3 aty BLK> @ LIST 3 16 gutter ; : contents 3 aty BLK> @ LIST 3 16 gutter ;
: selblk BLK> @ PREVBLK ! BLK@ contents ; : selblk BLK> @ PREVBLK ! BLK@ contents ;
: mode! ( c -- ) 63 0 AT-XY ; : mode! ( c -- ) 63 0 AT-XY ;

View File

@ -8,9 +8,3 @@
DUP 0x20 < IF 2DROP DROP EXIT THEN DUP 0x20 < IF 2DROP DROP EXIT THEN
( buf ln c ) 63 nspcs SWAP 4 SWAP AT-XY ( buf c ) SWAP C!+ ( buf ln c ) 63 nspcs SWAP 4 SWAP AT-XY ( buf c ) SWAP C!+
IN( _zbuf (rdln) IN( SWAP 63 MOVE ; IN( _zbuf (rdln) IN( SWAP 63 MOVE ;

View File

@ -2,7 +2,7 @@
: $[ BLK> @ acc@ - selblk ; : $[ BLK> @ acc@ - selblk ;
: $] BLK> @ acc@ + selblk ; : $] BLK> @ acc@ + selblk ;
: $t PREVBLK @ selblk ; : $t PREVBLK @ selblk ;
: $I mode! 'I' EMIT IBUF 1 buftype _I contents mode! SPC ; : $I mode! 'I' EMIT IBUF 1 buftype _i contents mode! SPC ;
: $F mode! 'F' EMIT FBUF 2 buftype _F setpos mode! SPC ; : $F mode! 'F' EMIT FBUF 2 buftype _F setpos mode! SPC ;
: $Y Y ; : $Y Y ;
: $E E contents ; : $E E contents ;
@ -10,7 +10,3 @@
: $h -1 cmv ; : $l 1 cmv ; : $k -64 cmv ; : $j 64 cmv ; : $h -1 cmv ; : $l 1 cmv ; : $k -64 cmv ; : $j 64 cmv ;
: $H EDPOS @ 0x3c0 AND pos! ; : $H EDPOS @ 0x3c0 AND pos! ;
: $L EDPOS @ 0x3f OR pos! ; : $L EDPOS @ 0x3f OR pos! ;

View File

@ -10,7 +10,3 @@
: $B EDPOS @ BLK( + acc@ 0 DO : $B EDPOS @ BLK( + acc@ 0 DO
BEGIN C@- WS? UNTIL BEGIN C@- WS? NOT UNTIL LOOP BEGIN C@- WS? UNTIL BEGIN C@- WS? NOT UNTIL LOOP
1+ BLK( - pos! ; 1+ BLK( - pos! ;

View File

@ -12,5 +12,5 @@
_U EDPOS @ 0x3c0 AND DUP pos! _cpos _zbuf BLK!! contents ; _U EDPOS @ 0x3c0 AND DUP pos! _cpos _zbuf BLK!! contents ;
: $o EDPOS @ 64 < IF EXIT THEN EDPOS @ 64 + EDPOS ! $O ; : $o EDPOS @ 64 < IF EXIT THEN EDPOS @ 64 + EDPOS ! $O ;
: $D $H 64 icpy : $D $H 64 icpy
acc@ 0 DO 16 EDPOS @ 64 / DO i _mvln- LOOP LOOP acc@ 0 DO 16 EDPOS @ 64 / DO I _mvln- LOOP LOOP
BLK!! contents ; BLK!! contents ;

View File

@ -3,7 +3,7 @@
DUP CMD 2+ C! CMD FIND IF EXECUTE ELSE DROP THEN DUP CMD 2+ C! CMD FIND IF EXECUTE ELSE DROP THEN
0 ACC ! UPPER 'Q' = ; 0 ACC ! UPPER 'Q' = ;
: bufp ( buf -- ) : bufp ( buf -- )
DUP 64 + SWAP DO i C@ 0x20 MAX EMIT LOOP ; DUP 64 + SWAP DO I C@ 0x20 MAX EMIT LOOP ;
: bufs : bufs
1 aty ." I: " IBUF bufp 1 aty ." I: " IBUF bufp
2 aty ." F: " FBUF bufp 0 3 gutter ; 2 aty ." F: " FBUF bufp 0 3 gutter ;
@ -11,6 +11,3 @@
clrscr 0 ACC ! 0 PREVPOS ! contents clrscr 0 ACC ! 0 PREVPOS ! contents
BEGIN status bufs setpos KEY handle UNTIL BEGIN status bufs setpos KEY handle UNTIL
19 aty (infl) ; 19 aty (infl) ;

View File

@ -13,4 +13,3 @@ Some programs need them, so they will automatically LOAD them.
Because more than one program can use the same extra words, Because more than one program can use the same extra words,
conditional loaders are recommended. If you want to load all conditional loaders are recommended. If you want to load all
words do "152 LOAD" which conditionally loads all extra words. words do "152 LOAD" which conditionally loads all extra words.

13
blk/152
View File

@ -1,16 +1,3 @@
'? CASE NOT [IF] 1 2 LOADR+ [THEN] DROP ( from '? ) '? CASE NOT [IF] 1 2 LOADR+ [THEN] DROP ( from '? )
'? FILL NOT [IF] 3 LOAD+ [THEN] DROP '? FILL NOT [IF] 3 LOAD+ [THEN] DROP
'? WIPE NOT [IF] 5 LOAD+ [THEN] DROP '? WIPE NOT [IF] 5 LOAD+ [THEN] DROP

View File

@ -7,10 +7,3 @@
[COMPILE] IF COMPILE DROP [COMPILE] IF COMPILE DROP
; IMMEDIATE ; IMMEDIATE
: ENDOF [COMPILE] ELSE ; IMMEDIATE : ENDOF [COMPILE] ELSE ; IMMEDIATE

View File

@ -7,10 +7,3 @@
[COMPILE] THEN [COMPILE] THEN
AGAIN AGAIN
; IMMEDIATE ; IMMEDIATE

11
blk/155
View File

@ -3,14 +3,3 @@
DUP I C! DUP I C!
LOOP DROP ; LOOP DROP ;
: ALLOT0 ( n -- ) H@ OVER 0 FILL ALLOT ; : ALLOT0 ( n -- ) H@ OVER 0 FILL ALLOT ;

22
blk/157
View File

@ -1,16 +1,8 @@
: WIPE BLK( 1024 0 FILL BLK!! ; : WIPE BLK( 1024 0 FILL BLK!! ;
: WIPED? ( -- f )
( src dst -- ) 1 ( f ) BLK) BLK( DO
: COPY FLUSH SWAP BLK@ BLK> ! BLK! ; I C@ IF DROP 0 ( f ) LEAVE THEN LOOP ;
: COPY ( src dst -- )
FLUSH SWAP BLK@ BLK> ! BLK! ;
: FREEBLKS? ( b1 b2 -- )
1+ SWAP DO I BLK@ WIPED? IF I . SPC THEN LOOP ;

14
blk/158
View File

@ -1,16 +1,2 @@
: LOWER DUP 'A' 'Z' =><= IF 32 + THEN ; : LOWER DUP 'A' 'Z' =><= IF 32 + THEN ;
: UPPER DUP 'a' 'z' =><= IF 32 - THEN ; : UPPER DUP 'a' 'z' =><= IF 32 - THEN ;

View File

@ -11,6 +11,3 @@ Z80 Assembler
238 OP3ddnn 240 OP3nn 238 OP3ddnn 240 OP3nn
242 Specials 246 Flow 242 Specials 246 Flow
249 Macros 249 Macros

13
blk/206
View File

@ -1,16 +1,3 @@
On top of that, you have the very nice BREAK, instruction, On top of that, you have the very nice BREAK, instruction,
which must also be preceded by a JRxx, and will jump to the which must also be preceded by a JRxx, and will jump to the
PC following the next AGAIN, PC following the next AGAIN,

View File

@ -9,8 +9,3 @@ JR [, Z, NZ, C, NC]
DI EI EXDEHL EXX HALT DI EI EXDEHL EXX HALT
NOP RET RETI RETN SCF NOP RET RETI RETN SCF

15
blk/212
View File

@ -1,16 +1 @@
1 37 LOADR+ 1 37 LOADR+

View File

@ -6,11 +6,3 @@ VARIABLE L1 VARIABLE L2 VARIABLE L3 VARIABLE L4
: BC 0 ; : DE 1 ; : HL 2 ; : AF 3 ; : SP AF ; : BC 0 ; : DE 1 ; : HL 2 ; : AF 3 ; : SP AF ;
: CNZ 0 ; : CZ 1 ; : CNC 2 ; : CC 3 ; : CNZ 0 ; : CZ 1 ; : CNC 2 ; : CC 3 ;
: CPO 4 ; : CPE 5 ; : CP 6 ; : CM 7 ; : CPO 4 ; : CPE 5 ; : CP 6 ; : CM 7 ;

View File

@ -9,8 +9,3 @@
0x17 OP1 RLA, 0x07 OP1 RLCA, 0x17 OP1 RLA, 0x07 OP1 RLCA,
0x1f OP1 RRA, 0x0f OP1 RRCA, 0x1f OP1 RRA, 0x0f OP1 RRCA,
0x37 OP1 SCF, 0x37 OP1 SCF,

View File

@ -7,10 +7,3 @@
0x18 OP1 JR, 0x10 OP1 DJNZ, 0x18 OP1 JR, 0x10 OP1 DJNZ,
0x38 OP1 JRC, 0x30 OP1 JRNC, 0x38 OP1 JRC, 0x30 OP1 JRNC,
0x28 OP1 JRZ, 0x20 OP1 JRNZ, 0x28 OP1 JRZ, 0x20 OP1 JRNZ,

View File

@ -10,7 +10,3 @@
0x04 OP1r INCr, 0x05 OP1r DECr, 0x04 OP1r INCr, 0x05 OP1r DECr,
: INC(IXY+), INCr, A, ; : INC(IXY+), INCr, A, ;
: DEC(IXY+), DECr, A, ; : DEC(IXY+), DECr, A, ;

View File

@ -12,5 +12,3 @@
0xb0 OP1r0 ORr, 0x90 OP1r0 SUBr, 0xb0 OP1r0 ORr, 0x90 OP1r0 SUBr,
0x98 OP1r0 SBCr, 0xa8 OP1r0 XORr, 0x98 OP1r0 SBCr, 0xa8 OP1r0 XORr,
: CP(IXY+), CPr, A, ; : CP(IXY+), CPr, A, ;

View File

@ -13,4 +13,3 @@
: ADDIXss, 0xdd A, ADDHLss, ; : ADDIXIX, HL ADDIXss, ; : ADDIXss, 0xdd A, ADDHLss, ; : ADDIXIX, HL ADDIXss, ;
: ADDIYss, 0xfd A, ADDHLss, ; : ADDIYIY, HL ADDIYss, ; : ADDIYss, 0xfd A, ADDHLss, ; : ADDIYIY, HL ADDIYss, ;

View File

@ -12,5 +12,3 @@
_1rr _1rr
; ;
0x40 OP1rr LDrr, 0x40 OP1rr LDrr,

View File

@ -11,6 +11,3 @@
SWAP ( ixy+- rd HL ) SWAP ( ixy+- rd HL )
LDIXYr, LDIXYr,
; ;

View File

@ -7,10 +7,3 @@
0xeda8 OP2 LDD, 0xedb8 OP2 LDDR, 0xeda8 OP2 LDD, 0xedb8 OP2 LDDR,
0xed44 OP2 NEG, 0xed44 OP2 NEG,
0xed4d OP2 RETI, 0xed45 OP2 RETN, 0xed4d OP2 RETI, 0xed45 OP2 RETN,

View File

@ -12,5 +12,3 @@
0xd6 OP2n SUBn, 0xd6 OP2n SUBn,
0xee OP2n XORn, 0xee OP2n XORn,
0xfe OP2n CPn, 0xfe OP2n CPn,

View File

@ -8,9 +8,3 @@
OR A, A, OR A, A,
; ;
0x06 OP2rn LDrn, 0x06 OP2rn LDrn,

View File

@ -11,6 +11,3 @@
0xc0 OP2br SETbr, 0xc0 OP2br SETbr,
0x80 OP2br RESbr, 0x80 OP2br RESbr,
0x40 OP2br BITbr, 0x40 OP2br BITbr,

View File

@ -13,4 +13,3 @@
0x08 OProt RRCr, 0x08 OProt RRCr,
0x20 OProt SLAr, 0x20 OProt SLAr,
0x38 OProt SRLr, 0x38 OProt SRLr,

View File

@ -11,6 +11,3 @@
; ;
0xed41 OP2r OUT(C)r, 0xed41 OP2r OUT(C)r,
0xed40 OP2r INr(C), 0xed40 OP2r INr(C),

View File

@ -9,8 +9,3 @@
; ;
0x4a OP2ss ADCHLss, 0x4a OP2ss ADCHLss,
0x42 OP2ss SBCHLss, 0x42 OP2ss SBCHLss,

View File

@ -9,8 +9,3 @@
A,, A,,
; ;
0x01 OP3ddnn LDddnn, 0x01 OP3ddnn LDddnn,

View File

@ -9,8 +9,3 @@
0xc3 OP3nn JPnn, 0xc3 OP3nn JPnn,
0x22 OP3nn LD(nn)HL, 0x22 OP3nn LD(nn)HL,
0x2a OP3nn LDHL(nn), 0x2a OP3nn LDHL(nn),

View File

@ -12,5 +12,3 @@
: JP(IX), IX DROP JP(HL), ; : JP(IX), IX DROP JP(HL), ;
: JP(IY), IY DROP JP(HL), ; : JP(IY), IY DROP JP(HL), ;

View File

@ -10,5 +10,3 @@ CREATE lblnext 0x1a , ( stable ABI until set in B300 )
: CODE ( same as CREATE, but with native word ) : CODE ( same as CREATE, but with native word )
(entry) 0 C, ( 0 == native ) ; (entry) 0 C, ( 0 == native ) ;
: ;CODE JPNEXT, ; : ;CODE JPNEXT, ;

View File

@ -6,11 +6,3 @@
THEN ; THEN ;
: AGAIN, BREAK?, PC - 1- A, ; : AGAIN, BREAK?, PC - 1- A, ;
: BWR @ AGAIN, ; : BWR @ AGAIN, ;

View File

@ -10,7 +10,3 @@
: LDDE(HL), E (HL) LDrr, HL INCss, D (HL) LDrr, ; : LDDE(HL), E (HL) LDrr, HL INCss, D (HL) LDrr, ;
: OUTHL, DUP A H LDrr, OUTnA, A L LDrr, OUTnA, ; : OUTHL, DUP A H LDrr, OUTnA, A L LDrr, OUTnA, ;
: OUTDE, DUP A D LDrr, OUTnA, A E LDrr, OUTnA, ; : OUTDE, DUP A D LDrr, OUTnA, A E LDrr, OUTnA, ;

View File

@ -7,10 +7,3 @@ See example in /emul/xcomp.fs
Why limit ourselves to icore? Oh, I've tried cross-compiling Why limit ourselves to icore? Oh, I've tried cross-compiling
the whole shebang. I tried. And failed. Too dynamic. the whole shebang. I tried. And failed. Too dynamic.

15
blk/262
View File

@ -1,16 +1 @@
1 LOAD+ 3 LOAD+ 6 LOAD+ 1 LOAD+ 3 LOAD+ 6 LOAD+

View File

@ -13,4 +13,3 @@ VARIABLE XCURRENT
XCON ' _xapply LITN XCON ' _xapply LITN
LIT< , FIND DROP _xapply , XCOFF ; LIT< , FIND DROP _xapply , XCOFF ;
: X[COMPILE] XCON ' _xapply , XCOFF ; : X[COMPILE] XCON ' _xapply , XCOFF ;

View File

@ -12,5 +12,3 @@ never supposed to encounter an immediate at this point.
If not found, we try the same word on system dict (RAM+02). If not found, we try the same word on system dict (RAM+02).
If found and is immediate, execute. If found and not immediate, If found and is immediate, execute. If found and not immediate,
error. If not found, try number. error. If not found, try number.

View File

@ -12,5 +12,3 @@
THEN THEN
AGAIN AGAIN
; ;

View File

@ -8,9 +8,3 @@
: : [ ' X: , ] ; : : [ ' X: , ] ;
CURRENT @ XCURRENT ! CURRENT @ XCURRENT !

View File

@ -10,7 +10,3 @@ up until 0x67, the (?br) wordref, pretty much everything has
to stay put. to stay put.
To assemble, run "282 LOAD". To assemble, run "282 LOAD".

10
blk/282
View File

@ -1,13 +1,3 @@
VARIABLE lblofl VARIABLE lblpushRS VARIABLE lblexec VARIABLE lblofl VARIABLE lblpushRS VARIABLE lblexec
VARIABLE lblfind VARIABLE lblfind
1 53 LOADR+ 1 53 LOADR+

View File

@ -13,4 +13,3 @@ CODE (loop) ( 0x80 )
A 1 IX+ LDrIXY, 1 IX- CP(IXY+), JRNZ, L2 BWR ( branch ) A 1 IX+ LDrIXY, 1 IX- CP(IXY+), JRNZ, L2 BWR ( branch )
( don't branch ) ( don't branch )
IX DECss, IX DECss, IX DECss, IX DECss, JR, L1 BWR IX DECss, IX DECss, IX DECss, IX DECss, JR, L1 BWR

View File

@ -10,7 +10,3 @@ CODE 2R>
20 BCALL, ( 20 == popRS ) EXDEHL, 20 BCALL, 20 BCALL, ( 20 == popRS ) EXDEHL, 20 BCALL,
HL PUSHqq, DE PUSHqq, HL PUSHqq, DE PUSHqq,
;CODE ;CODE

View File

@ -13,4 +13,3 @@ lblfind BSET
C A LDrr, B 0 LDrn, ( C holds our length ) C A LDrr, B 0 LDrn, ( C holds our length )
BC ADDHLss, HL INCss, ( HL points to after-last-char ) BC ADDHLss, HL INCss, ( HL points to after-last-char )
( cont . ) ( cont . )

View File

@ -6,11 +6,3 @@
LDA(DE), LDA(DE),
0x7f ANDn, ( remove IMMEDIATE flag ) 0x7f ANDn, ( remove IMMEDIATE flag )
C CPr, ( cont. ) C CPr, ( cont. )

View File

@ -13,4 +13,3 @@
DJNZ, AGAIN, DJNZ, AGAIN,
THEN, THEN,
( cont. ) ( cont. )

10
blk/296
View File

@ -4,13 +4,3 @@
L2 FSET ( end ) L2 FSET ( end )
HL POPqq, HL POPqq,
RET, RET,

View File

@ -11,6 +11,3 @@ PC ORG @ 0x15 + ! ( popRS )
IX DECss, IX DECss,
IX DECss, IX DECss,
RET, RET,

10
blk/298
View File

@ -1,13 +1,3 @@
lblofl BSET ( abortUnderflow ) lblofl BSET ( abortUnderflow )
DE BIN( @ 0x06 ( uflw ) + LDdd(nn), DE BIN( @ 0x06 ( uflw ) + LDdd(nn),
JR, L2 FWR ( execute, B301 ) JR, L2 FWR ( execute, B301 )

View File

@ -11,4 +11,3 @@
HL INCss, HL INCss,
D (HL) LDrr, D (HL) LDrr,
( continue to compiledWord ) ( continue to compiledWord )

View File

@ -10,6 +10,3 @@
HL INCss, HL INCss,
HL PUSHqq, IY POPqq, ( --> IP ) HL PUSHqq, IY POPqq, ( --> IP )
JR, lblexec BWR ( execute-B301 ) JR, lblexec BWR ( execute-B301 )

Some files were not shown because too many files have changed in this diff Show More