\ The Rest is Silence 03Apr84map************************************************************* ************************************************************* *** *** *** Please direct all questions, comments, and *** *** miscellaneous personal abuse to: *** *** *** *** Henry Laxen or Michael Perry *** *** 1259 Cornell Avenue 1125 Bancroft Way *** *** Berkeley, California Berkeley, California *** *** 94706 94702 *** *** *** ************************************************************* ************************************************************* \ Target System Setup 19Apr84mapONLY FORTH META ALSO FORTH HEX A800 ' TARGET-ORIGIN >BODY ! IN-META DECIMAL 2 92 THRU ( System Source Screens ) HEX CR .( Unresolved references: ) CR .UNRESOLVED CR .( Statistics: ) CR .( Last Host Address: ) [FORTH] HERE U. CR .( First Target Code Address: ) META 500 THERE U. CR .( Last Target Code Address: ) META HERE-T THERE U. CR CR DOS HERE-T 4E8 !-T META 500 1C - THERE HERE-T 100 + ONLY FORTH ALSO DOS SAVE A:KERNEL.68K FORTH CR .( Now return to CP/M and type: ) CR .( KERNEL EXTEND68.BLK ) CR .( OK ) DECIMAL \ Declare the Forward References and Version # 29Oct83map: ]] ] ; : [[ [COMPILE] [ ; FORTH IMMEDIATE META FORWARD: DEFINITIONS FORWARD: [ LABEL FILE-HEADER HEX 500 1C - DP-T ! 601A ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 0 ,-T 500 ,-T -1 ,-T DECIMAL \ Boot up Vectors and NEXT Interpreter 10Apr84mapASSEMBLER LABEL ORIGIN -1 #) JMP ( Low Level COLD Entry point ) -1 #) JMP ( Low Level WARM Entry point ) LABEL >NEXT IP )+ D7 MOVE D7 W LMOVE W )+ D7 MOVE D7 A0 LMOVE A0 ) JMP ASSEMBLER >NEXT META CONSTANT >NEXT ASSEMBLER DEFINITIONS META H: NEXT META ASSEMBLER >NEXT #) JMP ; IN-META HERE-T DUP 100 + CURRENT-T ! ( harmless ) VOCABULARY FORTH FORTH DEFINITIONS 0 OVER 2+ !-T ( link ) DUP 2+ SWAP 16 + !-T ( thread ) IN-META \ Run Time Code for Defining Words 07Mar84mapASSEMBLER LABEL NEST IP RP -) MOVE W IP LMOVE NEXT CODE EXIT (S -- ) RP )+ D7 MOVE D7 IP LMOVE NEXT END-CODE CODE UNNEST ' EXIT @-T ' UNNEST !-T END-CODE ASSEMBLER LABEL DODOES IP RP -) MOVE A7 )+ IP LMOVE ( fall through to DOCREATE ) LABEL DOCREATE W SP -) MOVE NEXT \ Run Time Code for Defining Words 07Mar84mapVARIABLE UP LABEL DOCONSTANT W ) SP -) MOVE NEXT LABEL DOUSER-VARIABLE W ) D0 MOVE UP #) D0 ADD D0 SP -) MOVE NEXT CODE (LIT) (S -- n ) IP )+ SP -) MOVE NEXT END-CODE \ Meta Defining Words 21Dec83mapT: LITERAL (S n -- ) [TARGET] (LIT) ,-T T; T: DLITERAL (S d -- ) [TARGET] (LIT) ,-T [TARGET] (LIT) ,-T T; T: ASCII (S -- ) [COMPILE] ASCII [[ TRANSITION ]] LITERAL [META] T; T: ['] (S -- ) 'T >BODY @ [[ TRANSITION ]] LITERAL [META] T; : CONSTANT (S n -- ) RECREATE [[ ASSEMBLER DOCONSTANT ]] LITERAL ,-T DUP ,-T CONSTANT ; \ Identify numbers and forward References 08Jan84mapHEX FORWARD: <(;CODE)> T: DOES> (S -- ) [FORWARD] <(;CODE)> HERE-T 4EB8 ,-T [[ ASSEMBLER DODOES ]] LITERAL ,-T T; : NUMERIC (S -- ) [FORTH] HERE [META] NUMBER DPL @ 1+ IF [[ TRANSITION ]] DLITERAL [META] ELSE DROP [[ TRANSITION ]] LITERAL [META] THEN ; : UNDEFINED (S -- ) HERE-T 0 ,-T IN-FORWARD [FORTH] CREATE [META] TRANSITION [FORTH] , FALSE , [META] DOES> FORWARD-CODE ; DECIMAL \ Meta Compiler Compiling Loop 21Dec83map[FORTH] VARIABLE T-IN META : ] (S -- ) STATE-T ON IN-TRANSITION BEGIN >IN @ T-IN ! DEFINED IF EXECUTE ELSE COUNT NUMERIC? IF NUMERIC ELSE T-IN @ >IN ! UNDEFINED THEN THEN STATE-T @ 0= UNTIL ; T: [ (S -- ) IN-META STATE-T OFF T; T: ; (S -- ) [TARGET] UNNEST [[ TRANSITION ]] [ T; : : (S -- ) TARGET-CREATE [[ ASSEMBLER NEST ]] LITERAL ,-T ] ; \ Run Time Code for Control Structures 07Mar84mapCODE BRANCH (S -- ) LABEL BRAN1 IP ) D7 MOVE D7 IP LMOVE NEXT END-CODE CODE ?BRANCH (S f -- ) SP )+ TST BRAN1 BEQ IP )+ TST NEXT END-CODE \ Meta Compiler Branching Words 01AUG83HHLT: BEGIN ?MARK T; T: THEN ?>RESOLVE T; T: ELSE [TARGET] BRANCH ?>MARK 2SWAP ?>RESOLVE T; T: WHILE [[ TRANSITION ]] IF T; T: REPEAT 2SWAP [[ TRANSITION ]] AGAIN THEN T; \ Run Time Code for Control Structures 07Mar84mapCODE (LOOP) (S -- ) 1 RP ) ADDQ BRAN1 BVC LONG RP )+ TST WORD RP )+ TST IP )+ TST NEXT END-CODE CODE (+LOOP) (S n -- ) SP )+ D0 MOVE D0 RP ) ADD BRAN1 BVC LONG RP )+ TST WORD RP )+ TST IP )+ TST NEXT END-CODE \ Run Time Code for Control Structures 07Mar84mapHEX CODE (DO) (S l i -- ) SP )+ D0 MOVE SP )+ D1 MOVE LABEL PDO IP )+ RP -) MOVE 8000 # D1 ADD D1 RP -) MOVE D1 D0 SUB D0 RP -) MOVE NEXT END-CODE CODE (?DO) (S l i -- ) SP )+ D0 MOVE SP )+ D1 MOVE D0 D1 CMP PDO BNE IP ) D7 MOVE D7 IP LMOVE NEXT END-CODE : BOUNDS (S adr len -- lim first ) OVER + SWAP ; DECIMAL \ Meta compiler Branching & Looping 28Oct83mapT: ?DO [TARGET] (?DO) ?>MARK T; T: DO [TARGET] (DO) ?>MARK T; T: LOOP [TARGET] (LOOP) OVER 2+ OVER ?RESOLVE T; T: +LOOP [TARGET] (+LOOP) OVER 2+ OVER ?RESOLVE T; \ Execution Control 28Apr84mapASSEMBLER >NEXT META CONSTANT >NEXT CODE EXECUTE (S cfa -- ) SP )+ D7 MOVE D7 W LMOVE W )+ D7 MOVE D7 A0 LMOVE A0 ) JMP END-CODE CODE PERFORM (S addr-of-cfa -- ) SP )+ D7 MOVE D7 W LMOVE W )+ D7 MOVE D7 W LMOVE W )+ D7 MOVE D7 A0 LMOVE A0 ) JMP END-CODE LABEL DODEFER (S -- ) ' PERFORM @-T 4 + #) JMP LABEL DOUSER-DEFER W ) D7 MOVE UP #) D7 ADD ' PERFORM @-T 2+ #) JMP CODE GO (S addr -- ) RTS END-CODE CODE NOOP NEXT END-CODE CODE PAUSE NEXT END-CODE \ Execution Control 07Mar84mapCODE I (S -- n ) RP ) D0 MOVE 2 RP D) D0 ADD D0 SP -) MOVE NEXT END-CODE CODE J (S -- n ) 6 RP D) D0 MOVE 8 RP D) D0 ADD D0 SP -) MOVE NEXT END-CODE CODE (LEAVE) (S -- ) LABEL PLEAVE LONG RP )+ TST WORD RP )+ D7 MOVE D7 IP LMOVE NEXT END-CODE CODE (?LEAVE) (S f -- ) SP )+ TST PLEAVE BNE NEXT END-CODE T: LEAVE [TARGET] (LEAVE) T; T: ?LEAVE [TARGET] (?LEAVE) T; \ 16 and 8 bit Memory Operations 07Mar84mapCODE @ (S addr -- n ) SP ) D7 MOVE D7 A0 LMOVE BYTE A0 )+ D0 MOVE WORD 8 # D0 LSL BYTE A0 ) D0 MOVE WORD D0 SP ) MOVE NEXT END-CODE CODE ! (S n addr -- ) SP )+ D7 MOVE D7 A0 LMOVE SP )+ D0 MOVE BYTE D0 1 A0 D) MOVE WORD 8 # D0 LSR BYTE D0 A0 ) MOVE NEXT END-CODE CODE C@ (S addr -- char ) SP ) D7 MOVE D7 A0 LMOVE D0 CLR BYTE A0 ) D0 MOVE WORD D0 SP ) MOVE NEXT END-CODE CODE C! (S char addr -- ) SP )+ D7 MOVE D7 A0 LMOVE SP )+ D0 MOVE BYTE D0 A0 ) MOVE NEXT END-CODE \ Block Move Memory Operations 07Mar84mapCODE CMOVE (S from to count -- ) SP )+ D0 MOVE 1 D0 ADDQ SP )+ D7 MOVE D7 A0 LMOVE SP )+ D7 MOVE D7 A1 LMOVE BEGIN 1 D0 SUBQ 0<> WHILE BYTE A1 )+ A0 )+ MOVE REPEAT NEXT END-CODE CODE CMOVE> (S from to count -- ) SP )+ D0 MOVE SP )+ D7 MOVE D0 D7 ADD D7 A0 LMOVE SP )+ D7 MOVE D0 D7 ADD D7 A1 LMOVE 1 D0 ADDQ BEGIN 1 D0 SUBQ 0<> WHILE BYTE A1 -) A0 -) MOVE REPEAT NEXT END-CODE \ 16 bit Stack Operations 07Mar84mapCODE SP@ (S -- n ) SP SP -) MOVE NEXT END-CODE CODE SP! (S n -- ) SP )+ D7 MOVE D7 SP LMOVE NEXT END-CODE CODE RP@ (S -- addr ) RP SP -) MOVE NEXT END-CODE CODE RP! (S n -- ) SP )+ D7 MOVE D7 RP LMOVE NEXT END-CODE \ 16 bit Stack Operations 07Mar84mapCODE DROP (S n1 -- ) SP )+ D0 MOVE NEXT END-CODE CODE DUP (S n1 -- n1 n1 ) SP ) SP -) MOVE NEXT END-CODE CODE SWAP (S n1 n2 -- n2 n1 ) LONG SP ) D0 MOVE D0 SWAP D0 SP ) MOVE NEXT END-CODE CODE OVER (S n1 n2 -- n1 n2 n1 ) 2 SP D) SP -) MOVE NEXT END-CODE \ 16 bit Stack Operations 07Mar84mapCODE TUCK (S n1 n2 -- n2 n1 n2 ) LONG SP ) D0 MOVE D0 SWAP D0 SP ) MOVE WORD D0 SP -) MOVE NEXT END-CODE CODE NIP (S n1 n2 -- n2 ) SP )+ SP ) MOVE NEXT END-CODE CODE ROT (S n1 n2 n3 --- n2 n3 n1 ) SP )+ D1 MOVE SP )+ D2 MOVE SP ) D0 MOVE D2 SP ) MOVE D1 SP -) MOVE D0 SP -) MOVE NEXT END-CODE CODE -ROT (S n1 n2 n3 --- n3 n1 n2 ) SP )+ D2 MOVE SP )+ D0 MOVE SP ) D1 MOVE D2 SP ) MOVE D1 SP -) MOVE D0 SP -) MOVE NEXT END-CODE CODE FLIP (S n1 -- n2 ) ( byte swap ) SP )+ D0 MOVE 8 # D0 ROL D0 SP -) MOVE NEXT END-CODE : ?DUP (S n -- [n] n ) DUP IF DUP THEN ; \ 16 bit Stack Operations 07Mar84mapCODE R> (S -- n ) RP )+ SP -) MOVE NEXT END-CODE CODE >R (S n -- ) SP )+ RP -) MOVE NEXT END-CODE CODE R@ RP ) SP -) MOVE NEXT END-CODE CODE PICK (S nm ... n2 n1 k -- nm ... n2 n1 nk ) LONG D0 CLR WORD SP )+ D0 MOVE D0 D0 ADD 0 D0 SP DI) SP -) MOVE NEXT END-CODE : ROLL (S n1 n2 .. nk n -- wierd ) >R R@ PICK SP@ DUP 2+ R> 1+ 2* CMOVE> DROP ; \ 16 bit Logical Operations 07Mar84mapCODE AND (S n1 n2 -- n3 ) SP )+ D0 MOVE D0 SP ) AND NEXT END-CODE CODE OR (S n1 n2 -- n3 ) SP )+ D0 MOVE D0 SP ) OR NEXT END-CODE CODE XOR (S n1 n2 -- n3 ) SP )+ D0 MOVE D0 SP ) EOR NEXT END-CODE CODE NOT (S n -- n' ) SP ) NOT NEXT END-CODE -1 CONSTANT TRUE 0 CONSTANT FALSE \ 16 bit Logical Operations 07Mar84mapCODE CSET (S b addr -- ) SP )+ D7 MOVE D7 A0 LMOVE SP )+ D0 MOVE BYTE D0 A0 ) OR NEXT END-CODE CODE CRESET (S b addr -- ) SP )+ D7 MOVE D7 A0 LMOVE SP )+ D0 MOVE D0 NOT BYTE D0 A0 ) AND NEXT END-CODE CODE CTOGGLE (S b addr -- ) SP )+ D7 MOVE D7 A0 LMOVE SP )+ D0 MOVE BYTE D0 A0 ) EOR NEXT END-CODE CODE ON (S addr -- ) SP )+ D7 MOVE D7 A0 LMOVE TRUE # A0 ) MOVE NEXT END-CODE CODE OFF (S addr -- ) SP )+ D7 MOVE D7 A0 LMOVE A0 ) CLR NEXT END-CODE \ 16 bit Arithmetic Operations 07Mar84mapCODE + (S n1 n2 -- sum ) SP )+ D0 MOVE D0 SP ) ADD NEXT END-CODE CODE NEGATE (S n -- n' ) SP ) NEG NEXT END-CODE CODE - (S n1 n2 -- n1-n2 ) SP )+ D0 MOVE D0 SP ) SUB NEXT END-CODE CODE ABS (S n -- n ) SP ) TST 0< IF SP ) NEG THEN NEXT END-CODE CODE +! (S n addr -- ) SP )+ D7 MOVE D7 A0 LMOVE BYTE A0 )+ D0 MOVE WORD 8 # D0 LSL BYTE A0 ) D0 MOVE WORD SP )+ D0 ADD D0 D1 MOVE 8 # D1 LSR BYTE D0 A0 ) MOVE D1 A0 -) MOVE NEXT END-CODE 0 CONSTANT 0 1 CONSTANT 1 2 CONSTANT 2 3 CONSTANT 3 \ 16 bit Arithmetic Operations 07Mar84mapCODE 2* (S n -- 2*n ) SP ) ASL NEXT END-CODE CODE 2/ (S n -- n/2 ) SP ) ASR NEXT END-CODE CODE U2/ (S u -- u/2 ) SP ) LSR NEXT END-CODE CODE 8* (S n -- 8*n ) SP )+ D0 MOVE 3 # D0 ASL D0 SP -) MOVE NEXT END-CODE CODE 1+ 1 SP ) ADDQ NEXT END-CODE CODE 2+ 2 SP ) ADDQ NEXT END-CODE CODE 1- 1 SP ) SUBQ NEXT END-CODE CODE 2- 2 SP ) SUBQ NEXT END-CODE \ 16 bit Arithmetic Operations Unsigned Multiply 03Apr84map CODE UM* (S n1 n2 -- d ) SP )+ D0 MOVE SP )+ D0 MULU LONG D0 SP -) MOVE NEXT END-CODE : U*D (S n1 n2 -- d ) UM* ; \ 16 bit Arithmetic Operations Unsigned Divide 07Mar84mapCODE UM/MOD (S d1 n1 -- Remainder Quotient ) SP )+ D0 MOVE LONG SP ) D1 MOVE D0 D1 DIVU D1 SWAP D1 SP ) MOVE NEXT END-CODE ASSEMBLER LABEL YES -1 # SP ) MOVE NEXT LABEL NO SP ) CLR NEXT \ 16 bit Comparison Operations 07Mar84mapCODE 0< (S n -- f ) SP ) TST YES BMI NO BRA END-CODE CODE 0= (S n -- f ) SP ) TST YES BEQ NO BRA END-CODE CODE 0> (S n -- f ) SP ) TST YES BGT NO BRA END-CODE CODE 0<> (S n -- f ) SP ) TST YES BNE NO BRA END-CODE CODE < (S n1 n2 -- f ) SP )+ D0 MOVE SP ) D0 CMP YES BGT NO BRA END-CODE CODE = (S n1 n2 -- f ) SP )+ D0 MOVE SP ) D0 CMP YES BEQ NO BRA END-CODE CODE > (S n1 n2 -- f ) SP )+ D0 MOVE SP ) D0 CMP YES BLT NO BRA END-CODE \ 16 bit Comparison Operations 07Mar84mapCODE U< (S n1 n2 -- f ) SP )+ D0 MOVE SP ) D0 CMP YES BHI NO BRA END-CODE CODE U> (S n1 n2 -- f ) SP )+ D0 MOVE SP ) D1 MOVE D0 D1 CMP YES BHI NO BRA END-CODE : <> (S n1 n2 -- f ) = NOT ; : ?NEGATE (S n1 n2 -- n3 ) 0< IF NEGATE THEN ; : MIN (S n1 n2 -- n3 ) 2DUP > IF SWAP THEN DROP ; : MAX (S n1 n2 -- n3 ) 2DUP < IF SWAP THEN DROP ; : BETWEEN (S n1 min max -- f ) >R OVER > SWAP R> > OR NOT ; : WITHIN (S n1 min max -- f ) 1- BETWEEN ; \ 32 bit Memory Operations 08Oct83map: 2@ (S addr -- d ) DUP 2+ @ SWAP @ ; : 2! (S d addr -- ) TUCK ! 2+ ! ; \ 32 bit Memory and Stack Operations 07Mar84mapCODE 2DROP (S a b -- ) SP )+ D0 LMOVE NEXT END-CODE CODE 2DUP (S a b -- a b a b ) SP ) SP -) LONG MOVE NEXT END-CODE CODE 2SWAP (S a b c d -- c d a b ) LONG SP )+ D0 MOVE SP ) D1 MOVE D0 SP ) MOVE D1 SP -) MOVE NEXT END-CODE CODE 2OVER (S a b c d -- a b c d a b ) 4 SP D) SP -) LONG MOVE NEXT END-CODE : 3DUP (S a b c -- a b c a b c ) DUP 2OVER ROT ; : 4DUP (S a b c d -- a b c d a b c d ) 2OVER 2OVER ; : 2ROT (S a b c d e f --- c d e f a b ) 5 ROLL 5 ROLL ; \ 32 bit Arithmetic Operations 07Mar84mapCODE D+ (S d1 d2 -- dsum ) LONG SP )+ D0 MOVE D0 SP ) ADD NEXT END-CODE CODE DNEGATE (S d# -- d#' ) LONG SP ) NEG NEXT END-CODE CODE S>D (S n -- d ) SP )+ A0 MOVE A0 SP -) LMOVE NEXT END-CODE CODE DABS (S d# -- d# ) SP ) TST 0< IF LONG SP ) NEG THEN NEXT END-CODE \ 32 bit Arithmetic Operations 07Mar84mapCODE D2* (S d -- d*2 ) LONG SP )+ D0 MOVE 1 # D0 ASL D0 SP -) MOVE NEXT END-CODE CODE D2/ (S d -- d/2 ) LONG SP )+ D0 MOVE 1 # D0 ASR D0 SP -) MOVE NEXT END-CODE : D- (S d1 d2 -- d3 ) DNEGATE D+ ; : ?DNEGATE (S d1 n -- d2 ) 0< IF DNEGATE THEN ; \ 32 bit Comparison Operations 05Oct83map: D0= (S d -- f ) OR 0= ; : D= (S d1 d2 -- f ) D- D0= ; : DU< (S ud1 ud2 -- f ) ROT SWAP 2DUP U< IF 2DROP 2DROP TRUE ELSE <> IF 2DROP FALSE ELSE U< THEN THEN ; : D< (S d1 d2 -- f ) 2 PICK OVER = IF DU< ELSE NIP ROT DROP < THEN ; : D> (S d1 d2 -- f ) 2SWAP D< ; : DMIN (S d1 d2 -- d3 ) 4DUP D> IF 2SWAP THEN 2DROP ; : DMAX (S d1 d2 -- d3 ) 4DUP D< IF 2SWAP THEN 2DROP ; \ Mixed Mode Arithmetic 01Oct83map: *D (S n1 n2 -- d# ) 2DUP XOR >R ABS SWAP ABS UM* R> ?DNEGATE ; : M/MOD (S d# n1 -- rem quot ) ?DUP IF DUP >R 2DUP XOR >R >R DABS R@ ABS UM/MOD SWAP R> ?NEGATE SWAP R> 0< IF NEGATE OVER IF 1- R@ ROT - SWAP THEN THEN R> DROP THEN ; : MU/MOD (S d# n1 -- rem d#quot ) >R 0 R@ UM/MOD R> SWAP >R UM/MOD R> ; \ 16 bit multiply and divide 27Sep83map: * (S n1 n2 -- n3 ) UM* DROP ; : /MOD (S n1 n2 -- rem quot ) >R S>D R> M/MOD ; : / (S n1 n2 -- quot ) /MOD NIP ; : MOD (S n1 n2 -- rem ) /MOD DROP ; : */MOD (S n1 n2 n3 -- rem quot ) >R *D R> M/MOD ; : */ (S n1 n2 n3 -- n1*n2/n3 ) */MOD NIP ; \ Task Dependant USER Variables 24Mar84mapUSER DEFINITIONS VARIABLE TOS ( TOP OF STACK ) VARIABLE ENTRY ( ENTRY POINT, CONTAINS MACHINE CODE ) VARIABLE LINK ( LINK TO NEXT TASK ) VARIABLE SP0 ( INITIAL PARAMETER STACK ) VARIABLE RP0 ( INITIAL RETURN STACK ) VARIABLE DP ( DICTIONARY POINTER ) VARIABLE #OUT ( NUMBER OF CHARACTERS EMITTED ) VARIABLE #LINE ( THE NUMBER OF LINES SENT SO FAR ) VARIABLE OFFSET ( RELATIVE TO ABSOLUTE DISK BLOCK 0 ) VARIABLE BASE ( FOR NUMERIC INPUT AND OUTPUT ) VARIABLE HLD ( POINTS TO LAST CHARACTER HELD IN PAD ) VARIABLE FILE ( POINTS TO FCB OF CURRENTLY OPEN FILE ) VARIABLE IN-FILE ( POINTS TO FCB OF CURRENTLY OPEN FILE ) VARIABLE PRINTING \ System VARIABLEs 24Mar84mapDEFER EMIT ( TO ALLOW PRINT SPOOLING ) META DEFINITIONS VARIABLE SCR ( SCREEN LAST LISTED OR EDITED ) VARIABLE PRIOR ( USED FOR DICTIONARY SEARCHES ) VARIABLE STATE ( COMPILATION OR INTERPRETATION ) VARIABLE WARNING ( GIVE USER DUPLICATE WARNINGS IF ON ) VARIABLE DPL ( NUMERIC INPUT PUNCTUATION ) VARIABLE R# ( EDITING CURSOR POSITION ) VARIABLE LAST ( POINTS TO NFA OF LATEST DEFINITION ) VARIABLE CSP ( HOLDS STACK POINTER FOR ERROR CHECKING ) VARIABLE CURRENT ( VOCABULARY WHICH GETS DEFINITIONS ) 8 CONSTANT #VOCS ( THE NUMBER OF VOCABULARIES TO SEARCH ) VARIABLE CONTEXT ( VOCABULARY SEARCHED FIRST ) HERE THERE #VOCS 2* DUP ALLOT ERASE \ System Variables 08Jan84mapVARIABLE 'TIB ( ADDRESS OF TERMINAL INPUT BUFFER ) VARIABLE WIDTH ( WIDTH OF NAME FIELD ) VARIABLE VOC-LINK ( POINTS TO NEWEST VOCABULARY ) VARIABLE BLK ( BLOCK NUMBER TO INTERPRET ) VARIABLE >IN ( OFFSET INTO INPUT STREAM ) VARIABLE SPAN ( NUMBER OF CHARACTERS EXPECTED ) VARIABLE #TIB ( NUMBER OF CHARACTERS TO INTERPRET ) VARIABLE END? ( TRUE IF INPUT STREAM EXHAUSTED ) \ Devices Strings 07Mar84map 32 CONSTANT BL 8 CONSTANT BS 7 CONSTANT BELL VARIABLE CAPS CODE FILL ( start-addr count char -- ) SP )+ D0 MOVE SP )+ D1 MOVE SP )+ D7 MOVE D7 A0 LMOVE 1 D1 SUBQ D1 DO BYTE D0 A0 )+ MOVE LOOP NEXT END-CODE : ERASE (S addr len -- ) 0 FILL ; : BLANK (S addr len -- ) BL FILL ; CODE COUNT (S addr -- addr+1 len ) SP )+ D7 MOVE D7 A0 LMOVE D0 CLR BYTE A0 )+ D0 MOVE WORD A0 SP -) MOVE D0 SP -) MOVE NEXT END-CODE CODE LENGTH (S addr -- addr+2 len ) SP )+ D7 MOVE D7 A0 LMOVE A0 )+ D0 MOVE A0 SP -) MOVE D0 SP -) MOVE NEXT END-CODE : MOVE ( from to len -- ) -ROT 2DUP U< IF ROT CMOVE> ELSE ROT CMOVE THEN ; \ Devices Strings 07Mar84mapCODE UPC (S char -- upper-case-char ) SP )+ D6 MOVE BYTE ASCII a D6 CMPI >= IF ASCII z D6 CMPI <= IF BL D6 SUBI THEN THEN WORD D6 SP -) MOVE NEXT END-CODE : UPPER (S addr len -- ) BOUNDS ?DO I DUP C@ UPC SWAP C! LOOP ; : HERE (S -- addr ) DP @ ; : PAD (S -- addr ) HERE 80 + ; : -TRAILING (S addr len -- addr len' ) DUP 0 ?DO 2DUP + 1- C@ BL <> ?LEAVE 1- LOOP ; \ Devices Strings 07Mar84mapCODE COMP (S addr1 addr2 len -- -1 | 0 | 1 ) SP )+ D0 MOVE 1 D0 ADDQ SP )+ D7 MOVE D7 A0 LMOVE SP )+ D7 MOVE D7 A1 LMOVE BEGIN 1 D0 SUBQ 0<> WHILE BYTE A1 )+ A0 )+ CMPM WORD 0<> IF 0< IF 1 # SP -) MOVE ELSE -1 # SP -) MOVE THEN NEXT THEN REPEAT SP -) CLR NEXT END-CODE \ Devices Strings 07Mar84mapLABEL >UPPER ( D6 --> D6 ) BYTE ASCII a D6 CMPI >= IF ASCII z D6 CMPI <= IF BL D6 SUBI THEN THEN RTS CODE CAPS-COMP (S addr1 addr2 len -- -1 | 0 | 1 ) SP )+ D0 MOVE 1 D0 ADDQ SP )+ D7 MOVE D7 A0 LMOVE SP )+ D7 MOVE D7 A1 LMOVE BEGIN 1 D0 SUBQ 0<> WHILE BYTE A1 )+ D6 MOVE >UPPER #) JSR D6 D1 MOVE A0 )+ D6 MOVE >UPPER #) JSR D1 D6 CMP WORD 0<> IF 0< IF 1 # SP -) MOVE ELSE -1 # SP -) MOVE THEN NEXT THEN REPEAT SP -) CLR NEXT END-CODE : COMPARE (S addr1 addr2 len -- -1 | 0 | 1 ) CAPS @ IF CAPS-COMP ELSE COMP THEN ; \ Devices Terminal IO via CP/M BIOS 13Apr84mapCREATE REG-BUF 64 ALLOT ( Save registers ) CODE BDOS (S n fun -- m ) SP )+ D0 MOVE SP )+ D7 MOVE D7 D1 LMOVE 2 TRAP D0 SP -) MOVE NEXT END-CODE CODE BIOS (S parm func# -- ret ) HEX SP )+ D0 MOVE SP )+ D1 MOVE LONG 7F00 REG-BUF #) MOVEM> WORD 3 TRAP D0 SP -) MOVE LONG 7F00 REG-BUF #) MOVEM< NEXT END-CODE DECIMAL : (KEY?) (S -- f ) 0 2 BIOS 0<> ; : (KEY) (S -- char ) BEGIN PAUSE (KEY?) UNTIL 0 3 BIOS ; : (CONSOLE) (S char -- ) PAUSE 4 BIOS DROP 1 #OUT +! ; \ Devices Terminal Input and Output 19Apr84mapDEFER KEY? DEFER KEY DEFER CR : PR-STAT (S -- f ) TRUE ( 0 15 BIOS ) ; : (PRINT) (S char -- ) BEGIN PAUSE PR-STAT UNTIL 5 BIOS DROP 1 #OUT +! ; : (EMIT) (S char -- ) PRINTING @ IF DUP (PRINT) -1 #OUT +! THEN (CONSOLE) ; : CRLF (S -- ) 13 EMIT 10 EMIT #OUT OFF 1 #LINE +! ; : TYPE (S addr len -- ) 0 ?DO COUNT EMIT LOOP DROP ; : SPACE (S -- ) BL EMIT ; : SPACES (S n -- ) 0 MAX 0 ?DO SPACE LOOP ; : BACKSPACES (S n -- ) 0 ?DO BS EMIT LOOP ; : BEEP (S -- ) BELL EMIT ; \ Devices System Dependent Control Characters 02Apr84map: BS-IN (S n c -- 0 | n-1 ) DROP DUP IF 1- BS ELSE BELL THEN EMIT ; : (DEL-IN) (S n c -- 0 | n-1 ) DROP DUP IF 1- BS EMIT SPACE BS ELSE BELL THEN EMIT ; : BACK-UP (S n c -- 0 ) DROP DUP BACKSPACES DUP SPACES BACKSPACES 0 ; : RES-IN (S c -- ) FORTH TRUE ABORT" Reset" ; : P-IN (S c -- ) DROP PRINTING @ NOT PRINTING ! ; \ Devices Terminal Input 16FEB84MAP: CR-IN (S m a n c -- m a m ) DROP SPAN ! OVER BL EMIT ; : (CHAR) (S a n char -- a n+1 ) 3DUP EMIT + C! 1+ ; DEFER CHAR DEFER DEL-IN VARIABLE CC CREATE CC-FORTH ] CHAR CHAR CHAR RES-IN CHAR CHAR CHAR CHAR BS-IN CHAR CHAR CHAR CHAR CR-IN CHAR CHAR P-IN CHAR CHAR CHAR CHAR BACK-UP CHAR CHAR BACK-UP CHAR CHAR CHAR CHAR CHAR CHAR CHAR [ \ Devices Terminal Input 29Sep83map: EXPECT (S adr len -- ) DUP SPAN ! SWAP 0 ( len adr 0 ) BEGIN 2 PICK OVER - ( len adr #so-far #left ) WHILE KEY DUP BL < IF DUP 2* CC @ + PERFORM ELSE DUP 127 = IF DEL-IN ELSE CHAR THEN THEN REPEAT 2DROP DROP ; : TIB (S -- adr ) 'TIB @ ; : QUERY (S -- ) TIB 80 EXPECT SPAN @ #TIB ! BLK OFF >IN OFF ; \ Devices BLOCK I/O 11Mar84map 4 CONSTANT #BUFFERS 1024 CONSTANT B/BUF 128 CONSTANT B/REC 8 CONSTANT REC/BLK 42 CONSTANT B/FCB VARIABLE DISK-ERROR -2 CONSTANT LIMIT #BUFFERS 1+ 8 * 2+ CONSTANT >SIZE LIMIT B/BUF #BUFFERS * - CONSTANT FIRST FIRST >SIZE - CONSTANT INIT-R0 : >BUFFERS (S -- adr ) FIRST >SIZE - ; : >END (S -- adr ) FIRST 2- ; : BUFFER# (S n -- adr ) 8* >BUFFERS + ; : >UPDATE (S -- adr ) 1 BUFFER# 6 + ; \ Devices BLOCK I/O 13Apr84mapDEFER READ-BLOCK (S buffer-header -- ) DEFER WRITE-BLOCK (S buffer-header -- ) : .FILE (S adr -- ) COUNT ?DUP IF ASCII @ + EMIT ." :" THEN 8 2DUP -TRAILING TYPE + ." ." 3 TYPE SPACE ; : FILE? (S -- ) FILE @ .FILE ; : SWITCH (S -- ) FILE @ IN-FILE @ FILE ! IN-FILE ! ; VOCABULARY DOS DOS DEFINITIONS : !FILES (S fcb -- ) DUP FILE ! IN-FILE ! ; : DISK-ABORT (S fcb a n -- ) TYPE ." in " .FILE ABORT ; : ?DISK-ERROR (S fcb n -- ) DUP DISK-ERROR ! IF " Disk error" DISK-ABORT ELSE DROP THEN ; \ Devices BLOCK I/O 30Mar84mapCREATE FCB1 B/FCB ALLOT : CLR-FCB (S fcb -- ) DUP B/FCB ERASE 1+ 11 BLANK ; : SET-DMA (S adr -- ) 26 BDOS DROP ; : RECORD# (S fcb -- adr ) 34 + ; : MAXREC# (S fcb -- adr ) 38 + ; : IN-RANGE (S fcb -- fcb ) DUP MAXREC# @ OVER RECORD# @ U< DUP DISK-ERROR ! IF 1 BUFFER# ON " Out of Range" DISK-ABORT THEN ; : REC-READ (S fcb -- ) DUP IN-RANGE 33 BDOS ?DISK-ERROR ; : REC-WRITE (S fcb -- ) DUP IN-RANGE 34 BDOS ?DISK-ERROR ; \ Devices BLOCK I/O 29Mar84map: SET-IO (S buf-header -- file buffer rec/blk 0 ) DUP 2@ REC/BLK * OVER RECORD# ! SWAP 4 + @ ( buf-addr ) REC/BLK 0 ; : FILE-READ (S buffer-header -- ) SET-IO DO 2DUP SET-DMA DUP REC-READ 1 SWAP RECORD# +! B/REC + LOOP 2DROP ; : FILE-WRITE (S buffer-header -- ) SET-IO DO 2DUP SET-DMA DUP REC-WRITE 1 SWAP RECORD# +! B/REC + LOOP 2DROP ; : FILE-IO (S -- ) ['] FILE-READ IS READ-BLOCK ['] FILE-WRITE IS WRITE-BLOCK ; \ Devices BLOCK I/O 29Mar84mapFORTH DEFINITIONS : CAPACITY (S -- n ) [ DOS ] FILE @ MAXREC# @ 1+ 0 8 UM/MOD NIP ; : LATEST? (S n fcb -- fcb n | a f ) DISK-ERROR OFF SWAP OFFSET @ + 2DUP 1 BUFFER# 2@ D= IF 2DROP 1 BUFFER# 4 + @ FALSE R> DROP THEN ; : ABSENT? (S n fcb -- a f ) LATEST? FALSE #BUFFERS 1+ 2 DO DROP 2DUP I BUFFER# 2@ D= IF 2DROP I LEAVE ELSE FALSE THEN LOOP ?DUP IF BUFFER# DUP >BUFFERS 8 CMOVE >R >BUFFERS DUP 8 + OVER R> SWAP - CMOVE> 1 BUFFER# 4 + @ FALSE ELSE >BUFFERS 2! TRUE THEN ; \ Devices BLOCK I/O 01Apr84map: UPDATE (S -- ) >UPDATE ON ; : DISCARD (S -- ) 1 >UPDATE ! ( 1 BUFFER# ON ) ; : MISSING (S -- ) >END 2- @ 0< IF >END 2- OFF >END 8 - WRITE-BLOCK THEN >END 4 - @ >BUFFERS 4 + ! ( buffer ) 1 >BUFFERS 6 + ! >BUFFERS DUP 8 + #BUFFERS 8* CMOVE> ; : (BUFFER) (S n fcb -- a ) PAUSE ABSENT? IF MISSING 1 BUFFER# 4 + @ THEN ; : BUFFER (S n -- a ) FILE @ (BUFFER) ; : (BLOCK) (S n fcb -- a ) (BUFFER) >UPDATE @ 0> IF 1 BUFFER# DUP READ-BLOCK 6 + OFF THEN ; : BLOCK (S n -- a ) FILE @ (BLOCK) ; : IN-BLOCK (S n -- a ) IN-FILE @ (BLOCK) ; \ Devices BLOCK I/O 01APR84MAP: EMPTY-BUFFERS (S -- ) FIRST LIMIT OVER - ERASE >BUFFERS #BUFFERS 1+ 8* ERASE FIRST 1 BUFFER# #BUFFERS 0 DO DUP ON 4 + 2DUP ! SWAP B/BUF + SWAP 4 + LOOP 2DROP ; : SAVE-BUFFERS (S -- ) 1 BUFFER# #BUFFERS 0 DO DUP @ 1+ IF DUP 6 + @ 0< IF DUP WRITE-BLOCK DUP 6 + OFF THEN 8 + THEN LOOP DROP ; : FLUSH (S -- ) SAVE-BUFFERS 0 BLOCK DROP EMPTY-BUFFERS ; : VIEW# (S -- addr ) FILE @ 40 + ; \ Devices BLOCK I/O 10Apr84mapDOS DEFINITIONS : FILE-SIZE (S fcb -- n ) DUP 35 BDOS DROP RECORD# @ ; : DOS-ERR? (S -- f ) 255 = ; : OPEN-FILE (S -- ) IN-FILE @ DUP 15 BDOS DOS-ERR? DUP DISK-ERROR ! IF " Open error" DISK-ABORT THEN DUP FILE-SIZE 1- SWAP MAXREC# ! ; HEX 45C CONSTANT DOS-FCB DECIMAL FORTH DEFINITIONS : DEFAULT (S -- ) [ DOS ] FCB1 DUP IN-FILE ! DUP FILE ! CLR-FCB DOS-FCB 1+ C@ BL <> IF DOS-FCB FCB1 12 CMOVE OPEN-FILE THEN ; : (LOAD) (S n -- ) FILE @ >R BLK @ >R >IN @ >R >IN OFF BLK ! IN-FILE @ FILE ! RUN R> >IN ! R> BLK ! R> !FILES ; DEFER LOAD \ Interactive Layer Number Input 07Mar84mapASSEMBLER LABEL FAIL SP -) CLR NEXT CODE DIGIT (S char base -- n true | char false ) SP )+ D0 MOVE SP ) D1 MOVE BYTE 48 # D1 SUB FAIL BMI 10 # D1 CMP 0>= IF 17 # D1 CMP FAIL BMI 7 D1 SUBQ THEN D0 D1 CMP FAIL BPL WORD D1 SP ) MOVE TRUE # SP -) MOVE NEXT END-CODE : DOUBLE? (S -- f ) DPL @ 1+ 0<> ; : CONVERT (S +d1 adr1 -- +d2 adr2 ) BEGIN 1+ DUP >R C@ BASE @ DIGIT WHILE SWAP BASE @ UM* DROP ROT BASE @ UM* D+ DOUBLE? IF 1 DPL +! THEN R> REPEAT DROP R> ; \ Interactive Layer Number Input 06Oct83map: (NUMBER?) (S adr -- d flag ) 0 0 ROT DUP 1+ C@ ASCII - = DUP >R - -1 DPL ! BEGIN CONVERT DUP C@ ASCII , ASCII / BETWEEN WHILE 0 DPL ! REPEAT -ROT R> IF DNEGATE THEN ROT C@ BL = ; : NUMBER? (S adr -- d flag ) FALSE OVER COUNT BOUNDS ?DO I C@ BASE @ DIGIT NIP IF DROP TRUE LEAVE THEN LOOP IF (NUMBER?) ELSE DROP 0 0 FALSE THEN ; : (NUMBER) (S adr -- d# ) NUMBER? NOT ?MISSING ; DEFER NUMBER \ Interactive Layer Number Output 03Apr84map: HOLD (S char -- ) -1 HLD +! HLD @ C! ; : <# (S -- ) PAD HLD ! ; : #> (S d# -- addr len ) 2DROP HLD @ PAD OVER - ; : SIGN (S n1 -- ) 0< IF ASCII - HOLD THEN ; : # (S -- ) BASE @ MU/MOD ROT 9 OVER < IF 7 + THEN ASCII 0 + HOLD ; : #S (S -- ) BEGIN # 2DUP OR 0= UNTIL ; : HEX (S -- ) 16 BASE ! ; : DECIMAL (S -- ) 10 BASE ! ; : OCTAL (S -- ) 8 BASE ! ; \ Interactive Layer Number Output 24FEB83HHL: (U.) (S u -- a l ) 0 <# #S #> ; : U. (S u -- ) (U.) TYPE SPACE ; : U.R (S u l -- ) >R (U.) R> OVER - SPACES TYPE ; : (.) (S n -- a l ) DUP ABS 0 <# #S ROT SIGN #> ; : . (S n -- ) (.) TYPE SPACE ; : .R (S n l -- ) >R (.) R> OVER - SPACES TYPE ; : (UD.) (S ud -- a l ) <# #S #> ; : UD. (S ud -- ) (UD.) TYPE SPACE ; : UD.R (S ud l -- ) >R (UD.) R> OVER - SPACES TYPE ; : (D.) (S d -- a l ) TUCK DABS <# #S ROT SIGN #> ; : D. (S d -- ) (D.) TYPE SPACE ; : D.R (S d l -- ) >R (D.) R> OVER - SPACES TYPE ; \ SKIP SCAN 07Mar84mapASSEMBLER LABEL DONE A0 SP -) MOVE D1 SP -) MOVE NEXT END-CODE CODE SKIP (S adr1 len1 char -- adr2 len2 ) SP )+ D0 MOVE SP )+ D1 MOVE 1 D1 ADDQ SP )+ D7 MOVE D7 A0 LMOVE BEGIN 1 D1 SUBQ 0<> WHILE BYTE A0 ) D2 MOVE D2 D0 CMP DONE BNE WORD 1 A0 ADDQ REPEAT DONE BRA END-CODE CODE SCAN (S adr1 len1 char -- adr2 len2 ) SP )+ D0 MOVE SP )+ D1 MOVE 1 D1 ADDQ SP )+ D7 MOVE D7 A0 LMOVE BEGIN 1 D1 SUBQ 0<> WHILE BYTE A0 ) D2 MOVE D2 D0 CMP DONE BEQ WORD 1 A0 ADDQ REPEAT DONE BRA END-CODE \ Interactive Layer Parsing 02Apr84map: /STRING (S addr len n -- addr' len' ) OVER MIN ROT OVER + -ROT - ; : PLACE (S str-addr len to -- ) 3DUP 1+ SWAP MOVE C! DROP ; : (SOURCE) (S -- addr len ) BLK @ ?DUP IF BLOCK B/BUF ELSE TIB #TIB @ THEN ; DEFER SOURCE : PARSE-WORD (S char -- addr len ) >R SOURCE TUCK >IN @ /STRING R@ SKIP OVER SWAP R> SCAN >R OVER - ROT R> DUP 0<> + - >IN ! ; : PARSE (S char -- addr len ) >R SOURCE >IN @ /STRING OVER SWAP R> SCAN >R OVER - DUP R> 0<> - >IN +! ; \ Interactive Layer Parsing 07Mar84map: 'WORD (S -- adr ) HERE ; : WORD (S char -- addr ) PARSE-WORD 'WORD PLACE 'WORD DUP COUNT + BL SWAP C! ( Stick Blank at end ) ; : >TYPE (S adr len -- ) TUCK PAD SWAP CMOVE PAD SWAP TYPE ; : .( (S -- ) ASCII ) PARSE >TYPE ; IMMEDIATE : ( (S -- ) ASCII ) PARSE 2DROP ; IMMEDIATE : \S (S -- ) END? ON ; IMMEDIATE \ Interactive Layer Dictionary 03Jun84mapCODE TRAVERSE (S addr direction -- addr' ) SP )+ D0 MOVE SP )+ D7 MOVE D7 A0 LMOVE D0 A0 ADDA BEGIN A0 ) 7 # BTST 0= WHILE D0 A0 ADDA REPEAT A0 SP -) MOVE NEXT END-CODE : DONE? (S n -- f ) STATE @ <> END? @ OR END? OFF ; : FORTH-83 (S -- ) FORTH DEFINITIONS CAPS OFF ; \ Interactive Layer Dictionary 07Mar84map: N>LINK 2- ; : L>NAME 2+ ; : BODY> 2- ; : NAME> 1 TRAVERSE 1+ ; : LINK> L>NAME NAME> ; : >BODY 2+ ; : >NAME 1- -1 TRAVERSE ; : >LINK >NAME N>LINK ; : >VIEW >LINK 2- ; : VIEW> 2+ LINK> ; CODE HASH (S str-addr voc-ptr -- thread ) SP )+ D1 MOVE SP )+ D7 MOVE D7 A0 LMOVE BYTE A0 )+ TST A0 )+ D0 MOVE WORD 3 # D0 AND D0 D0 ADD D0 D1 ADD D1 SP -) MOVE NEXT END-CODE \ Interactive Layer Dictionary 13Mar84mapCODE (FIND) (S string link -- code true | adr false ) HEX D7 D6 LMOVE D2 CLR SP )+ D7 MOVE BEGIN 0<> WHILE D7 A1 LMOVE SP ) D6 MOVE D6 A0 LMOVE A1 )+ TST BYTE A0 )+ D0 MOVE A1 )+ D1 MOVE D1 D2 MOVE D0 D1 EOR 3F # D1 AND ( mask flag bits ) 0= IF BEGIN A0 )+ D0 MOVE A1 )+ D1 MOVE D0 D1 EOR 0<> UNTIL 7F # D1 AND 0= ( found? ) WORD IF A1 SP ) MOVE 40 # D2 AND 0<> IF 1 # SP -) MOVE ELSE -1 # SP -) MOVE THEN NEXT THEN THEN D7 A1 LMOVE A1 ) D7 MOVE REPEAT SP -) CLR NEXT END-CODE DECIMAL \ Interactive Layer Dictionary 03Apr84map4 CONSTANT #THREADS : FIND (S addr -- cfa flag | addr false ) DUP C@ IF PRIOR OFF FALSE #VOCS 0 DO DROP CONTEXT I 2* + @ DUP IF DUP PRIOR @ OVER PRIOR ! = IF DROP FALSE ELSE OVER SWAP HASH @ (FIND) DUP ?LEAVE THEN THEN LOOP ELSE DROP END? ON ['] NOOP 1 THEN ; : ?UPPERCASE (S adr -- adr ) CAPS @ IF DUP COUNT UPPER THEN ; : DEFINED (S -- here 0 | cfa [ -1 | 1 ] ) BL WORD ?UPPERCASE FIND ; \ Interactive Layer Interpreter 27Sep83map: ?STACK (S -- ) ( System dependant ) SP@ SP0 @ SWAP U< ABORT" Stack Underflow" SP@ PAD U< ABORT" Stack Overflow" ; DEFER STATUS (S -- ) : INTERPRET (S -- ) BEGIN ?STACK DEFINED IF EXECUTE ELSE NUMBER DOUBLE? NOT IF DROP THEN THEN FALSE DONE? UNTIL ; \ Extensible Layer Compiler 09Apr84map: ALLOT (S n -- ) DP +! ; : , (S n -- ) HERE ! 2 ALLOT ; : C, (S char -- ) HERE C! 1 ALLOT ; : ALIGN HERE 1 AND IF BL C, THEN ; : EVEN DUP 1 AND + ; : COMPILE (S -- ) R> DUP 2+ >R @ , ; : IMMEDIATE (S -- ) 64 ( Precedence bit ) LAST @ CSET ; : LITERAL (S n -- ) COMPILE (LIT) , ; IMMEDIATE : DLITERAL (S d# -- ) SWAP [COMPILE] LITERAL [COMPILE] LITERAL ; IMMEDIATE : ASCII (S -- n ) BL WORD 1+ C@ STATE @ IF [COMPILE] LITERAL THEN ; IMMEDIATE : CONTROL (S -- n ) BL WORD 1+ C@ 31 AND STATE @ IF [COMPILE] LITERAL THEN ; IMMEDIATE \ Extensible Layer Compiler 08Oct83map: CRASH (S -- ) TRUE ABORT" Uninitialized execution vector." ; : ?MISSING (S f -- ) IF 'WORD COUNT TYPE TRUE ABORT" ?" THEN ; : ' (S -- cfa ) DEFINED 0= ?MISSING ; : ['] (S -- ) ' [COMPILE] LITERAL ; IMMEDIATE : [COMPILE] (S -- ) ' , ; IMMEDIATE : (") (S -- addr len ) R> COUNT 2DUP + EVEN >R ; : (.") (S -- ) R> COUNT 2DUP + EVEN >R TYPE ; : ," (S -- ) ASCII " PARSE TUCK 'WORD PLACE 1+ ALLOT ALIGN ; : ." (S -- ) COMPILE (.") ," ; IMMEDIATE : " (S -- ) COMPILE (") ," ; IMMEDIATE \ Interactive Layer Dictionary 12Apr84mapVARIABLE FENCE : TRIM (S faddr voc-addr -- ) #THREADS 0 DO 2DUP @ BEGIN 2DUP U> NOT WHILE @ REPEAT NIP OVER ! 2+ LOOP 2DROP ; : (FORGET) (S addr -- ) DUP FENCE @ U< ABORT" Below fence" DUP VOC-LINK @ BEGIN 2DUP U< WHILE @ REPEAT DUP VOC-LINK ! NIP BEGIN DUP WHILE 2DUP #THREADS 2* - TRIM @ REPEAT DROP DP ! ; : FORGET (S -- ) BL WORD ?UPPERCASE DUP CURRENT @ HASH @ (FIND) 0= ?MISSING >VIEW (FORGET) ; \ Extensible Layer Compiler 11Mar84mapDEFER WHERE DEFER ?ERROR : (?ERROR) (S adr len f -- ) IF >R >R SP0 @ SP! PRINTING OFF BLK @ IF >IN @ BLK @ WHERE THEN R> R> SPACE TYPE SPACE QUIT ELSE 2DROP THEN ; : (ABORT") (S f -- ) R@ COUNT ROT ?ERROR R> COUNT + EVEN >R ; : ABORT" (S -- ) COMPILE (ABORT") ," ; IMMEDIATE : ABORT (S -- ) TRUE ABORT" " ; \ Extensible Layer Structures 03Apr84map: ?CONDITION (S f -- ) NOT ABORT" Conditionals Wrong" ; : >MARK (S -- addr ) HERE 0 , ; : >RESOLVE (S addr -- ) HERE SWAP ! ; : MARK (S -- f addr ) TRUE >MARK ; : ?>RESOLVE (S f addr -- ) SWAP ?CONDITION >RESOLVE ; : ?RESOLVE ; IMMEDIATE : DO COMPILE (DO) ?>MARK ; IMMEDIATE : ?DO COMPILE (?DO) ?>MARK ; IMMEDIATE : LOOP COMPILE (LOOP) 2DUP 2+ ?RESOLVE ; IMMEDIATE : +LOOP COMPILE (+LOOP) 2DUP 2+ ?RESOLVE ; IMMEDIATE : UNTIL COMPILE ?BRANCH ?MARK ; IMMEDIATE : ELSE COMPILE BRANCH ?>MARK 2SWAP ?>RESOLVE ; IMMEDIATE : WHILE [COMPILE] IF ; IMMEDIATE \ Extensible Layer Defining Words 08Apr84map: ,VIEW (S -- ) BLK @ DUP IF VIEW# @ 4096 * + THEN , ; : "CREATE (S str -- ) COUNT HERE EVEN 4 + PLACE ALIGN ,VIEW HERE 0 , ( reserve link ) HERE LAST ! ( remember nfa ) HERE ( lfa nfa ) WARNING @ IF FIND IF HERE COUNT TYPE ." isn't unique " THEN DROP HERE THEN ( lfa nfa ) CURRENT @ HASH DUP @ ( lfa tha prev ) HERE 2- ROT ! ( lfa prev ) SWAP ! ( Resolve link field) HERE DUP C@ WIDTH @ MIN 1+ ALLOT ALIGN 128 SWAP CSET 128 HERE 1- CSET ( delimiter Bits ) COMPILE [ [FORTH] ASSEMBLER DOCREATE , META ] ; : CREATE (S -- ) BL WORD ?UPPERCASE "CREATE ; \ Extensible Layer Defining Words 21Dec83map: !CSP (S -- ) SP@ CSP ! ; : ?CSP (S -- ) SP@ CSP @ <> ABORT" Stack Changed" ; : HIDE (S -- ) LAST @ DUP N>LINK @ SWAP CURRENT @ HASH ! ; : REVEAL (S -- ) LAST @ DUP N>LINK SWAP CURRENT @ HASH ! ; : (;USES) (S -- ) R> @ LAST @ NAME> ! ; VOCABULARY ASSEMBLER : ;USES (S -- ) ?CSP COMPILE (;USES) [COMPILE] [ REVEAL ASSEMBLER ; IMMEDIATE : (;CODE) (S -- ) R> LAST @ NAME> ! ; : ;CODE (S -- ) ?CSP COMPILE (;CODE) [COMPILE] [ REVEAL ASSEMBLER ; IMMEDIATE HEX : DOES> (S -- ) COMPILE (;CODE) 4EB8 , ( JSR ) [ DECIMAL ] [ [ASSEMBLER] DODOES META ] LITERAL , ; IMMEDIATE \ Extensible Layer Defining Words 27Sep83map: [ (S -- ) STATE OFF ; IMMEDIATE : ] (S -- ) STATE ON BEGIN ?STACK DEFINED DUP IF 0> IF EXECUTE ELSE , THEN ELSE DROP NUMBER DOUBLE? IF [COMPILE] DLITERAL ELSE DROP [COMPILE] LITERAL THEN THEN TRUE DONE? UNTIL ; : : (S -- ) !CSP CURRENT @ CONTEXT ! CREATE HIDE ] ;USES NEST , : ; (S -- ) ?CSP COMPILE UNNEST REVEAL [COMPILE] [ ; IMMEDIATE \ Extensible Layer Defining Words 03Apr84map: RECURSIVE (S -- ) REVEAL ; IMMEDIATE : CONSTANT (S n -- ) CREATE , ;USES DOCONSTANT , : VARIABLE (S -- ) CREATE 0 , ;USES DOCREATE , : DEFER (S -- ) CREATE ['] CRASH , ;USES DODEFER , DODEFER RESOLVES : VOCABULARY (S -- ) CREATE #THREADS 0 DO 0 , LOOP HERE VOC-LINK @ , VOC-LINK ! DOES> CONTEXT ! ; RESOLVES : DEFINITIONS (S -- ) CONTEXT @ CURRENT ! ; \ Extensible Layer Defining Words 03Apr84map: 2CONSTANT CREATE , , (S d# -- ) DOES> 2@ ; (S -- d# ) DROP : 2VARIABLE 0 0 2CONSTANT (S -- ) DOES> ; (S -- addr ) DROP VARIABLE AVOC : CODE (S -- ) CREATE HIDE HERE DUP 2- ! CONTEXT @ AVOC ! ASSEMBLER ; ASSEMBLER DEFINITIONS : END-CODE AVOC @ CONTEXT ! REVEAL ; FORTH DEFINITIONS META IN-META \ Extensible Layer Defining Words 13Apr84mapVARIABLE #USER VOCABULARY USER USER DEFINITIONS : ALLOT (S n -- ) #USER +! ; ' CREATE ( avoid recursion: leave address for , in CREATE ) : CREATE (S -- ) [ , ] #USER @ , ;USES DOUSER-VARIABLE , : VARIABLE (S -- ) CREATE 2 ALLOT ; : DEFER (S -- ) VARIABLE ;USES DOUSER-DEFER , FORTH DEFINITIONS META IN-META \ Extensible Layer ReDefining Words 21Dec83map: >IS (S cfa -- data-address ) DUP @ DUP [ [ASSEMBLER] DOUSER-VARIABLE META ] LITERAL = SWAP DUP [ [ASSEMBLER] DOUSER-DEFER META ] LITERAL = SWAP DROP OR IF >BODY @ UP @ + ELSE >BODY THEN ; : (IS) (S cfa --- ) R@ @ >IS ! R> 2+ >R ; : IS (S cfa --- ) STATE @ IF COMPILE (IS) ELSE ' >IS ! THEN ; IMMEDIATE \ Initialization High Level 29Sep83map: RUN (S -- ) STATE @ IF ] STATE @ NOT IF INTERPRET THEN ELSE INTERPRET THEN ; : QUIT (S -- ) SP0 @ 'TIB ! BLK OFF [COMPILE] [ BEGIN RP0 @ RP! STATUS QUERY RUN STATE @ NOT IF ." ok" THEN AGAIN ; DEFER BOOT : WARM (S -- ) TRUE ABORT" Warm Start" ; : COLD (S -- ) BOOT QUIT ; \ Initialization High Level 19Apr84map1 CONSTANT INITIAL : OK (S -- ) INITIAL LOAD ; : START (S -- ) EMPTY-BUFFERS DEFAULT ; : BYE ( -- ) CR HERE 0 256 UM/MOD NIP 1+ DECIMAL U. ." Pages" 0 0 BDOS ; \ Initialization Low Level 07Mar84map [ASSEMBLER] HERE ORIGIN 6 + !-T ( WARM ENTRY POINT ) ' WARM 0 L#) W LEA W )+ D7 MOVE D7 A0 LMOVE A0 ) JMP HERE ORIGIN 2 + !-T ( COLD ENTRY POINT ) INIT-R0 0 L#) RP LEA INIT-R0 256 - 0 L#) SP LEA LONG D7 CLR WORD ' COLD 0 L#) W LEA W )+ D7 MOVE D7 A0 LMOVE A0 ) JMP \ Initialize User Variables 13Apr84mapHERE UP !-T ( SET UP USER AREA ) 0 , ( TOS ) 0 , ( ENTRY ) 0 , ( LINK ) INIT-R0 256 - , ( SP0 ) INIT-R0 , ( RP0 ) 0 , ( DP ) ( Must be patched later ) 0 , ( #OUT ) 0 , ( #LINE ) 0 , ( OFFSET ) 10 , ( BASE ) 0 , ( HLD ) 0 , ( FILE ) 0 , ( IN-FILE ) FALSE , ( PRINTING ) ' (EMIT) , ( EMIT ) \ Resident Tools 02Apr84map: DEPTH (S -- n ) SP@ SP0 @ SWAP - 2/ ; : .S (S -- ) DEPTH ?DUP IF 0 DO DEPTH I - 1- PICK 7 U.R SPACE KEY? ?LEAVE LOOP ELSE ." Empty " THEN ; : .ID (S nfa -- ) DUP 1+ DUP C@ ROT C@ 31 AND 0 ?DO DUP 127 AND EMIT 128 AND IF ASCII _ 128 OR ELSE 1+ DUP C@ THEN LOOP 2DROP SPACE ; : DUMP (S addr len -- ) 0 DO CR DUP 6 .R SPACE 16 0 DO DUP C@ 3 .R 1+ LOOP 16 +LOOP DROP ; \ For Completeness 03Apr84map: RECURSE (S -- ) LAST @ NAME> , ; IMMEDIATE \ Resolve Forward References 21Dec83map ' (.") RESOLVES <(.")> ' (") RESOLVES <(")> ' (;CODE) RESOLVES <(;CODE)> ' (;USES) RESOLVES <(;USES)> ' (IS) RESOLVES <(IS)> ' (ABORT") RESOLVES <(ABORT")> [ASSEMBLER] DOCREATE META RESOLVES [ASSEMBLER] DOUSER-DEFER META RESOLVES [ASSEMBLER] DOUSER-VARIABLE META RESOLVES \ Resolve Forward References 03Apr84map' SWAP RESOLVES SWAP ' DEFINITIONS RESOLVES DEFINITIONS ' + RESOLVES + ' OVER RESOLVES OVER ' [ RESOLVES [ ' 2+ RESOLVES 2+ ' 1+ RESOLVES 1+ ' 2* RESOLVES 2* ' 2DUP RESOLVES 2DUP ' ?MISSING RESOLVES ?MISSING ' RUN RESOLVES RUN ' ABORT RESOLVES ABORT ' QUIT RESOLVES QUIT \ Initialize DEFER words 19Apr84map ' (LOAD) IS LOAD ' (KEY?) IS KEY? ' (KEY) IS KEY ' CRLF IS CR ' FILE-READ IS READ-BLOCK ' FILE-WRITE IS WRITE-BLOCK ' NOOP IS WHERE ' CR IS STATUS ' (SOURCE) IS SOURCE ' START IS BOOT ' (NUMBER) IS NUMBER ' (CHAR) IS CHAR ' (DEL-IN) IS DEL-IN ' (?ERROR) IS ?ERROR \ Initialize Variables 20Apr84map' FORTH >BODY CURRENT !-T ' FORTH >BODY CONTEXT !-T ' CC-FORTH >BODY CC !-T HERE-T DP UP @-T + !-T ( INIT USER DP ) #USER-T @ #USER !-T ( INIT USER VAR COUNT ) TRUE CAPS !-T ( SET TO IGNORE CASE ) TRUE WARNING !-T ( SET TO ISSUE WARNINGS ) 31 WIDTH !-T ( 31 CHARACTER NAMES ) VOC-LINK-T @ VOC-LINK !-T ( INIT VOC-LINK ) \ Further Instructions 07Feb84map\S ******************************************************************* ****** Thus we have created a hopefully running ****** Forth system for the 68000. After this file ****** has been compiled, it is saved as a .68K file ****** called KERNEL.68K on the disk. To generate ****** a system you must now leave the Meta Compiler ****** and fire up KERNEL with the file EXTEND68.BLK ****** on the execute line. Be sure to prefix a B: ****** if necessary. ( KERNEL EXTEND68.BLK ) ****** Once you have fired it up, type START and it ****** will compile the applications. Good Luck. ****** *******************************************************************\ Target System Setup 13Apr84map Set up the address where Target Compiled Code begins Set up the address where the Target Headers begin Set up the HOST address where Target Image resides Load the Source Screens that define the System Save the System as a CP/M file, ready to be executed \ Declare the Forward References 27Jan84map]] We will need the FORTH version of ] quite often. [[ The same is true for [[. DEFINIITONS To avoid finding DEFINITIONS in the ONLY vocabulary[ To avoid finding [ in the TRANSITION vocabulary FILE-HEADER lay down image of the required file header in front of the target image. \ Boot up Vectors and NEXT Interpreter 07Oct83map The first 8 bytes in the system are vectors to the Cold and Warmstart entries. You can freely jump to them in code anytime. >NEXT is where all the action is. It is the guts of the Forth Virtual Machine. It must advance the interpretive pointer held in the IP register pair and jump indirect to what it points to. >NEXT The address of the inner interpreter. We define a few macros here to make our life a little easier later. Using NEXT as a macro allows us to put it inline later. \ Run Time Code for Defining Words 07Oct83mapNEST The runtime code for : It pushs the current IP onto the return stack and sets the IP to point to the parameter field of the word being executed. EXIT Pop an entry off the return stack and place it into the Interpretive Pointer. Terminates a Hi Level definition. UNNEST Same as exit. Compiled by ; to help decompiling. DODOES The runtime portion of defining words. First it pushes the IP onto the return stack and then it pushes the BODY address of the word being executed onto the parameter stack. DOCREATE Leave a pointer to its own parameter field on the stack. This is also the runtime for variable. \ Run Time Code for Defining Words 02AUG83HHLUP Holds a pointer to the current USER area. ( multitasking ) DOCONSTANT The run time code for CONSTANT. It takes the contents of the parameter field and pushes it onto the stack.DOUSER The run time code for USER variables. Places a pointer to the current version of this variable on the stack. Needed for multitasking. (LIT) The runtime code for literals. Pushes the following two bytes onto the parameter stack and moves the IP over them. It is compiled by the word LITERAL. \ Meta Defining Words 10MAR83HHLLITERAL Now that code field of (LIT) is known, define LITERAL DLITERAL Both LITERAL and DLITERAL are TRANSITION words, ie IMMEDIATE ASCII Compile the next character as a literal. ['] Compile the code field of the next word as a literal. CONSTANT Define a CONSTANT in the Target. We also save its value in META for use during interpretation. \ Identify numbers and forward References 02AUG83HHL<(;CODE)> Forward reference for code to patch code field. DOES> Compile the code field for (;CODE) and a CALL instruction to the run time for DOES, called DODOES. NUMERIC Make a number out of this word and compile it as either a single or double precision literal. NUMERIC is only called if the word is known to be a number. UNDEFINED Creates a forward reference "on the fly". The symbol is kept in the FORWARD vocabulary and it is initialized to unresolved. When executed it either compiles itself or links into a backwards pointing chain of forward references. \ Meta Compiler Compiling Loop 10MAR83HHLT-IN Needed to save a pointer into the input stream for later.] Start compiling into the TARGET system. Always search TRANSITION before TARGET for immediate words. If word is found, execute it. It must compile itself. If word is not found, convert it to a number if it is numeric, otherwise it is a forward reference. [ Sets STATE-T to false to exit the Meta Compiling loop above. ; Compile the code field of UNNEST and terminate compilation : Create a target word and set its code field to NEST. \ Run Time Code for Control Structures 05MAR83HHLBRANCH Performs an unconditional branch. Notice that we are using absolute addresses insead of relative ones. (fast) ?BRANCH Performs a conditional branch. If the top of the parameter stack in True, take the branch. If not, skip over the branch address which is inline. \ Meta Compiler Branching Words 10MAR83HHLThese are the META versions of the structured conditionals found in FORTH. They must compile the correct run time branch instruction, and then Mark and Resolve either forward or backward branches. These are very analogous to the regular conditionals in Forth. Since they are in the TRANSITION vocabulary, which is searched before the TARGET vocabulary, they will be executed instead of the TARGET versions of these words which are defined much later. \ Run Time Code for Control Structures 07Oct83map(LOOP) the runtime procedure for LOOP. Branches back to the beginning of the loop if there are more iterations to do. Otherwise it exits. The loop counter is incremented. (+LOOP) Increment the loop counter by the value on the stack and decide whether or not to loop again. \ Run Time Code for Control Structures 28AUG83HHL(DO) The runtime code compiled by DO. Pushes the inline address onto the return stack along with values needed by (LOOP). (?DO) The runtime code compiled by ?DO. The difference between ?DO and DO is that ?DO will not perform any iterations if the initial index is equal to the final index. BOUNDS Given address and length, make it ok for DO ... LOOP. \ Meta compiler Branching & Looping 10MAR83HHLThese are again the TRANSITION versions of the immediate words for looping. They compile the correct run time code and then Mark and Resolve the various branches. \ Execution Control 07Oct83mapEXECUTE the word whose code field is on the stack. Very useful for passing executable routines to procedures!!! PERFORM the word whose code field is stored at the address pointed to by the number on the stack. Same as @ EXECUTE DO-DEFER The runtime code for deferred words. Fetches the code field and executes it. DOUSER-DEFER The runtime code for User deferred words. These are identical to regular deferred words except that each task has its own version. GO Execute code at the given address. NOOP One of the most useful words in Forth. Does nothing. PAUSE Used by the Multitasker to switch tasks. \ Execution Control 01Oct83mapI returns the current loop index. It now requires a little more calculation to compute it than in FIG Forth but the tradeoff is a much faster (LOOP). The loop index is stored on the Return Stack. J returns the loop index of the inner loop in nested DO .. LOOPs. (LEAVE) Does an immediate exit of a DO ... LOOP structure. Unlike FIG Forth which waits until the next LOOP is executed. (?LEAVE) Leaves if the flag on the stack is true. Continues if not. LEAVE I have to do this to be 83-Standard. \ 16 and 8 bit Memory Operations 05MAR83HHL@ Fetch a 16 bit value from addr. ! Store a 16 bit value at addr. C@ Fetch an 8 bit value from addr. C! Store an 8 bit value at addr. \ Block Move Memory Operations 05MAR83HHLCMOVE Move a set of bytes from the from address to the to address. The number of bytes to be moved is count. The bytes are moved from low address to high address, so overlap is possible and in fact sometimes desired. CMOVE> The same as CMOVE above except that bytes are moved in the opposite direction, ie from high addresses to low addresses. \ 16 bit Stack Operations 02AUG83HHLSP@ Return the address of the next entry on the parameter stackSP! ( Warning, this is different from FIG Forth ) Sets the parameter stack pointer to the specified value. RP@ Return the address of the next entry on the return stack. RP! ( Warning, this is different from FIG Forth ) Sets the return stack pointer to the specified value. \ 16 bit Stack Operations 05MAR83HHLDROP Throw away the top element of the stack. DUP Duplicate the top element of the stack. SWAP Exchange the top two elements on the stack. OVER Copy the second element to the top. \ 16 bit Stack Operations 11MAR83HHLTUCK Tuck the first element under the second one. NIP Drop the second element from the stack. ROT Rotate the top three element, bringing the third to the top. -ROT The inverse of ROT. Rotates the top element to third place. FLIP Exhange the hi and low halves of a word. ?DUP Duplicate the top of the stack if it is non-zero. \ 16 bit Stack Operations 26Sep83mapR> Pops a value off of the return stack and pushes it onto the parameter stack. It is dangerous to use this randomly! >R Pops a value off of the parameter stack and pushes it onto return stack. It is dangerous to use this randomly! R@ Copies the value on the return stack to the parameter stack. PICK Reaches into the stack and grabs an element, copying it to the top of the stack. For example, if the stack has 1 2 3 Then 0 PICK is 3, 1 PICK is 2, and 2 PICK is 1. ROLL Similar to SHAKE and RATTLE. Should be avoided. 1 ROLL is SWAP, 2 ROLL is ROT, etc. ROLL can be useful, but it is slow. \ 16 bit Logical Operations 08Oct83mapAND Returns the bitwise AND of n1 and n2 on the stack. OR Returns the bitwise OR of n1 and n2 on the stack. XOR Returns the bitwise Exclusive Or of n1 and n2 on the stack. NOT Does a ones complement of the top. Equivalent to -1 XOR. TRUE FALSE Constants for clarity. \ 16 bit Logical Operations 23JUL83HHLCSET Set the contents of addr so that the bits that are 1 in n are also 1 in addr. Equivalent to DUP C@ ROT OR SWAP C! CRESET Set the contents of addr so the the bits that are 1 in n are zero in addr. Equivalent to DUP C@ ROT NOT AND SWAP C! CTOGGLE Flip the bits in addr by the value n. Equivalent to DUP C@ ROT XOR SWAP C! ON Set the contents of addr to TRUE OFF Set the contents of addr to FALSE \ 16 bit Arithmetic Operations 05MAR83HHL+ Add the top two numbers on the stack and return the result. NEGATE Turn the number into its negative. A twos complement op. - Subtracts n2 from n1 leaving the result on the stack. ABS Return the absolute value of the 16 bit integer on the stack +! Increment the value at addr by n. This is equivalent to the following: DUP @ ROT + SWAP ! but much faster. 0 1 Frequently used constants 2 3 Are faster and more code efficient. \ 16 bit Arithmetic Operations 07Oct83map2* Double the number on the Stack. 2/ Shift the number on the stack right one bit. Equivalent to division by 2 for positive numbers. U2/ 16 bit logical right shift. 8* Multiply the top of the stack by 8. 1+ Increment the top of the stack by one. 2+ Increment the top of the stack by two. 1- Decrement the top of the stack by one. 2- Decrement the top of the stack by two. \ 16 bit Arithmetic Operations Unsigned Multiply 03Apr84mapYou could write a whole book about multiplication and division, and in fact Knuth did. Suffice it to say that UM* is the basic multiplication primitive in Forth. It takes two unsigned 16 bitintegers and returns an unsigned 32 bit result. All other multiplication functions are derived from this primitive one. U*D is a synonym for UM* \ 16 bit Arithmetic Operations Unsigned Divide 08Oct83mapUM/MOD This is the division primitive in Forth. All other division operations are derived from it. It takes a double number, d1, and divides by by a single number n1. It leaves a remainder and a quotient on the stack. For a clearer understanding of arithmetic consult Knuth Volume 2 on Seminumerical Algorithms. YES Push a true flag on the stack and jump to next NO Push a false flag on the stack and jump to next \ 16 bit Comparison Operations 05MAR83HHL0< Returns true if top is negative, ie sign bit is on. 0= Returns True if top is zero, False otherwise. 0> Returns true if top is positive. 0<> Returns true if the top is non-zero, False otherwise. < Compare the top two elements on the stack as signed integers and return true if n1 < n2. = Returns true if the two elements on the stack are equal, False otherwise. > Compare the top two elements on the stack as signed integers and return true if n1 > n2. \ 16 bit Comparison Operations 08Oct83mapU< Compare the top two elements on the stack as unsigned integers and return true if the second is less than the first. Be sure to use U< whenever comparing addresses, or else strange things will happen beyond 32K. U> Compare the top two elements on the stack as unsigned integers. True if n1 > n2 unsigned. <> Returns true if the two element are not equal, else false. ?NEGATE Negate the second element if the top is negative. MIN Return the minimum of n1 and n2 MAX Return the maximum of n1 and n2 BETWEEN Return true if min <= n1 <= max, otherwise false. WITHIN Return true if min <= n1 < max, otherwise false. \ 32 bit Memory Operations 08Oct83map2@ Fetch a 32 bit value from addr. 2! Store a 32 bit value at addr. \ 32 bit Memory and Stack Operations 26Sep83map2DROP Drop the top two elements of the stack. 2DUP Duplicate the top two elements of the stack. 2SWAP Swap the top two pairs of numbers on the stack. You can use this operator to swap two 32 bit integers and preserve their meaning as double numbers. 2OVER Copy the second pair of numbers over the top pair. Behaves like 2SWAP for 32 bit integers. 3DUP Duplicate the top three elements of the stack. 4DUP Duplicate the top four elements of the stack. 2ROT rotates top three double numbers. \ 32 bit Arithmetic Operations 05MAR83HHLD+ Add the two double precision numbers on the stack and return the result as a double precision number. DNEGATE Same as NEGATE except for double precision numbers. S>D Take a single precision number and make it double precision by extending the sign bit to the upper half. DABS Return the absolute value of the 32 bit integer on the stack \ 32 bit Arithmetic Operations 03Apr84mapD2* 32 bit left shift. Equal to multiply by 2. D2/ 32 bit arithmetic right shift. Equivalent to divide by 2. D- Subtract the two double precision numbers. ?DNEGATE Negate the double number if the top is negative. \ 32 bit Comparison Operations 01Oct83mapD0= Compare the top double number to zero. True if d = 0 D= Compare the top two double numbers. True if d1 = d2 DU< Performs unsigned comparison of two double numbers. D< Compare the top two double numbers. True if d1 < d2 D> Compare the top two double numbers. True if d1 > d2 DMIN Return the lesser of the top two double numbers. DMAX Return the greater of the the top two double numbers. \ Mixed Mode Arithmetic 27Sep83mapThis does all the arithmetic you could possibly want and even more. I can never remember exactly what the order of the arguments is for any of these, except maybe * / and MOD, so I suggest you just try it when you are in doubt. That is one of the nice things about having an interpreter around, you can ask it questions anytime and it will tell you the answer. *D multiplys two singles and leaves a double. M/MOD divides a double by a single, leaving a single quotient and a single remainder. Division is floored. MU/MOD divides a double by a single, leaving a double quotient and a single remainder. Division is floored. \ 16 bit multiply and divide 27Sep83map */ is a particularly useful operator, as it allows you to do accurate arithmetic on fractional quantities. Think of it as multiplying n1 by the fraction n2/n3. The intermediate result is kept to full accuracy. Notice that this is not the same as * followed by /. See Starting Forth for more examples. \ Task Dependant USER Variables 24Mar84map TOS Saved during Task switching. ENTRY Jumped to during multitasking. LINK Points to next task in the circular queue SP0 Empty parameter stack for this task. RP0 Empty return stack for this task. DP Size of dictionary. Next available location. #OUT Number of characters sent since last CR. #LINE Number of CR's sent since last page. OFFSET Added to all block references. BASE The current numeric base for number input output. HLD Points to a converted character during numeric output. FILE Allows printing of one file while editing another. IN-FILE Allows printing of one file while editing another. PRINTING indicates whether printing is enabled. \ System VARIABLEs 24Mar84mapEMIT Sends a character to the output device. SCR Holds the screen number last listed or edited. PRIOR Points to the last vocabulary that was searched. DPL The decimal point location for number input. WARNING Checked by WARN for duplicate warnings. R# The cursor position during editing. HLD Points to a converted character during numeric output. LAST Points to the name of the most recently CREATEd word. CSP Used for compile time error checking. CURRENT New words are added to the CURRENT vocabulary. #VOCS The number of elements in the search order array. CONTEXT The array specifying the search order. \ System Variables 02AUG83HHL'TIB Points to characters entered by user. WIDTH Number of characters to keep in name field. VOC-LINK Points to the most recently defined vocabulary. BLK If non-zero, the block number we are interpreting. >IN Number of characters interpreted so far. SPAN Number of characters input by EXPECT. #TIB Used by WORD, when interpreting from the terminal. END? True if input stream exhausted, else false. \ Devices Strings 02AUG83HHLBL BS BELL Names for BLank, BackSpace, and BELL CAPS If true, then convert names to upper case FILL FILL the string starting at start-addr for count bytes with the character char. Both BLANK and ERASE are special cases of FILL. ERASE Fill the string with zeros BLANK Fill the string with blanks COUNT Given the address on the stack, returns the address plus one and the byte at that address. Useful for strings. LENGTH Given the address on the stack, returns the address plus two and the two byte contents of the address. MOVE Move the specified bytes without overlapping. \ Devices Strings 08Oct83mapUPC Convert a Char to upper Case UPPER Take the string at the specified address and convert it to upper case. It converts the string in place, so be sure to make a copy of the original if you need to use it later. HERE Return the address of the top of the dictionary PAD Floating Temporary Storage area. -TRAILING Return the address and length of the given string ignoring trailing blanks. \ Devices Strings 26Sep83mapCOMP This performs a string compare. If the two strings are equal, then COMPARE returns 0. If the two strings differ, then COMPARE returns -1 or +1. -1 is returned if string 1 is less than string 2. +1 is returned if string 1 is greater than string 2. All comparisons are relative to ASCII order. The code on this screen handles the case when upper/lower case is deemed significant. Thus lower case a does not match upper case A. \ Devices Strings 03Apr84map>UPPER A subroutine which converts the character in D6 to upper case.CAPS-COMP The code on this screen handles the case where case is not significant. Each character is converted to upper case before the comparison is made. Thus, lower case a and upper case A are considered identical. COMPARE Performs a string compare. If CAPS is true, characters from both strings are converted to upper case before comparing. \ Devices Terminal IO via CP/M BIOS 13Apr84mapBDOS Load up the registers and do a CP/M system call return the result placed in the A register on the stack. BIOS Load up the registers and do a CP/M Bios call. return the result placed in the A register on the stack (KEY?) Returns true if the user pressed a key, otherwise false. (KEY) Pauses until a key is ready, and returns it on the stack. (CONSOLE) Sends the character to the terminal. \ Devices Terminal Output 19Apr84mapKEY? Usually set to (KEY?), to sense keyboard status. KEY Usually set to (KEY) to get a character from the user. CR Typically set to CRLF, above. PR-STAT Return printer status, if implemented, else TRUE (PRINT) The value of the DEFERRED word EMIT when you want to send a character to the printer. (EMIT) sends a character to both the console and the printer. CRLF Sends a carriage return line feed sequence. TYPE Display the given string on the terminal. SPACE Send a space to the terminal SPACES Send a set of spaces to the terminal BACKSPACES Send a set of Backspaces to the terminal. BEEP Ring the bell on the terminal \ Devices System Dependent Control Characters 05Oct83mapBS-IN If at beginning of line, beep, otherwise back up 1. (DEL-IN) If at beginning of line, beep, otherwise back up and erase 1.BACK-UP Wipe out the current line by overwriting it with spaces. RES-IN Reset the system to a relatively clean state. P-IN Toggle the printer on or off \ Devices Terminal Input 16FEB84MAPCR-IN Finish input and remember the number of chars in SPAN (CHAR) Process an ordinary character by appending it to the buffer. CHAR is usually (CHAR). Executed for most characters. DEL-IN is usually (DEL-IN). Executed for delete characters. CC Points to current control character table. CC-FORTH Handle each control character as a special case. This generates an execution array which is indexed into by EXPECT to do the right thing when it receives a control character. \ Devices Terminal Input 29Sep83mapEXPECT Get a string from the terminal and place it in the buffer provided. Performs a certain amount of line editing. Saves the number of characters input in the Variable SPAN. Processes control characters per the array pointed to by CC. TIB Leaves address of text input buffer. QUERY Get more input from the user and place it at TIB. \ Devices BLOCK I/O 11Mar84mapThese variables are used by the BLOCK IO part of the system. Unlike FIG Forth the buffers are managed in a true least recently used scheme. The are maintained in memory as an array of 8 byte entries, whose format is defined at left. Whenever a BLOCK is referenced its pointer is moved to the head of the array, so the most recently used buffer is first. Thus multiple references are very fast. Also we have eliminated the need for a null at the end of each BLOCK buffer so that the size of a buffer is now exactly 1024 bytes. The format of entries in the buffer-pointer array is: 0-1 is Block Number 2-3 is Pointer to File 4-5 is Address of Buffer 6-7 is Update Flag BUFFER# Return the address the the nth buffer pointer. >END Return a pointer to just past the last buffer packet. >UPDATE Return a pointer to the update flag. \ Devices BLOCK I/O 04Apr84mapREAD-BLOCK performs physical read. WRITE-BLOCK performs physical write. .FILE (S adr -- ) print filename in fcb at adr. FILE? (S -- ) print name of current file. SWITCH exchange in-file and file. DOS vocabulary for native file system interface words. !FILES sets both file pointers to the specified file. DISK-ABORT (S fcb a n -- ) print error message and file name. ?DISK-ERROR (S fcb n -- ) report disk error. \ Devices BLOCK I/O 29Mar84mapFCB1 The default File Control Block CLR-FCB Initialize the specified FCB. SET-DMA CP/M system call to set dma address RECORD# Pointer to the specified Ramdom Record MAXREC# Pointer to the largest record allowed IN-RANGE Makes sure that the Random Record is within Range. Issues error message if it isn't. REC-READ Do a Random Access read REC-WRITE Do a Random Access write \ Devices BLOCK I/O 03Apr84mapSET-IO common set-up for file reads and writes. FILE-READ read 1024 bytes from a file. FILE-WRITE write 1024 bytes to a file. FILE-IO set block read and writes to use files. \ Devices BLOCK I/O 11Mar84map CAPACITY The number of blocks in the current file LATEST? For increased performance we first check to see if the block we want is the very first one in the list. If it is return the buffer address and false, and exit from the word that called us, namely ABSENT?. Otherwise we return as though nothing had happened. ABSENT? Search through the block/buffer list for a match. If it is found, bring the block packet to the top of the list and return a false flag and the address of the buffer. If the block is not found, return true, indicating it is absent, and the second parameter is garbage. \ Devices BLOCK I/O 01Apr84mapUPDATE Mark the most recently used buffer as modified. DISCARD Mark the most recently used buffer as unread. MISSING Writes the least recently used buffer to disk if it was modified, and moves all of the buffer pointers down by one, making the first one available for the new block. It then assigns the newly available buffer to the new block. (BUFFER) assigns a buffer to the specified block in the given file. No disk read is performed. Leaves the buffer address. BUFFER assigns a buffer to the specified block. No disk read is performed. Leaves the buffer address. (BLOCK) Leaves the address of a buffer containing the given block in the given file. Reads the disk if necessary. BLOCK Leaves the address of a buffer containing the given block. Reads the disk if necessary. IN-BLOCK like BLOCK, but for the IN-FILE. \ Devices BLOCK I/O 24Mar84mapEMPTY-BUFFERS First wipe out the data in the buffers. Next initialize the buffer pointers to point to the right addresses in memory and set all of the update flags to unmodified. SAVE-BUFFERS Write back all of the updated buffers to disk, and mark them as unmodified. Use this whenever you are worried about crashing or losing data. FLUSH Save and empties the buffers. Used for changing disks. The phrase " 0 BLOCK DROP " is a kludge for CP/M. Some systems do extra buffering in the BIOS, and you must access a new block to be sure the old one is actually written to diskVIEW# returns address of the view# field for this file. \ Devices BLOCK I/O 03Apr84map FILE-SIZE Return the size of the file in records. DOS-ERR? Returns true if a DOS error occurred. OPEN-FILE Open the current file and tell user if you can't. Determine the size of the file and save it for error check. DOS-FCB The address where the DOS puts a parsed FCB DEFAULT Opens the default file per the execute line. Move the already parsed file control block into FCB1, and open the file. This does nothing if no file was given. (LOAD) Load the screen number that is on the stack. The input stream is diverted from the terminal to the disk. LOAD Interpret a screen as if it were type in . \ Interactive Layer Number Input 30Sep83mapDIGIT Returns a flag indicating whether or not the character is a valid digit in the given base. If so, returns converted value and true, otherwise returns char and false. DOUBLE? Returns non-zero if period was encountered. CONVERT Starting with the unsigned double number ud1 and the string at adr1, convert the string to a number in the current base. Leave result and address of unconvertable digit on stack. \ Interactive Layer Number Input 06Oct83map(NUMBER?) Given a string containing at least one digit, convert it to a number. NUMBER? Convert the count delimited string at addr to a double number. NUMBER? takes into account a leading minus sign, and stores a pointer to the last delimiter in DPL. The string must end with a blank. Leaves a true flag if successful. (NUMBER) Convert the count delimited string at addr to a double number. (NUMBER) takes into account a leading minus sign, and stores a pointer to the last period in DPL. Note the string must end with a blank or an error message is issued. NUMBER Convert a string to a number. Normally (NUMBER) \ Interactive Layer Number Output 03Apr84mapHOLD Save the char for numeric output later. <# Start numeric conversion. #> Terminate numeric conversion. SIGN If n1 is negative insert a minus sign into the string. # Convert a single digit in the current base. #S Convert a number until it is finished. HEX All subsequent numeric IO will be in Hexadecimal. DECIMAL All subsequent numeric IO will be in Decimal. OCTAL All subsequent numeric IO will be in Octal. \ Interactive Layer Number Output 02AUG83HHL(U.) Convert an unsigned 16 bit number to a string. U. Output as an unsigned single number with trailing space. U.R Output as an unsigned single number right justified. (.) Convert a signed 16 bit number to a string. . Output as a signed single number with a trailing space. .R Output as a signed single number right justified. (UD.) Convert an unsigned double number to a string. UD. Output as an unsigned double number with a trailing spaceUD.R Output as an unsigned double number right justified. (D.) Convert a signed double number to a string. D. Output as a signed double number with a trailing space. D.R Output as a signed double number right justified. \ Interactive Layer Parsing 03Apr84mapDONE A common exit routine for SKIP and SCAN. SKIP Given the address and length of a string, and a character to look for, run through the string while we continue to find the character. Leave the address of the mismatch and the length of the remaining string. SCAN Given the address and length of a string, and a character to look for, run through the string until we find the character. Leave the address of the match and the length of the remaining string. \ Interactive Layer Parsing 01Oct83map/STRING Index into the string by n. Returns addr+n and len-n. PLACE Move the characters at from to to with a preceding length byte of len. (SOURCE) Returns the string to be scanned. This is the default value of the deferred word SOURCE. SOURCE Return a string from the current input stream. PARSE-WORD Scan the input stream until char is encountered. Skip over leading chars. Update >IN pointer. Leaves the address and length of the enclosed string. PARSE Scan the input stream until char is encountered. Update >IN pointer. Leaves the address and length of the enclosed string. \ Interactive Layer Parsing 03Apr84map'WORD Leaves the same address as WORD. In this system, 'WORD is the same as HERE. WORD Parse the input stream for char and return a count delimited string at here. Note there is always a blank following it. >TYPE TYPE for multitasking systems. .( Type the following string on the terminal. ( The Forth Comment Character. The input stream is skipped until a ) is encountered. \S comment to end of screen. \ Interactive Layer Dictionary 03Jun84mapTRAVERSE Run through a name field in the specified direction. Terminate when a byte whose high order bit is on is detected.DONE? True if the input stream is exhaused or state doesn't match FORTH-83 Let's hope so. \ Interactive Layer Dictionary 08Oct83mapN>LINK Go from name field to link field. L>NAME Go from link field to name field. BODY> Go from body to code field. NAME> Go from name field to code field. LINK> Go from link field to code field. >BODY Go from code field to body. >NAME Go from code field to name field. >LINK Go from code field to link field. >VIEW Go from code field to view field. VIEW> Go from view field to code field. HASH Given a string address and a pointer to a set of vocabulary chains, returns the actual thread. Uses the first character of the string to determine which thread. \ Interactive Layer Dictionary 08Oct83map(FIND) Does a search of the dictionary based on a pointer to a vocabulary thread and a string. If it finds the string in the chain, it returns a pointer to the CFA field inside the header. This field contains the code field address of the body. If it was an immediate word the flag returned is a 1. If it is non-immediate the flag returned is a -1. If the name was not found, the string address is returned along with a flag of zero. Note that links point to links, and are absolute addresses. \ Interactive Layer Dictionary 03Apr84map#THREADS The number of seperate linked lists per vocabulary. FIND Run through the vocabulary list searching for the name whose address is supplied on the stack. If the name is found, return the code field address of the name and a non-zero flag. The flag is -1 if the word is non-immediate and 1 if it is immediate. If the name is not found, the string address is returned along with a false flag. ?UPPERCASE Convert the given string to upper case if CAPS is true. DEFINED Look up the next word in the input stream. Return true if it exists, otherwise false. Maybe ignore case. \ Interactive Layer Interpreter 05MAR83HHL?STACK Check for parameter stack underflow or overflow and issue appropriate error message if detected. STATUS Indicate the current status of the system. INTERPRET The Forth Interpret Loop. If the next word is defined, execute it, otherwise convert it to a number and push it onto the stack. \ Extensible Layer Compiler 16Feb84mapALLOT Allocate more space in the dictionary , Set the contents of the dictionary value on the stack C, Same as , except uses an 8 bit value ALIGN Used to force even addresses. EVEN Makes the top of the stack an EVEN number. COMPILE Compile the following word when this def. executes IMMEDIATE Mark the last Header as an Immediate word. LITERAL Compile the single integer from the stack as a literal DLITERAL Compile the double integer from the stack as a literal. ASCII Compile the next character in the input stream as a literal Ascii integer. CONTROL Compile the next character in the input stream as a literal Ascii Control Character. \ Extensible Layer Compiler 08Oct83mapCRASH Default routine called by execution vectors. ?MISSING Tell user the word does not exist. ' Return the code field address of the next word ['] Like ' only used while compiling [COMPILE] Force compilation of an immediate word (") Return the address and length of the inline string (.") Type the inline string. Skip over it. ," Add the following text till a " to the dictionary. ." Compile the string to be typed out later. " Compile the string, return pointer later. \ Interactive Layer Dictionary 27Sep83mapFENCE Limit address for forgetting. TRIM (S faddr voc-addr -- ) Change the 4 hash pointers in a vocabulary so that they are all less than a specified value, faddr. (FORGET) (S code-addr relative-link-addr -- ) Forgets part of the dictionary. Both the code address and the header address are specified, and may be independant. (FORGET) resets all of the links and releases the space. FORGET (S -- ) Forget all of the code and headers before the next word. \ Extensible Layer Compiler 11Mar84mapWHERE Locates the screen and position following an error. ?ERROR Maybe indicate an error. Change this to alter ABORT" (?ERROR) Default for ?ERROR. Conditionally execute WHERE and type message. (ABORT") The Runtime code compiled by ABORT". Uses ERROR, and updates return stack. ABORT" If the flag is true, issue an error message and quit. ABORT Stop the system and indicate an error. \ Extensible Layer Structures 03Apr84map?CONDITION Simple compile time error checking. Usually adequate >MARK Set up for a Forward Branch >RESOLVE Resolve a Forward Branch MARK Set up a forward Branch with Error Checking ?>RESOLVE Resolve a forward Branch with Error Checking ? and ?< words to > and < words, and all of the 2DUPs to DUPs and the 2SWAPs to SWAPs. The rest should stay the same. \ Extensible Layer Defining Words 03Apr84map,VIEW Calculate and compile the VIEW field of the header. "CREATE Use the string at str to make a header, and initialize the code field. First we lay down the view field. Next we lay down an empty link field. We set up LAST so that it points to our name field, and check for duplicates. Next we link ourselves into the correct thread and delimit the name field bits. Finally lay down the code field. CREATE Make a header for the next word in the input stream. \ Extensible Layer Defining Words 06MAR83HHL!CSP Save the current stack level for error checking. ?CSP Issue error message if stack has changed. HIDE Removes the Last definition from the Header Dictionary. REVEAL Replaces the Last definition in the Header Dictionary. (;USES) Set the code field to the contents of following cellASSEMBLER Define the vocabulary to be filled later. ;USES Similar to the traditional ;CODE except used when run time code has been previously defined. (;CODE) Set the code field to the address of the following. ;CODE Used for defining the run time portion of a defining word in low level code. DOES> Specifies the run time of a defining word in high level Forth. \ Extensible Layer Defining Words 23JUL83HHL[ Stop compiling and start interpreting ] The Compiling Loop. First sets Compile State. Looks up the next word in the input stream and either executes it or compiles it depending upon whether or not it is immediate. If the word is not in the dictionary, it converts it to a number, either single or double precision depending on whether or not any punctuation was present. Continues until input stream is empty or state changes. : Defines a colon definition. The definition is hidden until it is completed, or the user desires recursion. The runtime for : adds a nesting level. ; Terminates a colon definition. Compiles the runtime code to remove a nesting level, and changes STATE so that compilation will terminate. \ Extensible Layer Defining Words 07SEP83HHLRECURSIVE Allow the current definition to be self referencing CONSTANT A defining word that creates constants. At runtime the value of the constant is placed on the stack. VARIABLE A defining word to create variables. At runtime the address of the variable is placed on the stack. DEFER Defining word for execution vectors. These are initially set to display an error message. They are initialized with IS. VOCABULARY Defines a new Forth vocabulary. VOC-LINK is a chain in temporal order and used by FORGET. At runtime a vocabulary changes the search order by setting CONTEXT. DEFINITIONS Subsequent definitions will be placed into CURRENT. \ Extensible Layer Defining Words 06Oct83map2CONSTANT Create a double number constant. This is defined for completeness, but never used, so the code field is discarded.2VARIABLE Create a double length variable. This is defined for completeness, but never used, so the code field is discarded. as appropriate. AVOC A variable that hold the old CONTEXT vocabulary CODE is the defining word for FORTH assembler definitions. It saves the context vocabulary and hides the name. END-CODE terminates a code definition and restores vocs. \ Extensible Layer Defining Words 07SEP83HHL#USER Count of how many user variables are allocated USER Vocabulary that holds task versions of defining words ALLOT Allocate some space in the user area for a task. When used with CREATE, you can define arrays this way. CREATE Define a word that returns the address of the next available user memory location. VARIABLE Define a task type variable. This is similar to the old FIG version of USER. DEFER Defines an execution vector that is task local. \ Extensible Layer ReDefining Words 07SEP83HHL>IS Maps a code field into a data field. If the word is in the USER class of words, then the data address must be calculated relative to the current user pointer. Otherwise it is just the parameter field. (IS) The code compiled by IS. Sets the following DEFERred word to the address on the parameter stack. IS Depending on STATE, either sets the following DEFERred word immediatly or compiles the setting for later. \ Initialization High Level 24JUL83HHLRUN Allows for multiline compilation. Thus you may enter a : definition that spans several lines. QUIT The main loop in Forth. Gets more input from the terminal and Interprets it. Responds with OK if healthy. BOOT The very first high level word executed during cold startWARM Performs a warm start, jumped to by vector at hex 104 COLD The high level cold start code. For ordinary forth, BOOT should initialize and pass control to QUIT. \ Initialization High Level 24JUL83HHLINITIAL The screen number to load for an application. OK Loads in an application from the INITIAL screen START Used to compile from a file after meta compilation has finished. BYE Returns control to CP/M. First it moves the heads down next to the code such that the system is contiguous when saved. Calculates the size in pages. \ Initialization Low Level 06MAR83HHL WARM Initialize the warm start entry point in low memory and jump immediately into hi level COLD Initialize the cold start entry point in low memory Then calculate how much space is consumed by CP/M and round it down to an even HEX boundary for safety. We then patch FIRST and LIMIT with this value and calculate the locations of the return stack and the Terminal Input buffer. We also set up the initial parameter stack and finally call the Hi Level COLD start routine. \ Initialize User Variables 27JUL83HHLFinally we must initialize the user variables that were defined earlier. User variables are relocatable, and sit on the top of the dictionary in whatever task they occur in. They must be laid down in the exact same order as their definitions. \ Resident Tools 27Sep83mapDEPTH Returns the number of items on the parameter stack .S Displays the contents of the parameter stack non destructively. Very useful when debugging. .ID Display the variable length name whose name field address is on the stack. If it is shorter than its count, it is padded with underscores. Only valid Ascii is typed. DUMP A primitive little dump routine to help you debug after you have changed the system source and nothing works any more. These words are in the reference word sets, 29Sep83mapand are only include for completeness. We prefer to use RECURSIVE rather than RECURSE. ( See RECURSIVE ) \ Resolve Forward References 06MAR83HHLWe must resolve the forward references that were required in the Meta Compiler. These are all run time code which wasn't known at the time the meta compiling version was defined. Theseare all either defining words or special case immediate words. \ Resolve Forward References 06MAR83HHLThese are forward references that were generated in the course of compiling the system source. Most of these are here because (DO) (?DO) and ROLL are written in high level and are defined very early in the system. While forward references should be avoided when possible, they should not be shunned as a matter of dogma. Since the meta compiler makes it easy to create and resolve forward references, why not take advantage of it when you need to. \ Initialize DEFERred words 03Apr84mapIn order to run, we must initialize all of the defferred words that were defined to something meaningful. Deferred words are also known as execution vectors. The most important execution vectors in the system are listed here. You can certainly createyour own with the defining word DEFER. Be sure you initialize them however, or else you will surely crash. \ Initialize Variables 20Apr84mapInitialize the CURRENT vocabulary to point to FORTH Initialize the CONTEXT vocabulary to point to FORTH Initialize the Threads in the Forth vocabulary The value of DP-BODY is only now know, so we must init it here The rest of the variables that are initialize are ordinary variables, which are resident in the dictionary, and must be correct upon cold boot. You can change some of these depending on how you want your system to come up initially. \ The Rest is Silence 26Sep83map*************************************************************