Reimplement CONSTANT, VARIABLE, VALUE using DOES>
[forth.jl.git] / src / lib.4th
index 28aa451..2312aeb 100644 (file)
@@ -1,3 +1,9 @@
+: \ IMMEDIATE
+        #TIB @ >IN !
+; \ We can now comment!
+
+\ BASIC DEFINITIONS  ----------------------------------------------------------------------
+
 : / /MOD SWAP DROP ;
 : MOD /MOD DROP ;
 : */ -ROT * SWAP / ;
 : FALSE 0 ;
 : NOT 0= ;
 
-: CELLS ; \ Allow for slightly more portable code
+\ Translate a number of cells into memory units
+\ (in our case 1 cell = 1 memory unit)
+: CELLS ;
+
+\ Since the smallest unit of memory in our system is 64 bits and since strings
+\ are stored as arrays of 64 bit integers, the character store/fetch words are
+\ just aliases of the standard store/fetch words.
+: C! ! ;
+: C@ @ ;
+: C, , ;
 
-: DEPTH PSP@ PSP0 - ;
+: DEPTH PSP@ PSP0 - ;
 
 : '\n' 10 ;
 : BL 32 ;
 
 : LITERAL IMMEDIATE ['] LIT , , ;
 
-: ':' [ CHAR : ] LITERAL ;
-: ';' [ CHAR ; ] LITERAL ;
-: '(' [ CHAR ( ] LITERAL ;
-: ')' [ CHAR ) ] LITERAL ;
-: '<' [ CHAR < ] LITERAL ;
-: '>' [ CHAR > ] LITERAL ;
-: '"' [ CHAR " ] LITERAL ;
-: 'A' [ CHAR A ] LITERAL ;
-: '0' [ CHAR 0 ] LITERAL ;
-: '-' [ CHAR - ] LITERAL ;
-: '.' [ CHAR . ] LITERAL ;
+: ' BL WORD FIND >CFA ;
+
+: CHAR BL WORD 1+ @ ;
+: [CHAR] IMMEDIATE
+    CHAR
+    ['] LIT , ,
+;
 
 : CR '\n' emit ;
 : SPACE BL emit ;
 
 : [COMPILE] IMMEDIATE
-        WORD            \ get the next word
+        BL WORD         \ get the next word
         FIND            \ find it in the dictionary
         >CFA            \ get its codeword
         ,               \ and compile that
         ,               \ compile it
 ;
 
-: DEBUGON TRUE DEBUG ! ;
-: DEBUGOFF FALSE DEBUG ! ;
-
 \ CONTROL STRUCTURES ----------------------------------------------------------------------
 
 : IF IMMEDIATE
         ['] 0BRANCH ,     \ compile 0BRANCH
-        HERE          \ save location of the offset on the stack
+        HERE          \ save location of the offset on the stack
         0 ,             \ compile a dummy offset
 ;
 
 : THEN IMMEDIATE
         DUP
-        HERE SWAP -   \ calculate the offset from the address saved on the stack
+        HERE SWAP -   \ calculate the offset from the address saved on the stack
         SWAP !          \ store the offset in the back-filled location
 ;
 
 : ELSE IMMEDIATE
         ['] BRANCH ,      \ definite branch to just over the false-part
-        HERE          \ save location of the offset on the stack
+        HERE          \ save location of the offset on the stack
         0 ,             \ compile a dummy offset
         SWAP            \ now back-fill the original (IF) offset
         DUP             \ same as for THEN word above
-        HERE SWAP -
+        HERE SWAP -
         SWAP !
 ;
 
 : BEGIN IMMEDIATE
-        HERE          \ save location on the stack
+        HERE          \ save location on the stack
 ;
 
 : UNTIL IMMEDIATE
         ['] 0BRANCH ,     \ compile 0BRANCH
-        HERE -        \ calculate the offset from the address saved on the stack
+        HERE -        \ calculate the offset from the address saved on the stack
         ,               \ compile the offset here
 ;
 
 : AGAIN IMMEDIATE
         ['] BRANCH ,      \ compile BRANCH
-        HERE -        \ calculate the offset back
+        HERE -        \ calculate the offset back
         ,               \ compile the offset here
 ;
 
 : WHILE IMMEDIATE
         ['] 0BRANCH ,     \ compile 0BRANCH
-        HERE          \ save location of the offset2 on the stack
+        HERE          \ save location of the offset2 on the stack
         0 ,             \ compile a dummy offset2
 ;
 
 : REPEAT IMMEDIATE
         ['] BRANCH ,      \ compile BRANCH
         SWAP            \ get the original offset (from BEGIN)
-        HERE - ,      \ and compile it after BRANCH
+        HERE - ,      \ and compile it after BRANCH
         DUP
-        HERE SWAP -   \ calculate the offset2
+        HERE SWAP -   \ calculate the offset2
         SWAP !          \ and back-fill it in the original location
 ;
 
 : DO IMMEDIATE
         ['] LIT , -1 , [COMPILE] IF
         ['] >R , ['] >R ,
-        ['] LIT , HERE 0 , ['] >R ,
-        HERE @
+        ['] LIT , HERE 0 , ['] >R ,
+        HERE
 ;
 
 : ?DO IMMEDIATE
         ['] 2DUP , ['] - , [COMPILE] IF
         ['] >R , ['] >R ,
-        ['] LIT , HERE 0 , ['] >R ,
-        HERE @
+        ['] LIT , HERE 0 , ['] >R ,
+        HERE
 ;
 
 : I RSP@ 3 - @ ;
 : ?LEAVE IMMEDIATE
         ['] 0BRANCH , 13 ,
         ['] R> , ['] RDROP , ['] RDROP ,
-        ['] LIT ,  HERE 7 + , ['] DUP , ['] -ROT , ['] - , ['] SWAP , ['] ! ,
+        ['] LIT ,  HERE 7 + , ['] DUP , ['] -ROT , ['] - , ['] SWAP , ['] ! ,
         ['] BRANCH ,
         0 ,
 ;
 ;
 
 : +LOOP IMMEDIATE
+
         ['] DUP , \ Store copy of increment
 
         ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] + , ['] 2DUP , ['] - ,
         [COMPILE] THEN
 
         \ Branch back to begining of loop kernel
-        ['] 0BRANCH , HERE - ,
+        ['] 0BRANCH , HERE - ,
 
         \ Clean up
         ['] RDROP , ['] RDROP , ['] RDROP ,
 
         \ Record address of loop end for any LEAVEs to use
-        HERE SWAP !
+        HERE SWAP !
 
         [COMPILE] ELSE
             ['] 2DROP , \ Clean up if loop was entirely skipped (?DO)
 : ( IMMEDIATE
         1               \ allowed nested parens by keeping track of depth
         BEGIN
-                KEY             \ read next character
-                DUP '(' = IF    \ open paren?
+                >IN @ #TIB @ >= IF      \ End of TIB?
+                        QUERY       \ Get next line
+                THEN
+
+                TIB >IN @ + @ 1 >IN +!
+                DUP [CHAR] ( = IF    \ open paren?
                         DROP            \ drop the open paren
                         1+              \ depth increases
                 ELSE
-                        ')' = IF        \ close paren?
+                        [CHAR] ) = IF        \ close paren?
                                 1-              \ depth decreases
                         THEN
                 THEN
 
         ( print the remainder )
         DUP 10 < IF
-                '0'             ( decimal digits 0..9 )
+                [CHAR] 0             ( decimal digits 0..9 )
         ELSE
                 10 -            ( hex and beyond digits A..Z )
-                'A'
+                [CHAR] A
         THEN
         +
         EMIT
         SWAP            ( u flag )
 
         IF                      ( was it negative? print the - character )
-                '-' EMIT
+                [CHAR] - EMIT
         THEN
 
         U.
 : . 0 .R SPACE ;
 
 : .S            ( -- )
-        '<' EMIT DEPTH U. '>' EMIT SPACE
-        PSP0 1+
+        [CHAR] < EMIT DEPTH U. [CHAR] > EMIT SPACE
+        PSP0 1+
         BEGIN
                 DUP PSP@ 2 - <=
         WHILE
 
 ( STRINGS ---------------------------------------------------------------------- )
 
-( Since the smallest unit of memory in our system is 64 bits and since strings
-  are stored as arrays of 64 bit integers, the character store/fetch words are
-  just aliases of the standard store/fetch words. )
-: C! ! ;
-: C@ @ ;
 
 ( Block copy, however, is important and novel: )
 : CMOVE ( src dest length -- )
 
 ( C, appends a byte to the current compiled word. )
 : C,
-        HERE C!
-        1 HERE +!
+        HERE C!
+        1 H +!
 ;
 
 : S" IMMEDIATE          ( -- addr len )
         STATE @ IF      ( compiling? )
                 ['] LITSTRING ,   ( compile LITSTRING )
-                HERE          ( save the address of the length word on the stack )
+                HERE          ( save the address of the length word on the stack )
                 0 ,             ( dummy length - we don't know what it is yet )
-                KEY DROP
+
                 BEGIN
-                        KEY             ( get next character of the string )
-                        DUP '"' <>
+                        >IN @ #TIB @ >= IF      \ End of TIB?
+                                QUERY           \ Get next line
+                        THEN
+
+                        TIB >IN @ + @ 1 >IN +!  \ Get char from TIB
+
+                        DUP [CHAR] " <>
                 WHILE
                         C,              ( copy character )
                 REPEAT
                 DROP            ( drop the double quote character at the end )
                 DUP             ( get the saved address of the length word )
-                HERE SWAP -   ( calculate the length )
+                HERE SWAP -   ( calculate the length )
                 1-              ( subtract 1 (because we measured from the start of the length word) )
                 SWAP !          ( and back-fill the length location )
         ELSE            ( immediate mode )
-                HERE          ( get the start address of the temporary space )
-                KEY DROP
+                HERE          ( get the start address of the temporary space )
+                
                 BEGIN
-                        KEY
-                        DUP '"' <>
+                        >IN @ #TIB @ >= IF      \ End of TIB?
+                                QUERY           \ Get next line
+                        THEN
+
+                        TIB >IN @ + @ 1 >IN +!  \ Get char from TIB
+
+                        DUP [CHAR] " <>
                 WHILE
                         OVER C!         ( save next character )
                         1+              ( increment address )
                 REPEAT
                 DROP            ( drop the final " character )
-                HERE -        ( calculate the length )
-                HERE          ( push the start address )
+                HERE -        ( calculate the length )
+                HERE          ( push the start address )
                 SWAP            ( addr len )
         THEN
 ;
 
 : ." IMMEDIATE          ( -- )
-        STATE @ IF      ( compiling? )
-                [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
-                ['] TELL ,        ( compile the final TELL )
-        ELSE
-                ( In immediate mode, just read characters and print them until we get
-                  to the ending double quote. )
-                KEY DROP
-                BEGIN
-                        KEY
-                        DUP '"' = IF
-                                DROP    ( drop the double quote character )
-                                EXIT    ( return from this function )
-                        THEN
-                        EMIT
-                AGAIN
-        THEN
+        [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
+        ['] TYPE ,      ( compile the final TYPE )
 ;
 
+: .( 
+        BEGIN
+                >IN @ #TIB @ >= IF      \ End of TIB?
+                        QUERY           \ Get next line
+                THEN
+
+                TIB >IN @ + @ 1 >IN +!  \ Get char from TIB
+
+                DUP [CHAR] ) = IF
+                        DROP    ( drop the double quote character )
+                        EXIT    ( return from this function )
+                THEN
+                EMIT
+        AGAIN
+;
+
+( Converts address of counted string into address of
+  start of string and length of string. )
+: COUNT ( addr1 -- addr2 n )
+        DUP 1+ SWAP @ ;
+
 
 ( CONSTANTS AND VARIABLES ------------------------------------------------------ )
 
 : CONSTANT
-        WORD HEADER     ( make dictionary entry (the name follows CONSTANT) )
-        DOCOL ,         ( append DOCOL (the codeword field of this word) )
-        ['] LIT ,       ( append the codeword LIT )
-        ,               ( append the value on the top of the stack )
-        ['] EXIT ,      ( append the codeword EXIT )
+        CREATE ,
+DOES>   @
 ;
 
-: ALLOT         ( n -- addr )
-        HERE @ SWAP     ( here n )
-        HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
+: ALLOT         ( n -- )
+        H +!         ( adds n to H, after this the old value of H is still on the stack )
 ;
 
 : VARIABLE
+        CREATE
         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
-        WORD HEADER     ( make the dictionary entry (the name follows VARIABLE) )
-        DOCOL ,         ( append DOCOL (the codeword field of this word) )
-        ['] LIT ,         ( append the codeword LIT )
-        ,               ( append the pointer to the new memory )
-        ['] EXIT ,        ( append the codeword EXIT )
 ;
 
-
 : VALUE         ( n -- )
-        WORD HEADER     ( make the dictionary entry (the name follows VALUE) )
-        DOCOL ,         ( append DOCOL )
-        ['] LIT ,       ( append the codeword LIT )
-        ,               ( append the initial value )
-        ['] EXIT ,      ( append the codeword EXIT )
+        CREATE ,
+DOES>   @
 ;
 
 : TO IMMEDIATE  ( n -- )
-        WORD            ( get the name of the value )
+        BL WORD         ( get the name of the value )
         FIND            ( look it up in the dictionary )
-        >DFA            ( get a pointer to the first data field (the 'LIT') )
-        1+              ( increment to point at the value )
+        >PFA            ( get a pointer to the first data field (the 'LIT') )
         STATE @ IF      ( compiling? )
                 ['] LIT ,         ( compile LIT )
                 ,               ( compile the address of the value )
 
 ( x +TO VAL adds x to VAL )
 : +TO IMMEDIATE
-        WORD            ( get the name of the value )
+        BL WORD         ( get the name of the value )
         FIND            ( look it up in the dictionary )
-        >DFA            ( get a pointer to the first data field (the 'LIT') )
-        1+              ( increment to point at the value )
+        >PFA            ( get a pointer to the first data field (the 'LIT') )
         STATE @ IF      ( compiling? )
                 ['] LIT ,         ( compile LIT )
                 ,               ( compile the address of the value )
         THEN
 ;
 
+( Fill u ints, starting at a, with the value b )
+: FILL          ( a u b -- )
+        -ROT OVER + SWAP ?DO
+                DUP I !
+        LOOP
+        DROP
+;
+
+: ERASE         ( a u -- )
+        0 FILL
+;
 
 ( PRINTING THE DICTIONARY ------------------------------------------------------ )
 
 ( FORGET ---------------------------------------------------------------------- )
 
 : FORGET
-        WORD FIND       ( find the word, gets the dictionary entry address )
+        BL WORD FIND    ( find the word, gets the dictionary entry address )
         DUP @ LATEST !  ( set LATEST to point to the previous word )
-        HERE !          ( and store HERE with the dictionary address )
+        H !          ( and store H with the dictionary address )
 ;
 
 ( DUMP ------------------------------------------------------------------------ )
 ;
 
 : SEE
-        WORD FIND       ( find the dictionary entry to decompile )
+        BL WORD DUP FIND     ( find the dictionary entry to decompile )
+
+        ?DUP 0= IF
+                ." Word '" COUNT TYPE ." ' not found in dictionary."
+                EXIT
+        THEN
+
+        SWAP DROP
 
         ( Now we search again, looking for the next word in the dictionary.  This gives us
           the length of the word that we will be decompiling.  (Well, mostly it does). )
-        HERE          ( address of the end of the last compiled word )
+        HERE          ( address of the end of the last compiled word )
         LATEST @        ( word last curr )
         BEGIN
                 2 PICK          ( word last curr word )
         DUP >CFA @ CASE
                 DOCOL OF
                         \ Colon definition
-                        ':' EMIT SPACE DUP ID. SPACE
+                        [CHAR] : EMIT SPACE DUP ID. SPACE
                         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN CR
                 ENDOF
                 DOVAR OF
         ENDCASE
 
         ( begin the definition with : NAME [IMMEDIATE] )
-        ( ':' EMIT SPACE DUP ID. SPACE
+        ( [CHAR] : EMIT SPACE DUP ID. SPACE
         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN CR 4 )
 
         4 SPACES
 
-        >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
+        >PFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
 
         ( now we start decompiling until we hit the end of the word )
         BEGIN           ( end start )
                         .                       ( and print it )
                 ENDOF
                 ['] LITSTRING OF          ( is it LITSTRING ? )
-                        [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
+                        [CHAR] S EMIT [CHAR] " EMIT SPACE ( print S"<space> )
                         1+ DUP @                ( get the length word )
                         SWAP 1+ SWAP            ( end start+1 length )
-                        2DUP TELL               ( print the string )
-                        '"' EMIT SPACE          ( finish the string with a final quote )
+                        2DUP TYPE               ( print the string )
+                        [CHAR] " EMIT SPACE          ( finish the string with a final quote )
                         +                       ( end start+1+len, aligned )
                         1-                     ( because we're about to add 4 below )
                 ENDOF
                 1+             ( end start+1 )
         REPEAT
 
-        ';' EMIT CR
+        [CHAR] ; EMIT CR
 
         2DROP           ( restore stack )
 ;
 ( MEMORY  ------------------------------------------------------------------ )
 
 : UNUSED  ( -- cells )
-        MEMSIZE HERE - ;
+        MEMSIZE HERE - ;