VE: add 't'

This is the first commit I do entirely in VE. It's a habit I'm planning
on taking as it helps a lot to find usability issues.
This commit is contained in:
Virgil Dupras 2020-06-11 18:12:01 -04:00
parent e83d5073ba
commit f6ded7712e
234 changed files with 1232 additions and 6 deletions

View File

@ -13,3 +13,4 @@ MASTER INDEX

14
blk/004
View File

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

View File

@ -10,3 +10,7 @@ binary (example "0b1010"), char literals are single characters
surrounded by ' (example 'X'). Char literals can't be used for
whitespaces.

View File

@ -12,3 +12,5 @@ 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,3 +4,13 @@ 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

@ -6,3 +6,11 @@ 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,3 +11,6 @@ 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,3 +4,13 @@ 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,3 +9,8 @@ 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

@ -13,3 +13,4 @@ to be used directly, but as part of another word.

11
blk/044
View File

@ -3,3 +3,14 @@ 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

View File

@ -6,3 +6,11 @@ ROLL Rotate PSP over n items. "1 ROLL" = SWAP,
"2 ROLL" = ROT. 0 is noop.

View File

@ -8,3 +8,9 @@ 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

@ -10,3 +10,7 @@ S= a1 a2 -- f Returns whether string a1 == a2.

10
blk/076
View File

@ -4,3 +4,13 @@ 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

@ -13,3 +13,4 @@ FUTURE USES section is unused for now.
DRIVERS section is reserved for recipe-specific drivers.

View File

@ -8,3 +8,9 @@
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,2 +1,16 @@
X ( n -- ): Delete X chars after cursor and place in IBUF.
E: Run X with n = length of FBUF.

View File

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

View File

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

View File

@ -10,3 +10,7 @@
: _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,3 +3,14 @@
14 I - _mvln+
LOOP ;
: U _U P ;

View File

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

View File

@ -11,3 +11,6 @@
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

@ -9,3 +9,8 @@
EDPOS @ 64 / _pln ;
: E FBUF _blen X ;
: Y FBUF _blen icpy ;

View File

@ -11,6 +11,6 @@ effect.
block. Any change made to the previously selected block is
saved beforehand.
'[' and ']' advances the selected block by "modifier".
'[' and ']' advances the selected block by "modifier". 't' opens
the previously opened block.
(cont.)

View File

@ -8,3 +8,9 @@ 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,3 +1,16 @@
'? UPPER NOT [IF] 33 LOAD+ [THEN] DROP ( B158 )
-20 LOAD+ ( B105, block editor )
1 6 LOADR+

View File

@ -1,5 +1,5 @@
CREATE CMD 2 C, '$' C, 0 C,
VARIABLE PREVPOS
CREATE PREVPOS 0 , CREATE PREVBLK 0 ,
: acc@ ACC @ 1 MAX ;
: num ACC @ SWAP _pdacc IF DROP ELSE ACC ! THEN ;
: nspcs ( n -- , spit n space ) 0 DO SPC LOOP ;
@ -9,5 +9,8 @@ VARIABLE PREVPOS
: status 0 aty ." BLK" SPC BLK> ? SPC ACC ?
SPC EDPOS @ 64 /MOD . ',' EMIT . 10 nspcs ;
: contents 3 aty BLK> @ LIST 3 16 gutter ;
: selblk BLK@ contents ;
: selblk BLK> @ PREVBLK ! BLK@ contents ;
: mode! ( c -- ) 63 0 AT-XY ;

View File

@ -8,3 +8,9 @@
( buf ln c ) 63 nspcs SWAP 4 SWAP AT-XY ( buf c )
SWAP DUP _zbuf C!+ DUP 63 + SWAP DO
C< DUP 0x0d = IF LEAVE THEN i C! LOOP ;

View File

@ -1,6 +1,7 @@
: $g ACC @ selblk ;
: $[ BLK> @ acc@ - selblk ;
: $] BLK> @ acc@ + selblk ;
: $t PREVBLK @ selblk ;
: $I mode! 'I' EMIT IBUF 1 buftype _I contents mode! SPC ;
: $F mode! 'F' EMIT FBUF 2 buftype _F setpos mode! SPC ;
: $Y Y ;
@ -10,3 +11,6 @@
: $H EDPOS @ 0x3c0 AND pos! ;
: $L EDPOS @ 0x3f OR pos! ;

View File

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

View File

@ -13,3 +13,4 @@
: $D $H 64 icpy
acc@ 0 DO 16 EDPOS @ 64 / DO i _mvln- LOOP LOOP
BLK!! contents ;

View File

@ -12,3 +12,5 @@
clrscr 0 ACC ! 0 PREVPOS ! contents
BEGIN status bufs setpos KEY handle UNTIL
0 0x08 RAM+ ! 19 aty ;

View File

@ -13,3 +13,4 @@ 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.

12
blk/152
View File

@ -2,3 +2,15 @@
'? FILL NOT [IF] 3 LOAD+ [THEN] DROP
'? EMPTY NOT [IF] 4 LOAD+ [THEN] DROP
'? WIPE NOT [IF] 5 LOAD+ [THEN] DROP

View File

