Added DO WHILE REPEAT, as well as . and .s
authorTim Vaughan <tgvaughan@gmail.com>
Mon, 25 Apr 2016 11:14:44 +0000 (23:14 +1200)
committerTim Vaughan <tgvaughan@gmail.com>
Mon, 25 Apr 2016 11:14:44 +0000 (23:14 +1200)
. and .s are now compiled from source, not
primitives!

src/forth.jl
src/lib.4th

index 78d8a53..3a2509b 100644 (file)
@@ -60,20 +60,24 @@ reg = Reg(mem[RSP0], mem[PSP0], 0, 0)
 
 # Stack manipulation functions
 
-type StackUnderflow <: Exception end
+type ParamStackUnderflow <: Exception end
+type ReturnStackUnderflow <: Exception end
+
+Base.showerror(io::IO, ex::ParamStackUnderflow) = print(io, "Parameter stack underflow.")
+Base.showerror(io::IO, ex::ReturnStackUnderflow) = print(io, "Return stack underflow.")
 
 getRSDepth() = reg.RSP - mem[RSP0]
 getPSDepth() = reg.PSP - mem[PSP0]
 
 function ensurePSDepth(depth::Int64)
     if getPSDepth()<depth
-        throw(StackUnderflow())
+        throw(ParamStackUnderflow())
     end
 end
 
 function ensureRSDepth(depth::Int64)
     if getRSDepth()<depth
-        throw(StackUnderflow())
+        throw(ReturnStackUnderflow())
     end
 end
 
@@ -888,9 +892,13 @@ BYE = defPrimWord("BYE", () -> begin
     return 0
 end)
 
+PROMPT = defPrimWord("PROMPT", () -> begin
+    println(" ok")
+end)
+
 NL = defPrimWord("\n", () -> begin
     if mem[STATE] == 0 && currentSource() == STDIN
-        println(" ok")
+        callPrim(mem[PROMPT])
     end
     return NEXT
 end, flags=F_IMMED)
