Implemented \ comments as a word, implemented [CHAR]
[forth.jl.git] / src / lib.4th
index eae7a5d..955cadf 100644 (file)
@@ -1,3 +1,10 @@
+: \ IMMEDIATE
+        KEY
+        10 = 0BRANCH [ -5 , ]
+; \ 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 @ - ;
 
 : '\n' 10 ;
 : BL 32 ;
 
-: LITERAL IMMEDIATE ' LIT , , ;
+: 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 ;
+: [CHAR] IMMEDIATE
+    CHAR
+    ['] LIT , ,
+;
 
 : CR '\n' emit ;
 : SPACE BL emit ;
@@ -51,7 +60,7 @@
 \ CONTROL STRUCTURES ----------------------------------------------------------------------
 
 : IF IMMEDIATE
-        ' 0BRANCH ,     \ compile 0BRANCH
+        ['] 0BRANCH ,     \ compile 0BRANCH
         HERE @          \ save location of the offset on the stack
         0 ,             \ compile a dummy offset
 ;
@@ -63,7 +72,7 @@
 ;
 
 : ELSE IMMEDIATE
-        ' BRANCH ,      \ definite branch to just over the false-part
+        ['] BRANCH ,      \ definite branch to just over the false-part
         HERE @          \ save location of the offset on the stack
         0 ,             \ compile a dummy offset
         SWAP            \ now back-fill the original (IF) offset
 ;
 
 : UNTIL IMMEDIATE
-        ' 0BRANCH ,     \ compile 0BRANCH
+        ['] 0BRANCH ,     \ compile 0BRANCH
         HERE @ -        \ calculate the offset from the address saved on the stack
         ,               \ compile the offset here
 ;
 
 : AGAIN IMMEDIATE
-        ' BRANCH ,      \ compile BRANCH
+        ['] BRANCH ,      \ compile BRANCH
         HERE @ -        \ calculate the offset back
         ,               \ compile the offset here
 ;
 
 : WHILE IMMEDIATE
-        ' 0BRANCH ,     \ compile 0BRANCH
+        ['] 0BRANCH ,     \ compile 0BRANCH
         HERE @          \ save location of the offset2 on the stack
         0 ,             \ compile a dummy offset2
 ;
 
 : REPEAT IMMEDIATE
-        ' BRANCH ,      \ compile BRANCH
+        ['] BRANCH ,      \ compile BRANCH
         SWAP            \ get the original offset (from BEGIN)
         HERE @ - ,      \ and compile it after BRANCH
         DUP
 ;
 
 : UNLESS IMMEDIATE
-        ' NOT ,         \ compile NOT (to reverse the test)
+        ['] NOT ,         \ compile NOT (to reverse the test)
         [COMPILE] IF    \ continue by calling the normal IF
 ;
 
 : DO IMMEDIATE
-        ' LIT , -1 , [COMPILE] IF
-        ' >R , ' >R ,
-        ' LIT , HERE @ 0 , ' >R ,
+        ['] LIT , -1 , [COMPILE] IF
+        ['] >R , ['] >R ,
+        ['] LIT , HERE @ 0 , ['] >R ,
         HERE @
 ;
 
 : ?DO IMMEDIATE
-        ' 2DUP , ' - , [COMPILE] IF
-        ' >R , ' >R ,
-        ' LIT , HERE @ 0 , ' >R ,
+        ['] 2DUP , ['] - , [COMPILE] IF
+        ['] >R , ['] >R ,
+        ['] LIT , HERE @ 0 , ['] >R ,
         HERE @
 ;
 
 : J RSP@ 6 - @ ;
 
 : ?LEAVE IMMEDIATE
-        ' 0BRANCH , 13 ,
-        ' R> , ' RDROP , ' RDROP ,
-        ' LIT ,  HERE @ 7 + , ' DUP , ' -ROT , ' - , ' SWAP , ' ! ,
-        ' BRANCH ,
+        ['] 0BRANCH , 13 ,
+        ['] R> , ['] RDROP , ['] RDROP ,
+        ['] LIT ,  HERE @ 7 + , ['] DUP , ['] -ROT , ['] - , ['] SWAP , ['] ! ,
+        ['] BRANCH ,
         0 ,
 ;
 
 : LEAVE IMMEDIATE
-        ' LIT , -1 ,
+        ['] LIT , -1 ,
         [COMPILE] ?LEAVE
 ;
 
 : +LOOP IMMEDIATE
-        ' DUP , \ Store copy of increment
+        ['] DUP , \ Store copy of increment
 
-        ' R> , ' SWAP , ' R> , ' SWAP , ' R> , ' SWAP , ' + , ' 2DUP , ' - ,
-        ' SWAP , ' >R , ' SWAP , ' >R , ' SWAP , ' >R ,
+        ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] + , ['] 2DUP , ['] - ,
+        ['] SWAP , ['] >R , ['] SWAP , ['] >R , ['] SWAP , ['] >R ,
 
         \ Condition differently depending on sign of increment
-        ' SWAP , ' 0>= , [COMPILE] IF
-            ' 0<= ,
+        ['] SWAP , ['] 0>= , [COMPILE] IF
+            ['] 0<= ,
         [COMPILE] ELSE
-            ' 0> ,
+            ['] 0> ,
         [COMPILE] THEN
 
         \ Branch back to begining of loop kernel
-        ' 0BRANCH , HERE @ - ,
+        ['] 0BRANCH , HERE @ - ,
 
         \ Clean up
-        ' RDROP , ' RDROP , ' RDROP ,
+        ['] RDROP , ['] RDROP , ['] RDROP ,
 
         \ Record address of loop end for any LEAVEs to use
         HERE @ SWAP !
 
         [COMPILE] ELSE
-            ' 2DROP , \ Clean up if loop was entirely skipped (?DO)
+            ['] 2DROP , \ Clean up if loop was entirely skipped (?DO)
         [COMPILE] THEN
 ;
 
 : LOOP IMMEDIATE
-        ' LIT , 1 ,
+        ['] LIT , 1 ,
         [COMPILE] +LOOP
 ;
 
+
+\ CASE ------------------------------------------------------------------------
+
+: CASE IMMEDIATE
+        0               \ push 0 to mark the bottom of the stack
+;
+
+: OF IMMEDIATE
+        ['] OVER ,        \ compile OVER
+        ['] = ,           \ compile =
+        [COMPILE] IF      \ compile IF
+        ['] DROP ,        \ compile DROP
+;
+
+: ENDOF IMMEDIATE
+        [COMPILE] ELSE    \ ENDOF is the same as ELSE
+;
+
+: ENDCASE IMMEDIATE
+        ['] DROP ,        \ compile DROP
+
+        \ keep compiling THEN until we get to our zero marker
+        BEGIN
+                ?DUP
+        WHILE
+                [COMPILE] THEN
+        REPEAT
+;
+
+
 \ COMMENTS ----------------------------------------------------------------------
 
 : ( IMMEDIATE
         1               \ allowed nested parens by keeping track of depth
         BEGIN
                 KEY             \ read next character
-                DUP '(' = IF    \ open paren?
+                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
+        [CHAR] < EMIT DEPTH U. [CHAR] > EMIT SPACE
         PSP0 @ 1+
         BEGIN
                 DUP PSP@ 2 - <=
 
 ( 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 -- )
 
 : S" IMMEDIATE          ( -- addr len )
         STATE @ IF      ( compiling? )
-                ' LITSTRING ,   ( compile LITSTRING )
+                ['] LITSTRING ,   ( compile LITSTRING )
                 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 '"' <>
+                        DUP [CHAR] " <>
                 WHILE
                         C,              ( copy character )
                 REPEAT
                 KEY DROP
                 BEGIN
                         KEY
-                        DUP '"' <>
+                        DUP [CHAR] " <>
                 WHILE
                         OVER C!         ( save next character )
                         1+              ( increment address )
 ;
 
 : ." 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. )
+        ['] TELL ,      ( compile the final TELL )
 ;
 
+: .( 
+        KEY DROP
+        BEGIN
+                KEY
+                DUP [CHAR] ) = IF
+                        DROP    ( drop the double quote character )
+                        EXIT    ( return from this function )
+                THEN
+                EMIT
+        AGAIN
+;
+
+
 ( CONSTANTS AND VARIABLES ------------------------------------------------------ )
 
 : CONSTANT
-        WORD            ( get the name (the name follows CONSTANT) )
-        CREATE          ( make the dictionary entry )
+        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 )
+        ['] LIT ,       ( append the codeword LIT )
+        ,               ( append the value on the top of the stack )
+        ['] EXIT ,      ( append the codeword EXIT )
 ;
 
-: ALLOT         ( n -- addr )
-        HERE @ SWAP     ( here n )
+: ALLOT         ( n -- )
         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
 ;
 
 : VARIABLE
+        CREATE
         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
-        WORD CREATE     ( 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 CREATE     ( make the dictionary entry (the name follows VALUE) )
+        WORD HEADER     ( make the dictionary entry (the name follows VALUE) )
         DOCOL ,         ( append DOCOL )
-        ' LIT ,         ( append the codeword LIT )
+        ['] LIT ,       ( append the codeword LIT )
         ,               ( append the initial value )
-        ' EXIT ,        ( append the codeword EXIT )
+        ['] EXIT ,      ( append the codeword EXIT )
 ;
 
 : TO IMMEDIATE  ( n -- )
         >DFA            ( get a pointer to the first data field (the 'LIT') )
         1+              ( increment to point at the value )
         STATE @ IF      ( compiling? )
-                ' LIT ,         ( compile LIT )
+                ['] LIT ,         ( compile LIT )
                 ,               ( compile the address of the value )
-                ' ! ,           ( compile ! )
+                ['] ! ,           ( compile ! )
         ELSE            ( immediate mode )
                 !               ( update it straightaway )
         THEN
         >DFA            ( get a pointer to the first data field (the 'LIT') )
         1+              ( increment to point at the value )
         STATE @ IF      ( compiling? )
-                ' LIT ,         ( compile LIT )
+                ['] LIT ,         ( compile LIT )
                 ,               ( compile the address of the value )
-                ' +! ,          ( compile +! )
+                ['] +! ,          ( compile +! )
         ELSE            ( immediate mode )
                 +!              ( update it straightaway )
         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 ------------------------------------------------------ )
 
         WHILE
                 SWAP 1+         ( addr len -- len addr+1 )
                 DUP @           ( len addr -- len addr char | get the next character)
-                EMIT            ( len addr char -- len addr | and print it)
+                DUP 32 >= OVER 127 <= AND IF
+                        EMIT    ( len addr char -- len addr | and print it)
+                ELSE
+                        BASE @ SWAP HEX
+                        ." \x" 0 .R
+                        BASE !
+                THEN
                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
         REPEAT
         2DROP           ( len addr -- )
         CR
 ;
 
+
 ( FORGET ---------------------------------------------------------------------- )
 
 : FORGET
 
 \ TODO!
 
-( CASE ------------------------------------------------------------------------ )
-
-: CASE IMMEDIATE
-        0               ( push 0 to mark the bottom of the stack )
-;
-
-: OF IMMEDIATE
-        ' OVER ,        ( compile OVER )
-        ' = ,           ( compile = )
-        [COMPILE] IF    ( compile IF )
-        ' DROP ,        ( compile DROP )
-;
-
-: ENDOF IMMEDIATE
-        [COMPILE] ELSE  ( ENDOF is the same as ELSE )
-;
-
-: ENDCASE IMMEDIATE
-        ' DROP ,        ( compile DROP )
-
-        ( keep compiling THEN until we get to our zero marker )
-        BEGIN
-                ?DUP
-        WHILE
-                [COMPILE] THEN
-        REPEAT
-;
-
 
 ( DECOMPILER ------------------------------------------------------------------ )
 
         DROP            ( at this point, the stack is: start-of-word end-of-word )
         SWAP            ( end-of-word start-of-word )
 
+        DUP >CFA @ CASE
+                DOCOL OF
+                        \ Colon definition
+                        [CHAR] : EMIT SPACE DUP ID. SPACE
+                        DUP ?IMMEDIATE IF ." IMMEDIATE " THEN CR
+                ENDOF
+                DOVAR OF
+                        \ Variable definition
+                        ." Variable " DUP ID. CR
+                        2DROP EXIT
+                ENDOF
+                DOCON OF
+                        \ Constant definition
+                        ." Constant " DUP ID. CR
+                        2DROP EXIT
+                ENDOF
+
+                \ Unknown codeword
+                ." Primitive or word with unrecognized codeword." CR 
+                DROP 2DROP EXIT
+        ENDCASE
+
         ( begin the definition with : NAME [IMMEDIATE] )
-        ':' EMIT SPACE DUP ID. SPACE
-        DUP ?IMMEDIATE IF ." IMMEDIATE " THEN
+        ( [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 )
 
                 DUP @           ( end start codeword )
 
                 CASE
-                ' LIT OF                ( is it LIT ? )
+                ['] LIT OF                ( is it LIT ? )
                         1+ DUP @                ( get next word which is the integer constant )
                         .                       ( and print it )
                 ENDOF
-                ' LITSTRING OF          ( is it LITSTRING ? )
-                        [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
+                ['] LITSTRING OF          ( is it LITSTRING ? )
+                        [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 )
+                        [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
-                ' 0BRANCH OF            ( is it 0BRANCH ? )
+                ['] 0BRANCH OF            ( is it 0BRANCH ? )
                         ." 0BRANCH ( "
                         1+ DUP @               ( print the offset )
                         .
                         ." ) "
                 ENDOF
-                ' BRANCH OF             ( is it BRANCH ? )
+                ['] BRANCH OF             ( is it BRANCH ? )
                         ." BRANCH ( "
                         1+ DUP @               ( print the offset )
                         .
                         ." ) "
                 ENDOF
-                ' ' OF                  ( is it ' (TICK) ? )
-                        [ CHAR ' ] LITERAL EMIT SPACE
+                ['] ['] OF                  ( is it ['] ? )
+                        ." ['] "
                         1+ DUP @               ( get the next codeword )
                         CFA>                    ( and force it to be printed as a dictionary entry )
                         ID. SPACE
                 ENDOF
-                ' EXIT OF               ( is it EXIT? )
+                ['] EXIT OF               ( is it EXIT? )
                         ( We expect the last word to be EXIT, and if it is then we don't print it
                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
                           of words, and then it needs to be printed. )
                 1+             ( end start+1 )
         REPEAT
 
-        ';' EMIT CR
+        [CHAR] ; EMIT CR
 
         2DROP           ( restore stack )
 ;
 
 
-( WELCOME MESSAGE ------------------------------------------------------------- )
-
-CR CR ."  --- TimForth initialized  --- "
-
+( MEMORY  ------------------------------------------------------------------ )
 
+: UNUSED  ( -- cells )
+        MEMSIZE HERE @ - ;