Assembly code.
[jonesforth.git] / jonesforth.f
1 \ -*- text -*-
2 \       A sometimes minimal FORTH compiler and tutorial for Linux / i386 systems. -*- asm -*-
3 \       By Richard W.M. Jones <rich@annexia.org> http://annexia.org/forth
4 \       This is PUBLIC DOMAIN (see public domain release statement below).
5 \       $Id: jonesforth.f,v 1.14 2007-10-10 13:01:05 rich Exp $
6 \
7 \       The first part of this tutorial is in jonesforth.S.  Get if from http://annexia.org/forth
8 \
9 \       PUBLIC DOMAIN ----------------------------------------------------------------------
10 \
11 \       I, the copyright holder of this work, hereby release it into the public domain. This applies worldwide.
12 \
13 \       In case this is not legally possible, I grant any entity the right to use this work for any purpose,
14 \       without any conditions, unless such conditions are required by law.
15 \
16 \       SETTING UP ----------------------------------------------------------------------
17 \
18 \       Let's get a few housekeeping things out of the way.  Firstly because I need to draw lots of
19 \       ASCII-art diagrams to explain concepts, the best way to look at this is using a window which
20 \       uses a fixed width font and is at least this wide:
21 \
22 \<------------------------------------------------------------------------------------------------------------------------>
23 \
24 \       Secondly make sure TABS are set to 8 characters.  The following should be a vertical
25 \       line.  If not, sort out your tabs.
26 \
27 \               |
28 \               |
29 \               |
30 \
31 \       Thirdly I assume that your screen is at least 50 characters high.
32 \
33 \       START OF FORTH CODE ----------------------------------------------------------------------
34 \
35 \       We've now reached the stage where the FORTH system is running and self-hosting.  All further
36 \       words can be written as FORTH itself, including words like IF, THEN, .", etc which in most
37 \       languages would be considered rather fundamental.
38 \
39 \       Some notes about the code:
40 \
41 \       I use indenting to show structure.  The amount of whitespace has no meaning to FORTH however
42 \       except that you must use at least one whitespace character between words, and words themselves
43 \       cannot contain whitespace.
44 \
45 \       FORTH is case-sensitive.  Use capslock!
46
47 \ The primitive word /MOD (DIVMOD) leaves both the quotient and the remainder on the stack.  (On
48 \ i386, the idivl instruction gives both anyway).  Now we can define the / and MOD in terms of /MOD
49 \ and a few other primitives.
50 : / /MOD SWAP DROP ;
51 : MOD /MOD DROP ;
52
53 \ Define some character constants
54 : '\n' 10 ;
55 : BL   32 ; \ BL (BLank) is a standard FORTH word for space.
56
57 \ CR prints a carriage return
58 : CR '\n' EMIT ;
59
60 \ SPACE prints a space
61 : SPACE BL EMIT ;
62
63 \ The 2... versions of the standard operators work on pairs of stack entries.  They're not used
64 \ very commonly so not really worth writing in assembler.  Here is how they are defined in FORTH.
65 : 2DUP OVER OVER ;
66 : 2DROP DROP DROP ;
67
68 \ NEGATE leaves the negative of a number on the stack.
69 : NEGATE 0 SWAP - ;
70
71 \ Standard words for booleans.
72 : TRUE  1 ;
73 : FALSE 0 ;
74 : NOT   0= ;
75
76 \ LITERAL takes whatever is on the stack and compiles LIT <foo>
77 : LITERAL IMMEDIATE
78         ' LIT ,         \ compile LIT
79         ,               \ compile the literal itself (from the stack)
80         ;
81
82 \ Now we can use [ and ] to insert literals which are calculated at compile time.  (Recall that
83 \ [ and ] are the FORTH words which switch into and out of immediate mode.)
84 \ Within definitions, use [ ... ] LITERAL anywhere that '...' is a constant expression which you
85 \ would rather only compute once (at compile time, rather than calculating it each time your word runs).
86 : ':'
87         [               \ go into immediate mode (temporarily)
88         CHAR :          \ push the number 58 (ASCII code of colon) on the parameter stack
89         ]               \ go back to compile mode
90         LITERAL         \ compile LIT 58 as the definition of ':' word
91 ;
92
93 \ A few more character constants defined the same way as above.
94 : ';' [ CHAR ; ] LITERAL ;
95 : '(' [ CHAR ( ] LITERAL ;
96 : ')' [ CHAR ) ] LITERAL ;
97 : '"' [ CHAR " ] LITERAL ;
98 : 'A' [ CHAR A ] LITERAL ;
99 : '0' [ CHAR 0 ] LITERAL ;
100 : '-' [ CHAR - ] LITERAL ;
101 : '.' [ CHAR . ] LITERAL ;
102
103 \ While compiling, '[COMPILE] word' compiles 'word' if it would otherwise be IMMEDIATE.
104 : [COMPILE] IMMEDIATE
105         WORD            \ get the next word
106         FIND            \ find it in the dictionary
107         >CFA            \ get its codeword
108         ,               \ and compile that
109 ;
110
111 \ RECURSE makes a recursive call to the current word that is being compiled.
112 \
113 \ Normally while a word is being compiled, it is marked HIDDEN so that references to the
114 \ same word within are calls to the previous definition of the word.  However we still have
115 \ access to the word which we are currently compiling through the LATEST pointer so we
116 \ can use that to compile a recursive call.
117 : RECURSE IMMEDIATE
118         LATEST @        \ LATEST points to the word being compiled at the moment
119         >CFA            \ get the codeword
120         ,               \ compile it
121 ;
122
123 \       CONTROL STRUCTURES ----------------------------------------------------------------------
124 \
125 \ So far we have defined only very simple definitions.  Before we can go further, we really need to
126 \ make some control structures, like IF ... THEN and loops.  Luckily we can define arbitrary control
127 \ structures directly in FORTH.
128 \
129 \ Please note that the control structures as I have defined them here will only work inside compiled
130 \ words.  If you try to type in expressions using IF, etc. in immediate mode, then they won't work.
131 \ Making these work in immediate mode is left as an exercise for the reader.
132
133 \ condition IF true-part THEN rest
134 \       -- compiles to: --> condition 0BRANCH OFFSET true-part rest
135 \       where OFFSET is the offset of 'rest'
136 \ condition IF true-part ELSE false-part THEN
137 \       -- compiles to: --> condition 0BRANCH OFFSET true-part BRANCH OFFSET2 false-part rest
138 \       where OFFSET if the offset of false-part and OFFSET2 is the offset of rest
139
140 \ IF is an IMMEDIATE word which compiles 0BRANCH followed by a dummy offset, and places
141 \ the address of the 0BRANCH on the stack.  Later when we see THEN, we pop that address
142 \ off the stack, calculate the offset, and back-fill the offset.
143 : IF IMMEDIATE
144         ' 0BRANCH ,     \ compile 0BRANCH
145         HERE @          \ save location of the offset on the stack
146         0 ,             \ compile a dummy offset
147 ;
148
149 : THEN IMMEDIATE
150         DUP
151         HERE @ SWAP -   \ calculate the offset from the address saved on the stack
152         SWAP !          \ store the offset in the back-filled location
153 ;
154
155 : ELSE IMMEDIATE
156         ' BRANCH ,      \ definite branch to just over the false-part
157         HERE @          \ save location of the offset on the stack
158         0 ,             \ compile a dummy offset
159         SWAP            \ now back-fill the original (IF) offset
160         DUP             \ same as for THEN word above
161         HERE @ SWAP -
162         SWAP !
163 ;
164
165 \ BEGIN loop-part condition UNTIL
166 \       -- compiles to: --> loop-part condition 0BRANCH OFFSET
167 \       where OFFSET points back to the loop-part
168 \ This is like do { loop-part } while (condition) in the C language
169 : BEGIN IMMEDIATE
170         HERE @          \ save location on the stack
171 ;
172
173 : UNTIL IMMEDIATE
174         ' 0BRANCH ,     \ compile 0BRANCH
175         HERE @ -        \ calculate the offset from the address saved on the stack
176         ,               \ compile the offset here
177 ;
178
179 \ BEGIN loop-part AGAIN
180 \       -- compiles to: --> loop-part BRANCH OFFSET
181 \       where OFFSET points back to the loop-part
182 \ In other words, an infinite loop which can only be returned from with EXIT
183 : AGAIN IMMEDIATE
184         ' BRANCH ,      \ compile BRANCH
185         HERE @ -        \ calculate the offset back
186         ,               \ compile the offset here
187 ;
188
189 \ BEGIN condition WHILE loop-part REPEAT
190 \       -- compiles to: --> condition 0BRANCH OFFSET2 loop-part BRANCH OFFSET
191 \       where OFFSET points back to condition (the beginning) and OFFSET2 points to after the whole piece of code
192 \ So this is like a while (condition) { loop-part } loop in the C language
193 : WHILE IMMEDIATE
194         ' 0BRANCH ,     \ compile 0BRANCH
195         HERE @          \ save location of the offset2 on the stack
196         0 ,             \ compile a dummy offset2
197 ;
198
199 : REPEAT IMMEDIATE
200         ' BRANCH ,      \ compile BRANCH
201         SWAP            \ get the original offset (from BEGIN)
202         HERE @ - ,      \ and compile it after BRANCH
203         DUP
204         HERE @ SWAP -   \ calculate the offset2
205         SWAP !          \ and back-fill it in the original location
206 ;
207
208 \ UNLESS is the same as IF but the test is reversed.
209 \
210 \ Note the use of [COMPILE]: Since IF is IMMEDIATE we don't want it to be executed while UNLESS
211 \ is compiling, but while UNLESS is running (which happens to be when whatever word using UNLESS is
212 \ being compiled -- whew!).  So we use [COMPILE] to reverse the effect of marking IF as immediate.
213 \ This trick is generally used when we want to write our own control words without having to
214 \ implement them all in terms of the primitives 0BRANCH and BRANCH, but instead reusing simpler
215 \ control words like (in this instance) IF.
216 : UNLESS IMMEDIATE
217         ' NOT ,         \ compile NOT (to reverse the test)
218         [COMPILE] IF    \ continue by calling the normal IF
219 ;
220
221 \       COMMENTS ----------------------------------------------------------------------
222 \
223 \ FORTH allows ( ... ) as comments within function definitions.  This works by having an IMMEDIATE
224 \ word called ( which just drops input characters until it hits the corresponding ).
225 : ( IMMEDIATE
226         1               \ allowed nested parens by keeping track of depth
227         BEGIN
228                 KEY             \ read next character
229                 DUP '(' = IF    \ open paren?
230                         DROP            \ drop the open paren
231                         1+              \ depth increases
232                 ELSE
233                         ')' = IF        \ close paren?
234                                 1-              \ depth decreases
235                         THEN
236                 THEN
237         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
238         DROP            \ drop the depth counter
239 ;
240
241 (
242         From now on we can use ( ... ) for comments.
243
244         STACK NOTATION ----------------------------------------------------------------------
245
246         In FORTH style we can also use ( ... -- ... ) to show the effects that a word has on the
247         parameter stack.  For example:
248
249         ( n -- )        means that the word consumes an integer (n) from the parameter stack.
250         ( b a -- c )    means that the word uses two integers (a and b, where a is at the top of stack)
251                                 and returns a single integer (c).
252         ( -- )          means the word has no effect on the stack
253 )
254
255 ( Some more complicated stack examples, showing the stack notation. )
256 : NIP ( x y -- y ) SWAP DROP ;
257 : TUCK ( x y -- y x y ) DUP ROT ;
258 : PICK ( x_u ... x_1 x_0 u -- x_u ... x_1 x_0 x_u )
259         1+              ( add one because of 'u' on the stack )
260         4 *             ( multiply by the word size )
261         DSP@ +          ( add to the stack pointer )
262         @               ( and fetch )
263 ;
264
265 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
266 : SPACES        ( n -- )
267         BEGIN
268                 DUP 0>          ( while n > 0 )
269         WHILE
270                 SPACE           ( print a space )
271                 1-              ( until we count down to 0 )
272         REPEAT
273         DROP
274 ;
275
276 ( Standard words for manipulating BASE. )
277 : DECIMAL ( -- ) 10 BASE ! ;
278 : HEX ( -- ) 16 BASE ! ;
279
280 (
281         PRINTING NUMBERS ----------------------------------------------------------------------
282
283         The standard FORTH word . (DOT) is very important.  It takes the number at the top
284         of the stack and prints it out.  However first I'm going to implement some lower-level
285         FORTH words:
286
287         U.R     ( u width -- )  which prints an unsigned number, padded to a certain width
288         U.      ( u -- )        which prints an unsigned number
289         .R      ( n width -- )  which prints a signed number, padded to a certain width.
290
291         For example:
292                 -123 6 .R
293         will print out these characters:
294                 <space> <space> - 1 2 3
295
296         In other words, the number padded left to a certain number of characters.
297
298         The full number is printed even if it is wider than width, and this is what allows us to
299         define the ordinary functions U. and . (we just set width to zero knowing that the full
300         number will be printed anyway).
301
302         Another wrinkle of . and friends is that they obey the current base in the variable BASE.
303         BASE can be anything in the range 2 to 36.
304
305         While we're defining . &c we can also define .S which is a useful debugging tool.  This
306         word prints the current stack (non-destructively) from top to bottom.
307 )
308
309 ( This is the underlying recursive definition of U. )
310 : U.            ( u -- )
311         BASE @ /MOD     ( width rem quot )
312         ?DUP IF                 ( if quotient <> 0 then )
313                 RECURSE         ( print the quotient )
314         THEN
315
316         ( print the remainder )
317         DUP 10 < IF
318                 '0'             ( decimal digits 0..9 )
319         ELSE
320                 10 -            ( hex and beyond digits A..Z )
321                 'A'
322         THEN
323         +
324         EMIT
325 ;
326
327 (
328         FORTH word .S prints the contents of the stack.  It doesn't alter the stack.
329         Very useful for debugging.
330 )
331 : .S            ( -- )
332         DSP@            ( get current stack pointer )
333         BEGIN
334                 DUP S0 @ <
335         WHILE
336                 DUP @ U.        ( print the stack element )
337                 SPACE
338                 4+              ( move up )
339         REPEAT
340         DROP
341 ;
342
343 ( This word returns the width (in characters) of an unsigned number in the current base )
344 : UWIDTH        ( u -- width )
345         BASE @ /        ( rem quot )
346         ?DUP IF         ( if quotient <> 0 then )
347                 RECURSE 1+      ( return 1+recursive call )
348         ELSE
349                 1               ( return 1 )
350         THEN
351 ;
352
353 : U.R           ( u width -- )
354         SWAP            ( width u )
355         DUP             ( width u u )
356         UWIDTH          ( width u uwidth )
357         -ROT            ( u uwidth width )
358         SWAP -          ( u width-uwidth )
359         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
360           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
361           a negative number of spaces anyway, so it's now safe to call SPACES ... )
362         SPACES
363         ( ... and then call the underlying implementation of U. )
364         U.
365 ;
366
367 (
368         .R prints a signed number, padded to a certain width.  We can't just print the sign
369         and call U.R because we want the sign to be next to the number ('-123' instead of '-  123').
370 )
371 : .R            ( n width -- )
372         SWAP            ( width n )
373         DUP 0< IF
374                 NEGATE          ( width u )
375                 1               ( save a flag to remember that it was negative | width n 1 )
376                 ROT             ( 1 width u )
377                 SWAP            ( 1 u width )
378                 1-              ( 1 u width-1 )
379         ELSE
380                 0               ( width u 0 )
381                 ROT             ( 0 width u )
382                 SWAP            ( 0 u width )
383         THEN
384         SWAP            ( flag width u )
385         DUP             ( flag width u u )
386         UWIDTH          ( flag width u uwidth )
387         -ROT            ( flag u uwidth width )
388         SWAP -          ( flag u width-uwidth )
389
390         SPACES          ( flag u )
391         SWAP            ( u flag )
392
393         IF                      ( was it negative? print the - character )
394                 '-' EMIT
395         THEN
396
397         U.
398 ;
399
400 ( Finally we can define word . in terms of .R, with a trailing space. )
401 : . 0 .R SPACE ;
402
403 ( The real U., note the trailing space. )
404 : U. U. SPACE ;
405
406 ( ? fetches the integer at an address and prints it. )
407 : ? ( addr -- ) @ . ;
408
409 ( c a b WITHIN returns true if a <= c and c < b )
410 : WITHIN
411         ROT             ( b c a )
412         OVER            ( b c a c )
413         <= IF
414                 > IF            ( b c -- )
415                         TRUE
416                 ELSE
417                         FALSE
418                 THEN
419         ELSE
420                 2DROP           ( b c -- )
421                 FALSE
422         THEN
423 ;
424
425 ( DEPTH returns the depth of the stack. )
426 : DEPTH         ( -- n )
427         S0 @ DSP@ -
428         4-                      ( adjust because S0 was on the stack when we pushed DSP )
429 ;
430
431 (
432         ALIGNED takes an address and rounds it up (aligns it) to the next 4 byte boundary.
433 )
434 : ALIGNED       ( addr -- addr )
435         3 + 3 INVERT AND        ( (addr+3) & ~3 )
436 ;
437
438 (
439         ALIGN aligns the HERE pointer, so the next word appended will be aligned properly.
440 )
441 : ALIGN HERE @ ALIGNED HERE ! ;
442
443 (
444         STRINGS ----------------------------------------------------------------------
445
446         S" string" is used in FORTH to define strings.  It leaves the address of the string and
447         its length on the stack, (length at the top of stack).  The space following S" is the normal
448         space between FORTH words and is not a part of the string.
449
450         This is tricky to define because it has to do different things depending on whether
451         we are compiling or in immediate mode.  (Thus the word is marked IMMEDIATE so it can
452         detect this and do different things).
453
454         In compile mode we append
455                 LITSTRING <string length> <string rounded up 4 bytes>
456         to the current word.  The primitive LITSTRING does the right thing when the current
457         word is executed.
458
459         In immediate mode there isn't a particularly good place to put the string, but in this
460         case we put the string at HERE (but we _don't_ change HERE).  This is meant as a temporary
461         location, likely to be overwritten soon after.
462 )
463 ( C, appends a byte to the current compiled word. )
464 : C,
465         HERE @ C!       ( store the character in the compiled image )
466         1 HERE +!       ( increment HERE pointer by 1 byte )
467 ;
468
469 : S" IMMEDIATE          ( -- addr len )
470         STATE @ IF      ( compiling? )
471                 ' LITSTRING ,   ( compile LITSTRING )
472                 HERE @          ( save the address of the length word on the stack )
473                 0 ,             ( dummy length - we don't know what it is yet )
474                 BEGIN
475                         KEY             ( get next character of the string )
476                         DUP '"' <>
477                 WHILE
478                         C,              ( copy character )
479                 REPEAT
480                 DROP            ( drop the double quote character at the end )
481                 DUP             ( get the saved address of the length word )
482                 HERE @ SWAP -   ( calculate the length )
483                 4-              ( subtract 4 (because we measured from the start of the length word) )
484                 SWAP !          ( and back-fill the length location )
485                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
486         ELSE            ( immediate mode )
487                 HERE @          ( get the start address of the temporary space )
488                 BEGIN
489                         KEY
490                         DUP '"' <>
491                 WHILE
492                         OVER C!         ( save next character )
493                         1+              ( increment address )
494                 REPEAT
495                 DROP            ( drop the final " character )
496                 HERE @ -        ( calculate the length )
497                 HERE @          ( push the start address )
498                 SWAP            ( addr len )
499         THEN
500 ;
501
502 (
503         ." is the print string operator in FORTH.  Example: ." Something to print"
504         The space after the operator is the ordinary space required between words and is not
505         a part of what is printed.
506
507         In immediate mode we just keep reading characters and printing them until we get to
508         the next double quote.
509
510         In compile mode we use S" to store the string, then add TELL afterwards:
511                 LITSTRING <string length> <string rounded up to 4 bytes> TELL
512
513         It may be interesting to note the use of [COMPILE] to turn the call to the immediate
514         word S" into compilation of that word.  It compiles it into the definition of .",
515         not into the definition of the word being compiled when this is running (complicated
516         enough for you?)
517 )
518 : ." IMMEDIATE          ( -- )
519         STATE @ IF      ( compiling? )
520                 [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
521                 ' TELL ,        ( compile the final TELL )
522         ELSE
523                 ( In immediate mode, just read characters and print them until we get
524                   to the ending double quote. )
525                 BEGIN
526                         KEY
527                         DUP '"' = IF
528                                 DROP    ( drop the double quote character )
529                                 EXIT    ( return from this function )
530                         THEN
531                         EMIT
532                 AGAIN
533         THEN
534 ;
535
536 (
537         CONSTANTS AND VARIABLES ----------------------------------------------------------------------
538
539         In FORTH, global constants and variables are defined like this:
540
541         10 CONSTANT TEN         when TEN is executed, it leaves the integer 10 on the stack
542         VARIABLE VAR            when VAR is executed, it leaves the address of VAR on the stack
543
544         Constants can be read but not written, eg:
545
546         TEN . CR                prints 10
547
548         You can read a variable (in this example called VAR) by doing:
549
550         VAR @                   leaves the value of VAR on the stack
551         VAR @ . CR              prints the value of VAR
552         VAR ? CR                same as above, since ? is the same as @ .
553
554         and update the variable by doing:
555
556         20 VAR !                sets VAR to 20
557
558         Note that variables are uninitialised (but see VALUE later on which provides initialised
559         variables with a slightly simpler syntax).
560
561         How can we define the words CONSTANT and VARIABLE?
562
563         The trick is to define a new word for the variable itself (eg. if the variable was called
564         'VAR' then we would define a new word called VAR).  This is easy to do because we exposed
565         dictionary entry creation through the CREATE word (part of the definition of : above).
566         A call to WORD [TEN] CREATE (where [TEN] means that "TEN" is the next word in the input)
567         leaves the dictionary entry:
568
569                                    +--- HERE
570                                    |
571                                    V
572         +---------+---+---+---+---+
573         | LINK    | 3 | T | E | N |
574         +---------+---+---+---+---+
575                    len
576
577         For CONSTANT we can continue by appending DOCOL (the codeword), then LIT followed by
578         the constant itself and then EXIT, forming a little word definition that returns the
579         constant:
580
581         +---------+---+---+---+---+------------+------------+------------+------------+
582         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
583         +---------+---+---+---+---+------------+------------+------------+------------+
584                    len              codeword
585
586         Notice that this word definition is exactly the same as you would have got if you had
587         written : TEN 10 ;
588
589         Note for people reading the code below: DOCOL is a constant word which we defined in the
590         assembler part which returns the value of the assembler symbol of the same name.
591 )
592 : CONSTANT
593         WORD            ( get the name (the name follows CONSTANT) )
594         CREATE          ( make the dictionary entry )
595         DOCOL ,         ( append DOCOL (the codeword field of this word) )
596         ' LIT ,         ( append the codeword LIT )
597         ,               ( append the value on the top of the stack )
598         ' EXIT ,        ( append the codeword EXIT )
599 ;
600
601 (
602         VARIABLE is a little bit harder because we need somewhere to put the variable.  There is
603         nothing particularly special about the user memory (the area of memory pointed to by HERE
604         where we have previously just stored new word definitions).  We can slice off bits of this
605         memory area to store anything we want, so one possible definition of VARIABLE might create
606         this:
607
608            +--------------------------------------------------------------+
609            |                                                              |
610            V                                                              |
611         +---------+---------+---+---+---+---+------------+------------+---|--------+------------+
612         | <var>   | LINK    | 3 | V | A | R | DOCOL      | LIT        | <addr var> | EXIT       |
613         +---------+---------+---+---+---+---+------------+------------+------------+------------+
614                              len              codeword
615
616         where <var> is the place to store the variable, and <addr var> points back to it.
617
618         To make this more general let's define a couple of words which we can use to allocate
619         arbitrary memory from the user memory.
620
621         First ALLOT, where n ALLOT allocates n bytes of memory.  (Note when calling this that
622         it's a very good idea to make sure that n is a multiple of 4, or at least that next time
623         a word is compiled that HERE has been left as a multiple of 4).
624 )
625 : ALLOT         ( n -- addr )
626         HERE @ SWAP     ( here n )
627         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
628 ;
629
630 (
631         Second, CELLS.  In FORTH the phrase 'n CELLS ALLOT' means allocate n integers of whatever size
632         is the natural size for integers on this machine architecture.  On this 32 bit machine therefore
633         CELLS just multiplies the top of stack by 4.
634 )
635 : CELLS ( n -- n ) 4 * ;
636
637 (
638         So now we can define VARIABLE easily in much the same way as CONSTANT above.  Refer to the
639         diagram above to see what the word that this creates will look like.
640 )
641 : VARIABLE
642         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
643         WORD CREATE     ( make the dictionary entry (the name follows VARIABLE) )
644         DOCOL ,         ( append DOCOL (the codeword field of this word) )
645         ' LIT ,         ( append the codeword LIT )
646         ,               ( append the pointer to the new memory )
647         ' EXIT ,        ( append the codeword EXIT )
648 ;
649
650 (
651         VALUES ----------------------------------------------------------------------
652
653         VALUEs are like VARIABLEs but with a simpler syntax.  You would generally use them when you
654         want a variable which is read often, and written infrequently.
655
656         20 VALUE VAL    creates VAL with initial value 20
657         VAL             pushes the value (20) directly on the stack
658         30 TO VAL       updates VAL, setting it to 30
659         VAL             pushes the value (30) directly on the stack
660
661         Notice that 'VAL' on its own doesn't return the address of the value, but the value itself,
662         making values simpler and more obvious to use than variables (no indirection through '@').
663         The price is a more complicated implementation, although despite the complexity there is no
664         performance penalty at runtime.
665
666         A naive implementation of 'TO' would be quite slow, involving a dictionary search each time.
667         But because this is FORTH we have complete control of the compiler so we can compile TO more
668         efficiently, turning:
669                 TO VAL
670         into:
671                 LIT <addr> !
672         and calculating <addr> (the address of the value) at compile time.
673
674         Now this is the clever bit.  We'll compile our value like this:
675
676         +---------+---+---+---+---+------------+------------+------------+------------+
677         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
678         +---------+---+---+---+---+------------+------------+------------+------------+
679                    len              codeword
680
681         where <value> is the actual value itself.  Note that when VAL executes, it will push the
682         value on the stack, which is what we want.
683
684         But what will TO use for the address <addr>?  Why of course a pointer to that <value>:
685
686                 code compiled   - - - - --+------------+------------+------------+-- - - - -
687                 by TO VAL                 | LIT        | <addr>     | !          |
688                                 - - - - --+------------+-----|------+------------+-- - - - -
689                                                              |
690                                                              V
691         +---------+---+---+---+---+------------+------------+------------+------------+
692         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
693         +---------+---+---+---+---+------------+------------+------------+------------+
694                    len              codeword
695
696         In other words, this is a kind of self-modifying code.
697
698         (Note to the people who want to modify this FORTH to add inlining: values defined this
699         way cannot be inlined).
700 )
701 : VALUE         ( n -- )
702         WORD CREATE     ( make the dictionary entry (the name follows VALUE) )
703         DOCOL ,         ( append DOCOL )
704         ' LIT ,         ( append the codeword LIT )
705         ,               ( append the initial value )
706         ' EXIT ,        ( append the codeword EXIT )
707 ;
708
709 : TO IMMEDIATE  ( n -- )
710         WORD            ( get the name of the value )
711         FIND            ( look it up in the dictionary )
712         >DFA            ( get a pointer to the first data field (the 'LIT') )
713         4+              ( increment to point at the value )
714         STATE @ IF      ( compiling? )
715                 ' LIT ,         ( compile LIT )
716                 ,               ( compile the address of the value )
717                 ' ! ,           ( compile ! )
718         ELSE            ( immediate mode )
719                 !               ( update it straightaway )
720         THEN
721 ;
722
723 ( x +TO VAL adds x to VAL )
724 : +TO IMMEDIATE
725         WORD            ( get the name of the value )
726         FIND            ( look it up in the dictionary )
727         >DFA            ( get a pointer to the first data field (the 'LIT') )
728         4+              ( increment to point at the value )
729         STATE @ IF      ( compiling? )
730                 ' LIT ,         ( compile LIT )
731                 ,               ( compile the address of the value )
732                 ' +! ,          ( compile +! )
733         ELSE            ( immediate mode )
734                 +!              ( update it straightaway )
735         THEN
736 ;
737
738 (
739         PRINTING THE DICTIONARY ----------------------------------------------------------------------
740
741         ID. takes an address of a dictionary entry and prints the word's name.
742
743         For example: LATEST @ ID. would print the name of the last word that was defined.
744 )
745 : ID.
746         4+              ( skip over the link pointer )
747         DUP C@          ( get the flags/length byte )
748         F_LENMASK AND   ( mask out the flags - just want the length )
749
750         BEGIN
751                 DUP 0>          ( length > 0? )
752         WHILE
753                 SWAP 1+         ( addr len -- len addr+1 )
754                 DUP C@          ( len addr -- len addr char | get the next character)
755                 EMIT            ( len addr char -- len addr | and print it)
756                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
757         REPEAT
758         2DROP           ( len addr -- )
759 ;
760
761 (
762         'WORD word FIND ?HIDDEN' returns true if 'word' is flagged as hidden.
763
764         'WORD word FIND ?IMMEDIATE' returns true if 'word' is flagged as immediate.
765 )
766 : ?HIDDEN
767         4+              ( skip over the link pointer )
768         C@              ( get the flags/length byte )
769         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
770 ;
771 : ?IMMEDIATE
772         4+              ( skip over the link pointer )
773         C@              ( get the flags/length byte )
774         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
775 ;
776
777 (
778         WORDS prints all the words defined in the dictionary, starting with the word defined most recently.
779         However it doesn't print hidden words.
780
781         The implementation simply iterates backwards from LATEST using the link pointers.
782 )
783 : WORDS
784         LATEST @        ( start at LATEST dictionary entry )
785         BEGIN
786                 ?DUP            ( while link pointer is not null )
787         WHILE
788                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
789                         DUP ID.         ( but if not hidden, print the word )
790                         SPACE
791                 THEN
792                 @               ( dereference the link pointer - go to previous word )
793         REPEAT
794         CR
795 ;
796
797 (
798         FORGET ----------------------------------------------------------------------
799
800         So far we have only allocated words and memory.  FORTH provides a rather primitive method
801         to deallocate.
802
803         'FORGET word' deletes the definition of 'word' from the dictionary and everything defined
804         after it, including any variables and other memory allocated after.
805
806         The implementation is very simple - we look up the word (which returns the dictionary entry
807         address).  Then we set HERE to point to that address, so in effect all future allocations
808         and definitions will overwrite memory starting at the word.  We also need to set LATEST to
809         point to the previous word.
810
811         Note that you cannot FORGET built-in words (well, you can try but it will probably cause
812         a segfault).
813
814         XXX: Because we wrote VARIABLE to store the variable in memory allocated before the word,
815         in the current implementation VARIABLE FOO FORGET FOO will leak 1 cell of memory.
816 )
817 : FORGET
818         WORD FIND       ( find the word, gets the dictionary entry address )
819         DUP @ LATEST !  ( set LATEST to point to the previous word )
820         HERE !          ( and store HERE with the dictionary address )
821 ;
822
823 (
824         DUMP ----------------------------------------------------------------------
825
826         DUMP is used to dump out the contents of memory, in the 'traditional' hexdump format.
827
828         Notice that the parameters to DUMP (address, length) are compatible with string words
829         such as WORD and S".
830 )
831 : DUMP          ( addr len -- )
832         BASE @ ROT              ( save the current BASE at the bottom of the stack )
833         HEX                     ( and switch to hexadecimal mode )
834
835         BEGIN
836                 ?DUP            ( while len > 0 )
837         WHILE
838                 OVER 8 U.R      ( print the address )
839                 SPACE
840
841                 ( print up to 16 words on this line )
842                 2DUP            ( addr len addr len )
843                 1- 15 AND 1+    ( addr len addr linelen )
844                 BEGIN
845                         ?DUP            ( while linelen > 0 )
846                 WHILE
847                         SWAP            ( addr len linelen addr )
848                         DUP C@          ( addr len linelen addr byte )
849                         2 .R SPACE      ( print the byte )
850                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
851                 REPEAT
852                 DROP            ( addr len )
853
854                 ( print the ASCII equivalents )
855                 2DUP 1- 15 AND 1+ ( addr len addr linelen )
856                 BEGIN
857                         ?DUP            ( while linelen > 0)
858                 WHILE
859                         SWAP            ( addr len linelen addr )
860                         DUP C@          ( addr len linelen addr byte )
861                         DUP 32 128 WITHIN IF    ( 32 <= c < 128? )
862                                 EMIT
863                         ELSE
864                                 DROP '.' EMIT
865                         THEN
866                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
867                 REPEAT
868                 DROP            ( addr len )
869                 CR
870
871                 DUP 1- 15 AND 1+ ( addr len linelen )
872                 DUP             ( addr len linelen linelen )
873                 ROT             ( addr linelen len linelen )
874                 -               ( addr linelen len-linelen )
875                 ROT             ( len-linelen addr linelen )
876                 +               ( len-linelen addr+linelen )
877                 SWAP            ( addr-linelen len-linelen )
878         REPEAT
879
880         DROP                    ( restore stack )
881         BASE !                  ( restore saved BASE )
882 ;
883
884 (
885         CASE ----------------------------------------------------------------------
886
887         CASE...ENDCASE is how we do switch statements in FORTH.  There is no generally
888         agreed syntax for this, so I've gone for the syntax mandated by the ISO standard
889         FORTH (ANS-FORTH).
890
891                 ( some value on the stack )
892                 CASE
893                 test1 OF ... ENDOF
894                 test2 OF ... ENDOF
895                 testn OF ... ENDOF
896                 ... ( default case )
897                 ENDCASE
898
899         The CASE statement tests the value on the stack by comparing it for equality with
900         test1, test2, ..., testn and executes the matching piece of code within OF ... ENDOF.
901         If none of the test values match then the default case is executed.  Inside the ... of
902         the default case, the value is still at the top of stack (it is implicitly DROP-ed
903         by ENDCASE).  When ENDOF is executed it jumps after ENDCASE (ie. there is no "fall-through"
904         and no need for a break statement like in C).
905
906         The default case may be omitted.  In fact the tests may also be omitted so that you
907         just have a default case, although this is probably not very useful.
908
909         An example (assuming that 'q', etc. are words which push the ASCII value of the letter
910         on the stack):
911
912                 0 VALUE QUIT
913                 0 VALUE SLEEP
914                 KEY CASE
915                         'q' OF 1 TO QUIT ENDOF
916                         's' OF 1 TO SLEEP ENDOF
917                         ( default case: )
918                         ." Sorry, I didn't understand key <" DUP EMIT ." >, try again." CR
919                 ENDCASE
920
921         (In some versions of FORTH, more advanced tests are supported, such as ranges, etc.
922         Other versions of FORTH need you to write OTHERWISE to indicate the default case.
923         As I said above, this FORTH tries to follow the ANS FORTH standard).
924
925         The implementation of CASE...ENDCASE is somewhat non-trivial.  I'm following the
926         implementations from here:
927         http://www.uni-giessen.de/faq/archiv/forthfaq.case_endcase/msg00000.html
928
929         The general plan is to compile the code as a series of IF statements:
930
931         CASE                            (push 0 on the immediate-mode parameter stack)
932         test1 OF ... ENDOF              test1 OVER = IF DROP ... ELSE
933         test2 OF ... ENDOF              test2 OVER = IF DROP ... ELSE
934         testn OF ... ENDOF              testn OVER = IF DROP ... ELSE
935         ... ( default case )            ...
936         ENDCASE                         DROP THEN [THEN [THEN ...]]
937
938         The CASE statement pushes 0 on the immediate-mode parameter stack, and that number
939         is used to count how many THEN statements we need when we get to ENDCASE so that each
940         IF has a matching THEN.  The counting is done implicitly.  If you recall from the
941         implementation above of IF, each IF pushes a code address on the immediate-mode stack,
942         and these addresses are non-zero, so by the time we get to ENDCASE the stack contains
943         some number of non-zeroes, followed by a zero.  The number of non-zeroes is how many
944         times IF has been called, so how many times we need to match it with THEN.
945
946         This code uses [COMPILE] so that we compile calls to IF, ELSE, THEN instead of
947         actually calling them while we're compiling the words below.
948
949         As is the case with all of our control structures, they only work within word
950         definitions, not in immediate mode.
951 )
952 : CASE IMMEDIATE
953         0               ( push 0 to mark the bottom of the stack )
954 ;
955
956 : OF IMMEDIATE
957         ' OVER ,        ( compile OVER )
958         ' = ,           ( compile = )
959         [COMPILE] IF    ( compile IF )
960         ' DROP ,        ( compile DROP )
961 ;
962
963 : ENDOF IMMEDIATE
964         [COMPILE] ELSE  ( ENDOF is the same as ELSE )
965 ;
966
967 : ENDCASE IMMEDIATE
968         ' DROP ,        ( compile DROP )
969
970         ( keep compiling THEN until we get to our zero marker )
971         BEGIN
972                 ?DUP
973         WHILE
974                 [COMPILE] THEN
975         REPEAT
976 ;
977
978 (
979         DECOMPILER ----------------------------------------------------------------------
980
981         CFA> is the opposite of >CFA.  It takes a codeword and tries to find the matching
982         dictionary definition.  (In truth, it works with any pointer into a word, not just
983         the codeword pointer, and this is needed to do stack traces).
984
985         In this FORTH this is not so easy.  In fact we have to search through the dictionary
986         because we don't have a convenient back-pointer (as is often the case in other versions
987         of FORTH).  Because of this search, CFA> should not be used when performance is critical,
988         so it is only used for debugging tools such as the decompiler and printing stack
989         traces.
990
991         This word returns 0 if it doesn't find a match.
992 )
993 : CFA>
994         LATEST @        ( start at LATEST dictionary entry )
995         BEGIN
996                 ?DUP            ( while link pointer is not null )
997         WHILE
998                 2DUP SWAP       ( cfa curr curr cfa )
999                 < IF            ( current dictionary entry < cfa? )
1000                         NIP             ( leave curr dictionary entry on the stack )
1001                         EXIT
1002                 THEN
1003                 @               ( follow link pointer back )
1004         REPEAT
1005         DROP            ( restore stack )
1006         0               ( sorry, nothing found )
1007 ;
1008
1009 (
1010         SEE decompiles a FORTH word.
1011
1012         We search for the dictionary entry of the word, then search again for the next
1013         word (effectively, the end of the compiled word).  This results in two pointers:
1014
1015         +---------+---+---+---+---+------------+------------+------------+------------+
1016         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
1017         +---------+---+---+---+---+------------+------------+------------+------------+
1018          ^                                                                             ^
1019          |                                                                             |
1020         Start of word                                                         End of word
1021
1022         With this information we can have a go at decompiling the word.  We need to
1023         recognise "meta-words" like LIT, LITSTRING, BRANCH, etc. and treat those separately.
1024 )
1025 : SEE
1026         WORD FIND       ( find the dictionary entry to decompile )
1027
1028         ( Now we search again, looking for the next word in the dictionary.  This gives us
1029           the length of the word that we will be decompiling.  (Well, mostly it does). )
1030         HERE @          ( address of the end of the last compiled word )
1031         LATEST @        ( word last curr )
1032         BEGIN
1033                 2 PICK          ( word last curr word )
1034                 OVER            ( word last curr word curr )
1035                 <>              ( word last curr word<>curr? )
1036         WHILE                   ( word last curr )
1037                 NIP             ( word curr )
1038                 DUP @           ( word curr prev (which becomes: word last curr) )
1039         REPEAT
1040
1041         DROP            ( at this point, the stack is: start-of-word end-of-word )
1042         SWAP            ( end-of-word start-of-word )
1043
1044         ( begin the definition with : NAME [IMMEDIATE] )
1045         ':' EMIT SPACE DUP ID. SPACE
1046         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN
1047
1048         >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
1049
1050         ( now we start decompiling until we hit the end of the word )
1051         BEGIN           ( end start )
1052                 2DUP >
1053         WHILE
1054                 DUP @           ( end start codeword )
1055
1056                 CASE
1057                 ' LIT OF                ( is it LIT ? )
1058                         4 + DUP @               ( get next word which is the integer constant )
1059                         .                       ( and print it )
1060                 ENDOF
1061                 ' LITSTRING OF          ( is it LITSTRING ? )
1062                         [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
1063                         4 + DUP @               ( get the length word )
1064                         SWAP 4 + SWAP           ( end start+4 length )
1065                         2DUP TELL               ( print the string )
1066                         '"' EMIT SPACE          ( finish the string with a final quote )
1067                         + ALIGNED               ( end start+4+len, aligned )
1068                         4 -                     ( because we're about to add 4 below )
1069                 ENDOF
1070                 ' 0BRANCH OF            ( is it 0BRANCH ? )
1071                         ." 0BRANCH ( "
1072                         4 + DUP @               ( print the offset )
1073                         .
1074                         ." ) "
1075                 ENDOF
1076                 ' BRANCH OF             ( is it BRANCH ? )
1077                         ." BRANCH ( "
1078                         4 + DUP @               ( print the offset )
1079                         .
1080                         ." ) "
1081                 ENDOF
1082                 ' ' OF                  ( is it ' (TICK) ? )
1083                         [ CHAR ' ] LITERAL EMIT SPACE
1084                         4 + DUP @               ( get the next codeword )
1085                         CFA>                    ( and force it to be printed as a dictionary entry )
1086                         ID. SPACE
1087                 ENDOF
1088                 ' EXIT OF               ( is it EXIT? )
1089                         ( We expect the last word to be EXIT, and if it is then we don't print it
1090                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
1091                           of words, and then it needs to be printed. )
1092                         2DUP                    ( end start end start )
1093                         4 +                     ( end start end start+4 )
1094                         <> IF                   ( end start | we're not at the end )
1095                                 ." EXIT "
1096                         THEN
1097                 ENDOF
1098                                         ( default case: )
1099                         DUP                     ( in the default case we always need to DUP before using )
1100                         CFA>                    ( look up the codeword to get the dictionary entry )
1101                         ID. SPACE               ( and print it )
1102                 ENDCASE
1103
1104                 4 +             ( end start+4 )
1105         REPEAT
1106
1107         ';' EMIT CR
1108
1109         2DROP           ( restore stack )
1110 ;
1111
1112 (
1113         EXECUTION TOKENS ----------------------------------------------------------------------
1114
1115         Standard FORTH defines a concept called an 'execution token' (or 'xt') which is very
1116         similar to a function pointer in C.  We map the execution token to a codeword address.
1117
1118                         execution token of DOUBLE is the address of this codeword
1119                                                     |
1120                                                     V
1121         +---------+---+---+---+---+---+---+---+---+------------+------------+------------+------------+
1122         | LINK    | 6 | D | O | U | B | L | E | 0 | DOCOL      | DUP        | +          | EXIT       |
1123         +---------+---+---+---+---+---+---+---+---+------------+------------+------------+------------+
1124                    len                         pad  codeword                                           ^
1125
1126         There is one assembler primitive for execution tokens, EXECUTE ( xt -- ), which runs them.
1127
1128         You can make an execution token for an existing word the long way using >CFA,
1129         ie: WORD [foo] FIND >CFA will push the xt for foo onto the stack where foo is the
1130         next word in input.  So a very slow way to run DOUBLE might be:
1131
1132                 : DOUBLE DUP + ;
1133                 : SLOW WORD FIND >CFA EXECUTE ;
1134                 5 SLOW DOUBLE . CR      \ prints 10
1135
1136         We also offer a simpler and faster way to get the execution token of any word FOO:
1137
1138                 ['] FOO
1139
1140         (Exercises for readers: (1) What is the difference between ['] FOO and ' FOO?
1141         (2) What is the relationship between ', ['] and LIT?)
1142
1143         More useful is to define anonymous words and/or to assign xt's to variables.
1144
1145         To define an anonymous word (and push its xt on the stack) use :NONAME ... ; as in this
1146         example:
1147
1148                 :NONAME ." anon word was called" CR ;   \ pushes xt on the stack
1149                 DUP EXECUTE EXECUTE                     \ executes the anon word twice
1150
1151         Stack parameters work as expected:
1152
1153                 :NONAME ." called with parameter " . CR ;
1154                 DUP
1155                 10 SWAP EXECUTE         \ prints 'called with parameter 10'
1156                 20 SWAP EXECUTE         \ prints 'called with parameter 20'
1157
1158         Notice that the above code has a memory leak: the anonymous word is still compiled
1159         into the data segment, so even if you lose track of the xt, the word continues to
1160         occupy memory.  A good way to keep track of the xt and thus avoid the memory leak is
1161         to assign it to a CONSTANT, VARIABLE or VALUE:
1162
1163                 0 VALUE ANON
1164                 :NONAME ." anon word was called" CR ; TO ANON
1165                 ANON EXECUTE
1166                 ANON EXECUTE
1167
1168         Another use of :NONAME is to create an array of functions which can be called quickly
1169         (think: fast switch statement).  This example is adapted from the ANS FORTH standard:
1170
1171                 10 CELLS ALLOT CONSTANT CMD-TABLE
1172                 : SET-CMD CELLS CMD-TABLE + ! ;
1173                 : CALL-CMD CELLS CMD-TABLE + @ EXECUTE ;
1174
1175                 :NONAME ." alternate 0 was called" CR ;  0 SET-CMD
1176                 :NONAME ." alternate 1 was called" CR ;  1 SET-CMD
1177                         \ etc...
1178                 :NONAME ." alternate 9 was called" CR ;  9 SET-CMD
1179
1180                 0 CALL-CMD
1181                 1 CALL-CMD
1182 )
1183
1184 : :NONAME
1185         0 0 CREATE      ( create a word with no name - we need a dictionary header because ; expects it )
1186         HERE @          ( current HERE value is the address of the codeword, ie. the xt )
1187         DOCOL ,         ( compile DOCOL (the codeword) )
1188         ]               ( go into compile mode )
1189 ;
1190
1191 : ['] IMMEDIATE
1192         ' LIT ,         ( compile LIT )
1193 ;
1194
1195 (
1196         EXCEPTIONS ----------------------------------------------------------------------
1197
1198         Amazingly enough, exceptions can be implemented directly in FORTH, in fact rather easily.
1199
1200         The general usage is as follows:
1201
1202                 : FOO ( n -- ) THROW ;
1203
1204                 : TEST-EXCEPTIONS
1205                         25 ['] FOO CATCH        \ execute 25 FOO, catching any exception
1206                         ?DUP IF
1207                                 ." called FOO and it threw exception number: "
1208                                 . CR
1209                                 DROP            \ we have to drop the argument of FOO (25)
1210                         THEN
1211                 ;
1212                 \ prints: called FOO and it threw exception number: 25
1213
1214         CATCH runs an execution token and detects whether it throws any exception or not.  The
1215         stack signature of CATCH is rather complicated:
1216
1217                 ( a_n-1 ... a_1 a_0 xt -- r_m-1 ... r_1 r_0 0 )         if xt did NOT throw an exception
1218                 ( a_n-1 ... a_1 a_0 xt -- ?_n-1 ... ?_1 ?_0 e )         if xt DID throw exception 'e'
1219
1220         where a_i and r_i are the (arbitrary number of) argument and return stack contents
1221         before and after xt is EXECUTEd.  Notice in particular the case where an exception
1222         is thrown, the stack pointer is restored so that there are n of _something_ on the
1223         stack in the positions where the arguments a_i used to be.  We don't really guarantee
1224         what is on the stack -- perhaps the original arguments, and perhaps other nonsense --
1225         it largely depends on the implementation of the word that was executed.
1226
1227         THROW, ABORT and a few others throw exceptions.
1228
1229         Exception numbers are non-zero integers.  By convention the positive numbers can be used
1230         for app-specific exceptions and the negative numbers have certain meanings defined in
1231         the ANS FORTH standard.  (For example, -1 is the exception thrown by ABORT).
1232
1233         0 THROW does nothing.  This is the stack signature of THROW:
1234
1235                 ( 0 -- )
1236                 ( * e -- ?_n-1 ... ?_1 ?_0 e )  the stack is restored to the state from the corresponding CATCH
1237
1238         The implementation hangs on the definitions of CATCH and THROW and the state shared
1239         between them.
1240
1241         Up to this point, the return stack has consisted merely of a list of return addresses,
1242         with the top of the return stack being the return address where we will resume executing
1243         when the current word EXITs.  However CATCH will push a more complicated 'exception stack
1244         frame' on the return stack.  The exception stack frame records some things about the
1245         state of execution at the time that CATCH was called.
1246
1247         When called, THROW walks up the return stack (the process is called 'unwinding') until
1248         it finds the exception stack frame.  It then uses the data in the exception stack frame
1249         to restore the state allowing execution to continue after the matching CATCH.  (If it
1250         unwinds the stack and doesn't find the exception stack frame then it prints a message
1251         and drops back to the prompt, which is also normal behaviour for so-called 'uncaught
1252         exceptions').
1253
1254         This is what the exception stack frame looks like.  (As is conventional, the return stack
1255         is shown growing downwards from higher to lower memory addresses).
1256
1257                 +------------------------------+
1258                 | return address from CATCH    |   Notice this is already on the
1259                 |                              |   return stack when CATCH is called.
1260                 +------------------------------+
1261                 | original parameter stack     |
1262                 | pointer                      |
1263                 +------------------------------+  ^
1264                 | exception stack marker       |  |
1265                 | (EXCEPTION-MARKER)           |  |   Direction of stack
1266                 +------------------------------+  |   unwinding by THROW.
1267                                                   |
1268                                                   |
1269
1270         The EXCEPTION-MARKER marks the entry as being an exception stack frame rather than an
1271         ordinary return address, and it is this which THROW "notices" as it is unwinding the
1272         stack.  (If you want to implement more advanced exceptions such as TRY...WITH then
1273         you'll need to use a different value of marker if you want the old and new exception stack
1274         frame layouts to coexist).
1275
1276         What happens if the executed word doesn't throw an exception?  It will eventually
1277         return and call EXCEPTION-MARKER, so EXCEPTION-MARKER had better do something sensible
1278         without us needing to modify EXIT.  This nicely gives us a suitable definition of
1279         EXCEPTION-MARKER, namely a function that just drops the stack frame and itself
1280         returns (thus "returning" from the original CATCH).
1281
1282         One thing to take from this is that exceptions are a relatively lightweight mechanism
1283         in FORTH.
1284 )
1285
1286 : EXCEPTION-MARKER
1287         RDROP                   ( drop the original parameter stack pointer )
1288         0                       ( there was no exception, this is the normal return path )
1289 ;
1290
1291 : CATCH         ( xt -- exn? )
1292         DSP@ 4+ >R              ( save parameter stack pointer (+4 because of xt) on the return stack )
1293         ' EXCEPTION-MARKER 4+   ( push the address of the RDROP inside EXCEPTION-MARKER ... )
1294         >R                      ( ... on to the return stack so it acts like a return address )
1295         EXECUTE                 ( execute the nested function )
1296 ;
1297
1298 : THROW         ( n -- )
1299         ?DUP IF                 ( only act if the exception code <> 0 )
1300                 RSP@                    ( get return stack pointer )
1301                 BEGIN
1302                         DUP R0 4- <             ( RSP < R0 )
1303                 WHILE
1304                         DUP @                   ( get the return stack entry )
1305                         ' EXCEPTION-MARKER 4+ = IF      ( found the EXCEPTION-MARKER on the return stack )
1306                                 4+                      ( skip the EXCEPTION-MARKER on the return stack )
1307                                 RSP!                    ( restore the return stack pointer )
1308
1309                                 ( Restore the parameter stack. )
1310                                 DUP DUP DUP             ( reserve some working space so the stack for this word
1311                                                           doesn't coincide with the part of the stack being restored )
1312                                 R>                      ( get the saved parameter stack pointer | n dsp )
1313                                 4-                      ( reserve space on the stack to store n )
1314                                 SWAP OVER               ( dsp n dsp )
1315                                 !                       ( write n on the stack )
1316                                 DSP! EXIT               ( restore the parameter stack pointer, immediately exit )
1317                         THEN
1318                         4+
1319                 REPEAT
1320
1321                 ( No matching catch - print a message and restart the INTERPRETer. )
1322                 DROP
1323
1324                 CASE
1325                 0 1- OF ( ABORT )
1326                         ." ABORTED" CR
1327                 ENDOF
1328                         ( default case )
1329                         ." UNCAUGHT THROW "
1330                         DUP . CR
1331                 ENDCASE
1332                 QUIT
1333         THEN
1334 ;
1335
1336 : ABORT         ( -- )
1337         0 1- THROW
1338 ;
1339
1340 ( Print a stack trace by walking up the return stack. )
1341 : PRINT-STACK-TRACE
1342         RSP@                            ( start at caller of this function )
1343         BEGIN
1344                 DUP R0 4- <             ( RSP < R0 )
1345         WHILE
1346                 DUP @                   ( get the return stack entry )
1347                 CASE
1348                 ' EXCEPTION-MARKER 4+ OF        ( is it the exception stack frame? )
1349                         ." CATCH ( DSP="
1350                         4+ DUP @ U.             ( print saved stack pointer )
1351                         ." ) "
1352                 ENDOF
1353                                                 ( default case )
1354                         DUP
1355                         CFA>                    ( look up the codeword to get the dictionary entry )
1356                         ?DUP IF                 ( and print it )
1357                                 2DUP                    ( dea addr dea )
1358                                 ID.                     ( print word from dictionary entry )
1359                                 [ CHAR + ] LITERAL EMIT
1360                                 SWAP >DFA 4+ - .        ( print offset )
1361                         THEN
1362                 ENDCASE
1363                 4+                      ( move up the stack )
1364         REPEAT
1365         DROP
1366         CR
1367 ;
1368
1369 (
1370         C STRINGS ----------------------------------------------------------------------
1371
1372         FORTH strings are represented by a start address and length kept on the stack or in memory.
1373
1374         Most FORTHs don't handle C strings, but we need them in order to access the process arguments
1375         and environment left on the stack by the Linux kernel, and to make some system calls.
1376
1377         Operation       Input           Output          FORTH word      Notes
1378         ----------------------------------------------------------------------
1379
1380         Create FORTH string             addr len        S" ..."
1381
1382         Create C string                 c-addr          Z" ..."
1383
1384         C -> FORTH      c-addr          addr len        DUP STRLEN
1385
1386         FORTH -> C      addr len        c-addr          CSTRING         Allocated in a temporary buffer, so
1387                                                                         should be consumed / copied immediately.
1388                                                                         FORTH string should not contain NULs.
1389
1390         For example, DUP STRLEN TELL prints a C string.
1391 )
1392
1393 (
1394         Z" .." is like S" ..." except that the string is terminated by an ASCII NUL character.
1395
1396         To make it more like a C string, at runtime Z" just leaves the address of the string
1397         on the stack (not address & length as with S").  To implement this we need to add the
1398         extra NUL to the string and also a DROP instruction afterwards.  Apart from that the
1399         implementation just a modified S".
1400 )
1401 : Z" IMMEDIATE
1402         STATE @ IF      ( compiling? )
1403                 ' LITSTRING ,   ( compile LITSTRING )
1404                 HERE @          ( save the address of the length word on the stack )
1405                 0 ,             ( dummy length - we don't know what it is yet )
1406                 BEGIN
1407                         KEY             ( get next character of the string )
1408                         DUP '"' <>
1409                 WHILE
1410                         HERE @ C!       ( store the character in the compiled image )
1411                         1 HERE +!       ( increment HERE pointer by 1 byte )
1412                 REPEAT
1413                 0 HERE @ C!     ( add the ASCII NUL byte )
1414                 1 HERE +!
1415                 DROP            ( drop the double quote character at the end )
1416                 DUP             ( get the saved address of the length word )
1417                 HERE @ SWAP -   ( calculate the length )
1418                 4-              ( subtract 4 (because we measured from the start of the length word) )
1419                 SWAP !          ( and back-fill the length location )
1420                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
1421                 ' DROP ,        ( compile DROP (to drop the length) )
1422         ELSE            ( immediate mode )
1423                 HERE @          ( get the start address of the temporary space )
1424                 BEGIN
1425                         KEY
1426                         DUP '"' <>
1427                 WHILE
1428                         OVER C!         ( save next character )
1429                         1+              ( increment address )
1430                 REPEAT
1431                 DROP            ( drop the final " character )
1432                 0 SWAP C!       ( store final ASCII NUL )
1433                 HERE @          ( push the start address )
1434         THEN
1435 ;
1436
1437 : STRLEN        ( str -- len )
1438         DUP             ( save start address )
1439         BEGIN
1440                 DUP C@ 0<>      ( zero byte found? )
1441         WHILE
1442                 1+
1443         REPEAT
1444
1445         SWAP -          ( calculate the length )
1446 ;
1447
1448 : CSTRING       ( addr len -- c-addr )
1449         SWAP OVER       ( len saddr len )
1450         HERE @ SWAP     ( len saddr daddr len )
1451         CMOVE           ( len )
1452
1453         HERE @ +        ( daddr+len )
1454         0 SWAP C!       ( store terminating NUL char )
1455
1456         HERE @          ( push start address )
1457 ;
1458
1459 (
1460         THE ENVIRONMENT ----------------------------------------------------------------------
1461
1462         Linux makes the process arguments and environment available to us on the stack.
1463
1464         The top of stack pointer is saved by the early assembler code when we start up in the FORTH
1465         variable S0, and starting at this pointer we can read out the command line arguments and the
1466         environment.
1467
1468         Starting at S0, S0 itself points to argc (the number of command line arguments).
1469
1470         S0+4 points to argv[0], S0+8 points to argv[1] etc up to argv[argc-1].
1471
1472         argv[argc] is a NULL pointer.
1473
1474         After that the stack contains environment variables, a set of pointers to strings of the
1475         form NAME=VALUE and on until we get to another NULL pointer.
1476
1477         The first word that we define, ARGC, pushes the number of command line arguments (note that
1478         as with C argc, this includes the name of the command).
1479 )
1480 : ARGC
1481         S0 @ @
1482 ;
1483
1484 (
1485         n ARGV gets the nth command line argument.
1486
1487         For example to print the command name you would do:
1488                 0 ARGV TELL CR
1489 )
1490 : ARGV ( n -- str u )
1491         1+ CELLS S0 @ + ( get the address of argv[n] entry )
1492         @               ( get the address of the string )
1493         DUP STRLEN      ( and get its length / turn it into a FORTH string )
1494 ;
1495
1496 (
1497         ENVIRON returns the address of the first environment string.  The list of strings ends
1498         with a NULL pointer.
1499
1500         For example to print the first string in the environment you could do:
1501                 ENVIRON @ DUP STRLEN TELL
1502 )
1503 : ENVIRON       ( -- addr )
1504         ARGC            ( number of command line parameters on the stack to skip )
1505         2 +             ( skip command line count and NULL pointer after the command line args )
1506         CELLS           ( convert to an offset )
1507         S0 @ +          ( add to base stack address )
1508 ;
1509
1510 (
1511         SYSTEM CALLS AND FILES  ----------------------------------------------------------------------
1512
1513         Miscellaneous words related to system calls, and standard access to files.
1514 )
1515
1516 ( BYE exits by calling the Linux exit(2) syscall. )
1517 : BYE           ( -- )
1518         0               ( return code (0) )
1519         SYS_EXIT        ( system call number )
1520         SYSCALL1
1521 ;
1522
1523 (
1524         UNUSED returns the number of cells remaining in the user memory (data segment).
1525
1526         For our implementation we will use Linux brk(2) system call to find out the end
1527         of the data segment and subtract HERE from it.
1528 )
1529 : GET-BRK       ( -- brkpoint )
1530         0 SYS_BRK SYSCALL1      ( call brk(0) )
1531 ;
1532
1533 : UNUSED        ( -- n )
1534         GET-BRK         ( get end of data segment according to the kernel )
1535         HERE @          ( get current position in data segment )
1536         -
1537         4 /             ( returns number of cells )
1538 ;
1539
1540 (
1541         MORECORE increases the data segment by the specified number of (4 byte) cells.
1542
1543         NB. The number of cells requested should normally be a multiple of 1024.  The
1544         reason is that Linux can't extend the data segment by less than a single page
1545         (4096 bytes or 1024 cells).
1546
1547         This FORTH doesn't automatically increase the size of the data segment "on demand"
1548         (ie. when , (COMMA), ALLOT, CREATE, and so on are used).  Instead the programmer
1549         needs to be aware of how much space a large allocation will take, check UNUSED, and
1550         call MORECORE if necessary.  A simple programming exercise is to change the
1551         implementation of the data segment so that MORECORE is called automatically if
1552         the program needs more memory.
1553 )
1554 : BRK           ( brkpoint -- )
1555         SYS_BRK SYSCALL1
1556 ;
1557
1558 : MORECORE      ( cells -- )
1559         CELLS GET-BRK + BRK
1560 ;
1561
1562 (
1563         Standard FORTH provides some simple file access primitives which we model on
1564         top of Linux syscalls.
1565
1566         The main complication is converting FORTH strings (address & length) into C
1567         strings for the Linux kernel.
1568
1569         Notice there is no buffering in this implementation.
1570 )
1571
1572 : R/O ( -- fam ) O_RDONLY ;
1573 : R/W ( -- fam ) O_RDWR ;
1574
1575 : OPEN-FILE     ( addr u fam -- fd 0 (if successful) | c-addr u fam -- fd errno (if there was an error) )
1576         ROT             ( fam addr u )
1577         CSTRING         ( fam cstring )
1578         SYS_OPEN SYSCALL2 ( open (filename, flags) )
1579         DUP             ( fd fd )
1580         DUP 0< IF       ( errno? )
1581                 NEGATE          ( fd errno )
1582         ELSE
1583                 DROP 0          ( fd 0 )
1584         THEN
1585 ;
1586
1587 : CREATE-FILE   ( addr u fam -- fd 0 (if successful) | c-addr u fam -- fd errno (if there was an error) )
1588         O_CREAT OR
1589         O_TRUNC OR
1590         ROT             ( fam addr u )
1591         CSTRING         ( fam cstring )
1592         420 ROT         ( 0644 fam cstring )
1593         SYS_OPEN SYSCALL3 ( open (filename, flags|O_TRUNC|O_CREAT, 0644) )
1594         DUP             ( fd fd )
1595         DUP 0< IF       ( errno? )
1596                 NEGATE          ( fd errno )
1597         ELSE
1598                 DROP 0          ( fd 0 )
1599         THEN
1600 ;
1601
1602 : CLOSE-FILE    ( fd -- 0 (if successful) | fd -- errno (if there was an error) )
1603         SYS_CLOSE SYSCALL1
1604         NEGATE
1605 ;
1606
1607 : READ-FILE     ( addr u fd -- u2 0 (if successful) | addr u fd -- 0 0 (if EOF) | addr u fd -- u2 errno (if error) )
1608         ROT SWAP -ROT   ( u addr fd )
1609         SYS_READ SYSCALL3
1610
1611         DUP             ( u2 u2 )
1612         DUP 0< IF       ( errno? )
1613                 NEGATE          ( u2 errno )
1614         ELSE
1615                 DROP 0          ( u2 0 )
1616         THEN
1617 ;
1618
1619 (
1620         PERROR prints a message for an errno, similar to C's perror(3) but we don't have the extensive
1621         list of strerror strings available, so all we can do is print the errno.
1622 )
1623 : PERROR        ( errno addr u -- )
1624         TELL
1625         ':' EMIT SPACE
1626         ." ERRNO="
1627         . CR
1628 ;
1629
1630 (
1631         ASSEMBLER CODE ----------------------------------------------------------------------
1632
1633         This is just the outline of a simple assembler, allowing you to write FORTH primitives
1634         in assembly language.
1635
1636         Assembly primitives begin ': NAME' in the normal way, but are ended with ;CODE.  ;CODE
1637         updates the header so that the codeword isn't DOCOL, but points instead to the assembled
1638         code (in the DFA part of the word).
1639
1640         We provide a convenience macro NEXT (you guessed the rest).
1641
1642         The rest consists of some immediate words which expand into machine code appended to the
1643         definition of the word.  Only a very tiny part of the i386 assembly space is covered, just
1644         enough to write a few assembler primitives below.
1645 )
1646
1647 : ;CODE IMMEDIATE
1648         ALIGN                   ( machine code is assembled in bytes so isn't necessarily aligned at the end )
1649         LATEST @ DUP
1650         HIDDEN                  ( unhide the word )
1651         DUP >DFA SWAP >CFA !    ( change the codeword to point to the data area )
1652         [COMPILE] [             ( go back to immediate mode )
1653 ;
1654
1655 HEX
1656
1657 ( Equivalent to the NEXT macro )
1658 : NEXT IMMEDIATE AD C, FF C, 20 C, ;
1659
1660 ( The i386 registers )
1661 : EAX IMMEDIATE 0 ;
1662 : ECX IMMEDIATE 1 ;
1663 : EDX IMMEDIATE 2 ;
1664 : EBX IMMEDIATE 3 ;
1665 : ESP IMMEDIATE 4 ;
1666 : EBP IMMEDIATE 5 ;
1667 : ESI IMMEDIATE 6 ;
1668 : EDI IMMEDIATE 7 ;
1669
1670 ( i386 stack instructions )
1671 : PUSH IMMEDIATE 50 + C, ;
1672 : POP IMMEDIATE 58 + C, ;
1673
1674 ( RDTSC instruction )
1675 : RDTSC IMMEDIATE 0F C, 31 C, ;
1676
1677 DECIMAL
1678
1679 (
1680         RDTSC is an assembler primitive which reads the Pentium timestamp counter (a very fine-
1681         grained counter which counts processor clock cycles).  Because the TSC is 64 bits wide
1682         we have to push it onto the stack in two slots.
1683 )
1684 : RDTSC         ( -- lsb msb )
1685         RDTSC           ( writes the result in %edx:%eax )
1686         EAX PUSH        ( push lsb )
1687         EDX PUSH        ( push msb )
1688         NEXT
1689 ;CODE
1690
1691 (
1692         NOTES ----------------------------------------------------------------------
1693
1694         DOES> isn't possible to implement with this FORTH because we don't have a separate
1695         data pointer.
1696 )
1697
1698 (
1699         WELCOME MESSAGE ----------------------------------------------------------------------
1700
1701         Print the version and OK prompt.
1702 )
1703
1704 : WELCOME
1705         S" TEST-MODE" FIND NOT IF
1706                 ." JONESFORTH VERSION " VERSION . CR
1707                 UNUSED . ." CELLS REMAINING" CR
1708                 ." OK "
1709         THEN
1710 ;
1711
1712 WELCOME
1713 HIDE WELCOME