@@ -917,6 +925,10 @@ EOF_WORD = defPrimWord("\x04", () -> begin
     pop!(sources)
 
     if length(sources)>0
+        if currentSource() == STDIN
+            callPrim(mem[PROMPT])
+        end
+
         return NEXT
     else
         return 0
@@ -952,15 +964,12 @@ function run()
             jmp = callPrim(jmp)
 
         catch ex
-            if isa(ex, StackUnderflow)
-                println("Stack underflow!")
+            showerror(STDOUT, ex)
+            println()
 
-                mem[NUMTIB] = 0
-                reg.IP = QUIT + 1
-                jmp = NEXT
-            else
-                rethrow(ex)
-            end
+            mem[NUMTIB] = 0
+            reg.IP = QUIT + 1
+            jmp = NEXT
         end
     end
 end
@@ -1028,16 +1037,6 @@ function printRS()
     end
 end
 
-DOT = defPrimWord(".", () -> begin
-    print(popPS())
-    return NEXT
-end)
-
-#DOTS = defPrimWord(".s", () -> begin
-#    printPS()
-#    return NEXT
-#end)
-
 DUMP = defPrimWord("DUMP", () -> begin
     count = popPS()
     addr = popPS()
index b7cd560..4b60a1e 100644 (file)
@@ -1,4 +1,4 @@
-: / /MOD SWAP DROP ;
+' 1+ , : / /MOD SWAP DROP ;
 : MOD /MOD DROP ;
 
 : '\n' 10 ;
 : FALSE 0 ;
 : NOT 0= ;
 
-: LITERAL IMMEDIATE ' LIT , , ;
+: CELLS ; \ Allow for slightly more portable code
 
-: ':'
-    [
-    CHAR :
-    ]
-    LITERAL
-;
+: DEPTH PSP@ PSP0 @ - ;
+
+: 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 ;
 
-\ While compiling, '[COMPILE] word' compiles 'word' if it would otherwise be IMMEDIATE.
 : [COMPILE] IMMEDIATE
         WORD            \ get the next word
         FIND            \ find it in the dictionary
         ,               \ and compile that
 ;
 
-\ RECURSE makes a recursive call to the current word that is being compiled.
-\
-\ Normally while a word is being compiled, it is marked HIDDEN so that references to the
-\ same word within are calls to the previous definition of the word.  However we still have
-\ access to the word which we are currently compiling through the LATEST pointer so we
-\ can use that to compile a recursive call.
 : RECURSE IMMEDIATE
         LATEST @        \ LATEST points to the word being compiled at the moment
         >CFA            \ get the codeword
         ,               \ compile it
 ;
 
-\       CONTROL STRUCTURES ----------------------------------------------------------------------
-\
-\ So far we have defined only very simple definitions.  Before we can go further, we really need to
-\ make some control structures, like IF ... THEN and loops.  Luckily we can define arbitrary control
-\ structures directly in FORTH.
-\
-\ Please note that the control structures as I have defined them here will only work inside compiled
-\ words.  If you try to type in expressions using IF, etc. in immediate mode, then they won't work.
-\ Making these work in immediate mode is left as an exercise for the reader.
-
-\ condition IF true-part THEN rest
-\       -- compiles to: --> condition 0BRANCH OFFSET true-part rest
-\       where OFFSET is the offset of 'rest'
-\ condition IF true-part ELSE false-part THEN
-\       -- compiles to: --> condition 0BRANCH OFFSET true-part BRANCH OFFSET2 false-part rest
-\       where OFFSET if the offset of false-part and OFFSET2 is the offset of rest
-
-\ IF is an IMMEDIATE word which compiles 0BRANCH followed by a dummy offset, and places
-\ the address of the 0BRANCH on the stack.  Later when we see THEN, we pop that address
-\ off the stack, calculate the offset, and back-fill the offset.
+\ CONTROL STRUCTURES ----------------------------------------------------------------------
+
 : IF IMMEDIATE
         ' 0BRANCH ,     \ compile 0BRANCH
         HERE @          \ save location of the offset on the stack
         SWAP !
 ;
 
-\ BEGIN loop-part condition UNTIL
-\       -- compiles to: --> loop-part condition 0BRANCH OFFSET
-\       where OFFSET points back to the loop-part
-\ This is like do { loop-part } while (condition) in the C language
 : BEGIN IMMEDIATE
         HERE @          \ save location on the stack
 ;
         ,               \ compile the offset here
 ;
 
-\ BEGIN loop-part AGAIN
-\       -- compiles to: --> loop-part BRANCH OFFSET
-\       where OFFSET points back to the loop-part
-\ In other words, an infinite loop which can only be returned from with EXIT
 : AGAIN IMMEDIATE
         ' BRANCH ,      \ compile BRANCH
         HERE @ -        \ calculate the offset back
         ,               \ compile the offset here
 ;
 
-\ BEGIN condition WHILE loop-part REPEAT
-\       -- compiles to: --> condition 0BRANCH OFFSET2 loop-part BRANCH OFFSET
-\       where OFFSET points back to condition (the beginning) and OFFSET2 points to after the whole piece of code
-\ So this is like a while (condition) { loop-part } loop in the C language
 : WHILE IMMEDIATE
         ' 0BRANCH ,     \ compile 0BRANCH
         HERE @          \ save location of the offset2 on the stack
         SWAP !          \ and back-fill it in the original location
 ;
 
-\ UNLESS is the same as IF but the test is reversed.
-\
-\ Note the use of [COMPILE]: Since IF is IMMEDIATE we don't want it to be executed while UNLESS
-\ is compiling, but while UNLESS is running (which happens to be when whatever word using UNLESS is
-\ being compiled -- whew!).  So we use [COMPILE] to reverse the effect of marking IF as immediate.
-\ This trick is generally used when we want to write our own control words without having to
-\ implement them all in terms of the primitives 0BRANCH and BRANCH, but instead reusing simpler
-\ control words like (in this instance) IF.
 : UNLESS IMMEDIATE
         ' NOT ,         \ compile NOT (to reverse the test)
         [COMPILE] IF    \ continue by calling the normal IF
 ;
 
-\       COMMENTS ----------------------------------------------------------------------
-\
-\ FORTH allows ( ... ) as comments within function definitions.  This works by having an IMMEDIATE
-\ word called ( which just drops input characters until it hits the corresponding ).
+: DO IMMEDIATE
+        ' >R , ' >R ,
+        HERE @
+;
+
+: LOOP IMMEDIATE
+        ' R> , ' R> , ' 1+ , ' 2DUP , ' - ,
+        ' SWAP , ' >R , ' SWAP , ' >R ,
+        ' 0<= , ' 0BRANCH ,
+        HERE @ - ,
+        ' RDROP , ' RDROP ,
+;
+
+
+\ COMMENTS ----------------------------------------------------------------------
+
 : ( IMMEDIATE
         1               \ allowed nested parens by keeping track of depth
         BEGIN
         DROP            \ drop the depth counter
 ;
 
-(
-        From now on we can use ( ... ) for comments.
-
-        STACK NOTATION ----------------------------------------------------------------------
-
-        In FORTH style we can also use ( ... -- ... ) to show the effects that a word has on the
-        parameter stack.  For example:
-
-        ( n -- )        means that the word consumes an integer (n) from the parameter stack.
-        ( b a -- c )    means that the word uses two integers (a and b, where a is at the top of stack)
-                                and returns a single integer (c).
-        ( -- )          means the word has no effect on the stack
-)
-
 ( Some more complicated stack examples, showing the stack notation. )
 : NIP ( x y -- y ) SWAP DROP ;
 : TUCK ( x y -- y x y ) DUP ROT ;
 : DECIMAL ( -- ) 10 BASE ! ;
 : HEX ( -- ) 16 BASE ! ;
 
-(
-        PRINTING NUMBERS ----------------------------------------------------------------------
-
-        The standard FORTH word . (DOT) is very important.  It takes the number at the top
-        of the stack and prints it out.  However first I'm going to implement some lower-level
-        FORTH words:
-
-        U.R     ( u width -- )  which prints an unsigned number, padded to a certain width
-        U.      ( u -- )        which prints an unsigned number
-        .R      ( n width -- )  which prints a signed number, padded to a certain width.
-
-        For example:
-                -123 6 .R
-        will print out these characters:
-                <space> <space> - 1 2 3
-
-        In other words, the number padded left to a certain number of characters.
-
-        The full number is printed even if it is wider than width, and this is what allows us to
-        define the ordinary functions U. and . (we just set width to zero knowing that the full
-        number will be printed anyway).
-
-        Another wrinkle of . and friends is that they obey the current base in the variable BASE.
-        BASE can be anything in the range 2 to 36.
+( Compute absolute value. )
+: ABS           ( n -- m)
+        dup 0< if
+                negate
+        then
+;
 
-        While we're defining . &c we can also define .S which is a useful debugging tool.  This
-        word prints the current stack (non-destructively) from top to bottom.
-)
+( PRINTING NUMBERS ---------------------------------------------------------------------- )
 
 ( This is the underlying recursive definition of U. )
 : U.            ( u -- )
         EMIT
 ;
 
+( This word returns the width (in characters) of an unsigned number in the current base )
+: UWIDTH        ( u -- width )
+        BASE @ /        ( rem quot )
+        ?DUP IF         ( if quotient <> 0 then )
+                RECURSE 1+      ( return 1+recursive call )
+        ELSE
+                1               ( return 1 )
+        THEN
+;
+
+: U.R           ( u width -- )
+        SWAP            ( width u )
+        DUP             ( width u u )
+        UWIDTH          ( width u uwidth )
+        -ROT            ( u uwidth width )
+        SWAP -          ( u width-uwidth )
+        ( At this point if the requested width is narrower, we'll have a negative number on the stack.
+          Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
+          a negative number of spaces anyway, so it's now safe to call SPACES ... )
+        SPACES
+        ( ... and then call the underlying implementation of U. )
+        U.
+;
+
+: .R            ( n width -- )
+        SWAP            ( width n )
+        DUP 0< IF
+                NEGATE          ( width u )
+                1               ( save a flag to remember that it was negative | width n 1 )
+                ROT             ( 1 width u )
+                SWAP            ( 1 u width )
+                1-              ( 1 u width-1 )
+        ELSE
+                0               ( width u 0 )
+                ROT             ( 0 width u )
+                SWAP            ( 0 u width )
+        THEN
+        SWAP            ( flag width u )
+        DUP             ( flag width u u )
+        UWIDTH          ( flag width u uwidth )
+        -ROT            ( flag u uwidth width )
+        SWAP -          ( flag u width-uwidth )
+
+        SPACES          ( flag u )
+        SWAP            ( u flag )
+
+        IF                      ( was it negative? print the - character )
+                '-' EMIT
+        THEN
+
+        U.
+;
+
+: U. U. SPACE ;
+
+: . 0 .R SPACE ;
+
+: .S            ( -- )
+        '<' EMIT DEPTH U. '>' EMIT SPACE
+        PSP0 @ 1+
+        BEGIN
+                DUP PSP@ 2 - <=
+        WHILE
+                DUP @ .
+                1+
+        REPEAT
+        DROP
+;
+
+( ? fetches the integer at an address and prints it. )
+: ? ( addr -- ) @ . ;
+
+( c a b WITHIN returns true if a <= c and c < b )
+: WITHIN
+        ROT             ( b c a )
+        OVER            ( b c a c )
+        <= IF
+                > IF            ( b c -- )
+                        TRUE
+                ELSE
+                        FALSE
+                THEN
+        ELSE
+                2DROP           ( b c -- )
+                FALSE
+        THEN
+;