@ -9,3 +9,8 @@
: ENDOF [COMPILE] ELSE ; IMMEDIATE

View File

@ -9,3 +9,8 @@
; IMMEDIATE

11
blk/155
View File

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

12
blk/156
View File

@ -2,3 +2,15 @@
LIT< _sys FIND NOT IF ABORT THEN
DUP HERE ! CURRENT ! ;

11
blk/157
View File

@ -3,3 +3,14 @@
( src dst -- )
: COPY SWAP BLK@ BLK> ! BLK! ;

14
blk/158
View File

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

View File

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

13
blk/206
View File

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

View File

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

15
blk/212
View File

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

View File

@ -6,3 +6,11 @@ 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

@ -10,3 +10,7 @@
0x1f OP1 RRA, 0x0f OP1 RRCA,
0x37 OP1 SCF,

View File

@ -9,3 +9,8 @@
0x28 OP1 JRZ, 0x20 OP1 JRNZ,

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -13,3 +13,4 @@
0xee OP2n XORn,
0xfe OP2n CPn,

View File

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

View File

@ -12,3 +12,5 @@
0x80 OP2br RESbr,
0x40 OP2br BITbr,

View File

@ -12,3 +12,5 @@
0xed41 OP2r OUT(C)r,
0xed40 OP2r INr(C),

View File

@ -10,3 +10,7 @@
0x4a OP2ss ADCHLss,
0x42 OP2ss SBCHLss,

View File

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

View File

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

View File

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

View File

@ -13,3 +13,4 @@
;
: ;CODE JPNEXT, ;

View File

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

View File

@ -10,3 +10,7 @@
: 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,3 +7,10 @@ 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 +1,16 @@
1 LOAD+ 3 LOAD+ 6 LOAD+

View File

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

View File

@ -12,3 +12,5 @@ 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 founf and not immediate,
error. If not found, try number.

View File

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

View File

@ -9,3 +9,8 @@
CURRENT @ XCURRENT !

View File

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

15
blk/282
View File

@ -1 +1,16 @@
1 53 LOADR+

View File

@ -13,3 +13,4 @@ NOP, NOP, ( 24, addrWord ) NOP, NOP, ( 26, unused )
0 JPnn, ( RST 30 )
0 JPnn, ( 33, execute ) NOP, NOP, ( unused )
0 JPnn, ( RST 38 )

View File

@ -13,3 +13,4 @@ CODE (loop) ( 0x77 )
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

@ -12,3 +12,5 @@ PC ORG @ 0x24 + ! ( addrWord )
IY INCss,
DE PUSHqq,
JPNEXT,

View File

@ -8,3 +8,9 @@ PC ORG @ 0x22 + ! ( litWord, 0xf7, tight on the 0x100 limit )
DE ADDIYss,
HL PUSHqq,
JPNEXT,

View File

@ -13,3 +13,4 @@ PC ORG @ 1 + ! ( main )
Forth. )
BIN( @ 0x08 + LDHL(nn),
RAMSTART 0x02 + LD(nn)HL, ( RAM+02 == CURRENT cont. )

12
blk/290
View File

@ -2,3 +2,15 @@
HL L1 @ LDddnn,
0x03 BCALL, ( 03 == find )
0x33 BJP, ( 33 == execute )

View File

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

View File

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

View File

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

10
blk/296
View File

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

View File

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

View File

@ -5,3 +5,12 @@ L2 BSET ( abortUnderflow )
0x03 BCALL, ( find )
0x33 BJP, ( 33 == execute )

View File

@ -11,3 +11,6 @@ PC ORG @ 0x1e + ! ( chkPS )
CNC RETcc, ( PS_ADDR >= SP? good )
JR, L2 BWR ( abortUnderflow-B298 )

View File

@ -13,3 +13,4 @@ L3 BSET PC ORG @ 0x34 + ! ( execute )
( DE points to PFA )
JP(HL),

View File

@ -10,3 +10,7 @@ L1 BSET PC ORG @ 0x0f + ! ( compiledWord )
HL INCss,
HL PUSHqq, IY POPqq, ( --> IP )
JR, L3 BWR ( execute-B301 )

11
blk/303
View File

@ -3,3 +3,14 @@ PC ORG @ 0x0c + ! ( cellWord )
DE PUSHqq,
JPNEXT,

View File

@ -7,3 +7,10 @@ CODE EXECUTE
DE POPqq,
chkPS,
JR, L3 BWR ( execute-B301 )

View File

@ -9,3 +9,8 @@ CODE ROT
BC PUSHqq, ( A )
;CODE

View File

@ -8,3 +8,9 @@ CODE SWAP
;CODE

View File

@ -9,3 +9,8 @@ CODE OVER
;CODE

View File

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

View File

@ -13,3 +13,4 @@ CODE (roll)
HL DECss,
LDDR,
;CODE

View File

@ -12,3 +12,5 @@ CODE 2DUP
DE PUSHqq, HL PUSHqq,
;CODE

View File

@ -9,3 +9,8 @@ CODE 'S
HL PUSHqq,
;CODE

View File

@ -12,3 +12,5 @@ CODE AND
;CODE

View File

@ -10,3 +10,7 @@ CODE OR
H A LDrr,
HL PUSHqq,
;CODE

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