blkunpack: don't include trailing empty lines

This was becoming heavy to manage.
This commit is contained in:
Virgil Dupras 2020-06-23 06:52:34 -04:00
parent 49d7a7f435
commit 2d9a07d215
252 changed files with 8 additions and 1331 deletions

View File

@ -11,6 +11,3 @@ MASTER INDEX
620 Sega Master System Recipe
650 AVR assembler 730 8086 assembler
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
23 Branching

View File

@ -9,8 +9,3 @@ are hexadecimals (example "0x12ef"), "0b" prefixes indicate
binary (example "0b1010"), char literals are single characters
surrounded by ' (example 'X'). Char literals can't be used for
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
;" if bar is not an immediate. However, ": foo COMPILE bar ;"
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
word can also be overriden, mostly as a companion to the
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.
To compare whether something is negative, use the "0<" word
which is the equivalent to "0x7fff >".

View File

@ -13,4 +13,3 @@ At compile time, colon definition stops processing words when
reaching the 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.
When you span Collapse OS over multiple disks, don't forget to
adjust those absolute LOADs.

View File

@ -11,6 +11,3 @@ try to strive towards a few goals:
4. B200-B500 are for bootstrapping
5. The rest is for recipes.
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
C@ and C*. There is also a AMOVE word that is the same as MOVE
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
simplified. So here's one more constraint for you to help you
towards simplicity.

View File

@ -10,7 +10,3 @@ and Extra words (B150).
52 Addressed devices 54 Arithmetic / Bits
56 Logic 58 Strings
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.
"*I*" in description indicates an IMMEDIATE word.

13
blk/035
View File

@ -1,16 +1,3 @@
(cont.)
~ - Container for native code. Usually not an executable word.
? - 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.
PREV a -- a Return a wordref's previous entry.
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.
LEAVE -- In a DO..LOOP, exit at the next LOOP call.
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.
ROLL Rotate PSP over n items. "1 ROLL" = SWAP,
"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 second 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
with a1+u, going down.
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
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
MAX a b -- n Returns the highest of a and b
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
string literal.
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
default and that should generally be used when we want to emit
a newline.

10
blk/070
View File

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

View File

@ -9,8 +9,3 @@ it. As a general rule, we go like this:
4. Is it a number?
5. If yes, push that number to PS, goto 1
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
seldom have words requiring more than 3 items from the stack.
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
also a pointer to an executable, but as for the other fields,
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.
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
addr to PSP, it executes its reference exactly like a
compiled word.

View File

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

14
blk/102
View File

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

View File

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

View File

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

View File

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

View File

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

11
blk/109
View File

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

View File

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

View File

@ -11,6 +11,3 @@
ELSE DROP 1+ ( ilen becomes rbuffsize+1 ) THEN
DUP IBUF EDPOS @ _cpos ROT MOVE ( ilen ) EDPOS +! BLK!! ;
: I IBUF _type _I EDPOS @ 64 / _pln ;

View File

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

View File

@ -8,9 +8,3 @@ be sure, then press 'E'.
'R' goes into replace mode at current cursor position.
Following keystrokes replace current character and advance
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 )
-20 LOAD+ ( B105, block editor )
1 6 LOADR+

View File

@ -12,5 +12,3 @@ CREATE PREVPOS 0 , CREATE PREVBLK 0 ,
: contents 3 aty BLK> @ LIST 3 16 gutter ;
: selblk BLK> @ PREVBLK ! BLK@ contents ;
: mode! ( c -- ) 63 0 AT-XY ;

View File

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

View File

@ -10,7 +10,3 @@
: $h -1 cmv ; : $l 1 cmv ; : $k -64 cmv ; : $j 64 cmv ;
: $H EDPOS @ 0x3c0 AND pos! ;
: $L EDPOS @ 0x3f OR pos! ;

View File

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

View File

@ -11,6 +11,3 @@
clrscr 0 ACC ! 0 PREVPOS ! contents
BEGIN status bufs setpos KEY handle UNTIL
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,
conditional loaders are recommended. If you want to load all
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 '? )
'? FILL NOT [IF] 3 LOAD+ [THEN] DROP
'? WIPE NOT [IF] 5 LOAD+ [THEN] DROP

View File

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

View File

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

11
blk/155
View File

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

14
blk/158
View File

@ -1,16 +1,2 @@
: LOWER 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
242 Specials 246 Flow
249 Macros

13
blk/206
View File

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

View File

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

15
blk/212
View File

@ -1,16 +1 @@
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 ;
: CNZ 0 ; : CZ 1 ; : CNC 2 ; : CC 3 ;
: CPO 4 ; : CPE 5 ; : CP 6 ; : CM 7 ;

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -12,5 +12,3 @@
: JP(IX), IX 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 )
(entry) 0 C, ( 0 == native ) ;
: ;CODE JPNEXT, ;

View File

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

View File

@ -10,7 +10,3 @@
: LDDE(HL), E (HL) LDrr, HL INCss, D (HL) LDrr, ;
: OUTHL, DUP A H LDrr, OUTnA, A L 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
the whole shebang. I tried. And failed. Too dynamic.

15
blk/262
View File

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

View File

@ -13,4 +13,3 @@ VARIABLE XCURRENT
XCON ' _xapply LITN
LIT< , FIND DROP _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 found and is immediate, execute. If found and not immediate,
error. If not found, try number.

View File

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

View File

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

View File

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

10
blk/282
View File

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

View File

@ -13,4 +13,3 @@ CODE (loop) ( 0x80 )
A 1 IX+ LDrIXY, 1 IX- CP(IXY+), JRNZ, L2 BWR ( branch )
( don't branch )
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,
HL PUSHqq, DE PUSHqq,
;CODE

View File

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

View File

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

View File

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

10
blk/296
View File

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

View File

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

10
blk/298
View File

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

View File

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

View File

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

View File

@ -10,7 +10,3 @@ lblchkPS BSET ( chkPS )
EXX,
CNC RETcc, ( PS_ADDR >= SP? good )
JR, lblofl BWR ( abortUnderflow-B298 )

View File

@ -13,4 +13,3 @@ CODE ROT
chkPS,
DE PUSHqq, ( B ) HL PUSHqq, ( C ) BC PUSHqq, ( A )
;CODE

View File

@ -6,11 +6,3 @@ CODE SWAP
HL PUSHqq, ( B )
DE PUSHqq, ( A )
;CODE

View File

@ -7,10 +7,3 @@ CODE OVER
HL PUSHqq, ( B )
DE PUSHqq, ( A )
;CODE

View File

@ -13,4 +13,3 @@ CODE PICK
CC lblofl @ JPccnn, ( abortUnderflow-B298 )
BC PUSHqq,
;CODE

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