3c62f34dcfce938b80cec795f161b17f2e8ae08c
[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.10 2007-09-29 16:06:27 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 : 'SPACE' 32 ;
56
57 \ CR prints a carriage return
58 : CR '\n' EMIT ;
59
60 \ SPACE prints a space
61 : SPACE 'SPACE' EMIT ;
62
63 \ DUP, DROP are defined in assembly for speed, but this is how you might define them
64 \ in FORTH.  Notice use of the scratch variables _X and _Y.
65 \ : DUP _X ! _X @ _X @ ;
66 \ : DROP _X ! ;
67
68 \ The 2... versions of the standard operators work on pairs of stack entries.  They're not used
69 \ very commonly so not really worth writing in assembler.  Here is how they are defined in FORTH.
70 : 2DUP OVER OVER ;
71 : 2DROP DROP DROP ;
72
73 \ More standard FORTH words.
74 : 2* 2 * ;
75 : 2/ 2 / ;
76
77 \ NEGATE leaves the negative of a number on the stack.
78 : NEGATE 0 SWAP - ;
79
80 \ Standard words for booleans.
81 : TRUE  1 ;
82 : FALSE 0 ;
83 : NOT   0= ;
84
85 \ LITERAL takes whatever is on the stack and compiles LIT <foo>
86 : LITERAL IMMEDIATE
87         ' LIT ,         \ compile LIT
88         ,               \ compile the literal itself (from the stack)
89         ;
90
91 \ Now we can use [ and ] to insert literals which are calculated at compile time.  (Recall that
92 \ [ and ] are the FORTH words which switch into and out of immediate mode.)
93 \ Within definitions, use [ ... ] LITERAL anywhere that '...' is a constant expression which you
94 \ would rather only compute once (at compile time, rather than calculating it each time your word runs).
95 : ':'
96         [               \ go into immediate mode (temporarily)
97         CHAR :          \ push the number 58 (ASCII code of colon) on the parameter stack
98         ]               \ go back to compile mode
99         LITERAL         \ compile LIT 58 as the definition of ':' word
100 ;
101
102 \ A few more character constants defined the same way as above.
103 : ';' [ CHAR ; ] LITERAL ;
104 : '(' [ CHAR ( ] LITERAL ;
105 : ')' [ CHAR ) ] LITERAL ;
106 : '"' [ CHAR " ] LITERAL ;
107 : 'A' [ CHAR A ] LITERAL ;
108 : '0' [ CHAR 0 ] LITERAL ;
109 : '-' [ CHAR - ] LITERAL ;
110 : '.' [ CHAR . ] LITERAL ;
111
112 \ While compiling, '[COMPILE] word' compiles 'word' if it would otherwise be IMMEDIATE.
113 : [COMPILE] IMMEDIATE
114         WORD            \ get the next word
115         FIND            \ find it in the dictionary
116         >CFA            \ get its codeword
117         ,               \ and compile that
118 ;
119
120 \ RECURSE makes a recursive call to the current word that is being compiled.
121 \
122 \ Normally while a word is being compiled, it is marked HIDDEN so that references to the
123 \ same word within are calls to the previous definition of the word.  However we still have
124 \ access to the word which we are currently compiling through the LATEST pointer so we
125 \ can use that to compile a recursive call.
126 : RECURSE IMMEDIATE
127         LATEST @        \ LATEST points to the word being compiled at the moment
128         >CFA            \ get the codeword
129         ,               \ compile it
130 ;
131
132 \       CONTROL STRUCTURES ----------------------------------------------------------------------
133 \
134 \ So far we have defined only very simple definitions.  Before we can go further, we really need to
135 \ make some control structures, like IF ... THEN and loops.  Luckily we can define arbitrary control
136 \ structures directly in FORTH.
137 \
138 \ Please note that the control structures as I have defined them here will only work inside compiled
139 \ words.  If you try to type in expressions using IF, etc. in immediate mode, then they won't work.
140 \ Making these work in immediate mode is left as an exercise for the reader.
141
142 \ condition IF true-part THEN rest
143 \       -- compiles to: --> condition 0BRANCH OFFSET true-part rest
144 \       where OFFSET is the offset of 'rest'
145 \ condition IF true-part ELSE false-part THEN
146 \       -- compiles to: --> condition 0BRANCH OFFSET true-part BRANCH OFFSET2 false-part rest
147 \       where OFFSET if the offset of false-part and OFFSET2 is the offset of rest
148
149 \ IF is an IMMEDIATE word which compiles 0BRANCH followed by a dummy offset, and places
150 \ the address of the 0BRANCH on the stack.  Later when we see THEN, we pop that address
151 \ off the stack, calculate the offset, and back-fill the offset.
152 : IF IMMEDIATE
153         ' 0BRANCH ,     \ compile 0BRANCH
154         HERE @          \ save location of the offset on the stack
155         0 ,             \ compile a dummy offset
156 ;
157
158 : THEN IMMEDIATE
159         DUP
160         HERE @ SWAP -   \ calculate the offset from the address saved on the stack
161         SWAP !          \ store the offset in the back-filled location
162 ;
163
164 : ELSE IMMEDIATE
165         ' BRANCH ,      \ definite branch to just over the false-part
166         HERE @          \ save location of the offset on the stack
167         0 ,             \ compile a dummy offset
168         SWAP            \ now back-fill the original (IF) offset
169         DUP             \ same as for THEN word above
170         HERE @ SWAP -
171         SWAP !
172 ;
173
174 \ BEGIN loop-part condition UNTIL
175 \       -- compiles to: --> loop-part condition 0BRANCH OFFSET
176 \       where OFFSET points back to the loop-part
177 \ This is like do { loop-part } while (condition) in the C language
178 : BEGIN IMMEDIATE
179         HERE @          \ save location on the stack
180 ;
181
182 : UNTIL IMMEDIATE
183         ' 0BRANCH ,     \ compile 0BRANCH
184         HERE @ -        \ calculate the offset from the address saved on the stack
185         ,               \ compile the offset here
186 ;
187
188 \ BEGIN loop-part AGAIN
189 \       -- compiles to: --> loop-part BRANCH OFFSET
190 \       where OFFSET points back to the loop-part
191 \ In other words, an infinite loop which can only be returned from with EXIT
192 : AGAIN IMMEDIATE
193         ' BRANCH ,      \ compile BRANCH
194         HERE @ -        \ calculate the offset back
195         ,               \ compile the offset here
196 ;
197
198 \ BEGIN condition WHILE loop-part REPEAT
199 \       -- compiles to: --> condition 0BRANCH OFFSET2 loop-part BRANCH OFFSET
200 \       where OFFSET points back to condition (the beginning) and OFFSET2 points to after the whole piece of code
201 \ So this is like a while (condition) { loop-part } loop in the C language
202 : WHILE IMMEDIATE
203         ' 0BRANCH ,     \ compile 0BRANCH
204         HERE @          \ save location of the offset2 on the stack
205         0 ,             \ compile a dummy offset2
206 ;
207
208 : REPEAT IMMEDIATE
209         ' BRANCH ,      \ compile BRANCH
210         SWAP            \ get the original offset (from BEGIN)
211         HERE @ - ,      \ and compile it after BRANCH
212         DUP
213         HERE @ SWAP -   \ calculate the offset2
214         SWAP !          \ and back-fill it in the original location
215 ;
216
217 \       COMMENTS ----------------------------------------------------------------------
218 \
219 \ FORTH allows ( ... ) as comments within function definitions.  This works by having an IMMEDIATE
220 \ word called ( which just drops input characters until it hits the corresponding ).
221 : ( IMMEDIATE
222         1               \ allowed nested parens by keeping track of depth
223         BEGIN
224                 KEY             \ read next character
225                 DUP '(' = IF    \ open paren?
226                         DROP            \ drop the open paren
227                         1+              \ depth increases
228                 ELSE
229                         ')' = IF        \ close paren?
230                                 1-              \ depth decreases
231                         THEN
232                 THEN
233         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
234         DROP            \ drop the depth counter
235 ;
236
237 (
238         From now on we can use ( ... ) for comments.
239
240         STACK NOTATION ----------------------------------------------------------------------
241
242         In FORTH style we can also use ( ... -- ... ) to show the effects that a word has on the
243         parameter stack.  For example:
244
245         ( n -- )        means that the word consumes an integer (n) from the parameter stack.
246         ( b a -- c )    means that the word uses two integers (a and b, where a is at the top of stack)
247                                 and returns a single integer (c).
248         ( -- )          means the word has no effect on the stack
249 )
250
251 ( Some more complicated stack examples, showing the stack notation. )
252 : NIP ( x y -- y ) SWAP DROP ;
253 : TUCK ( x y -- y x y ) DUP ROT ;
254 : PICK ( x_u ... x_1 x_0 u -- x_u ... x_1 x_0 x_u )
255         1+              ( add one because of 'u' on the stack )
256         4 *             ( multiply by the word size )
257         DSP@ +          ( add to the stack pointer )
258         @               ( and fetch )
259 ;
260
261 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
262 : SPACES        ( n -- )
263         BEGIN
264                 DUP 0>          ( while n > 0 )
265         WHILE
266                 SPACE           ( print a space )
267                 1-              ( until we count down to 0 )
268         REPEAT
269         DROP
270 ;
271
272 ( Standard words for manipulating BASE. )
273 : DECIMAL ( -- ) 10 BASE ! ;
274 : HEX ( -- ) 16 BASE ! ;
275
276 (
277         PRINTING NUMBERS ----------------------------------------------------------------------
278
279         The standard FORTH word . (DOT) is very important.  It takes the number at the top
280         of the stack and prints it out.  However first I'm going to implement some lower-level
281         FORTH words:
282
283         U.R     ( u width -- )  which prints an unsigned number, padded to a certain width
284         U.      ( u -- )        which prints an unsigned number
285         .R      ( n width -- )  which prints a signed number, padded to a certain width.
286
287         For example:
288                 -123 6 .R
289         will print out these characters:
290                 <space> <space> - 1 2 3
291
292         In other words, the number padded left to a certain number of characters.
293
294         The full number is printed even if it is wider than width, and this is what allows us to
295         define the ordinary functions U. and . (we just set width to zero knowing that the full
296         number will be printed anyway).
297
298         Another wrinkle of . and friends is that they obey the current base in the variable BASE.
299         BASE can be anything in the range 2 to 36.
300
301         While we're defining . &c we can also define .S which is a useful debugging tool.  This
302         word prints the current stack (non-destructively) from top to bottom.
303 )
304
305 ( This is the underlying recursive definition of U. )
306 : U.            ( u -- )
307         BASE @ /MOD     ( width rem quot )
308         DUP 0<> IF      ( if quotient <> 0 then )
309                 RECURSE         ( print the quotient )
310         ELSE
311                 DROP            ( drop the zero quotient )
312         THEN
313
314         ( print the remainder )
315         DUP 10 < IF
316                 '0'             ( decimal digits 0..9 )
317         ELSE
318                 10 -            ( hex and beyond digits A..Z )
319                 'A'
320         THEN
321         +
322         EMIT
323 ;
324
325 (
326         FORTH word .S prints the contents of the stack.  It doesn't alter the stack.
327         Very useful for debugging.
328 )
329 : .S            ( -- )
330         DSP@            ( get current stack pointer )
331         BEGIN
332                 DUP S0 @ <
333         WHILE
334                 DUP @ U.        ( print the stack element )
335                 SPACE
336                 4+              ( move up )
337         REPEAT
338         DROP
339 ;
340
341 ( This word returns the width (in characters) of an unsigned number in the current base )
342 : UWIDTH        ( u -- width )
343         BASE @ /        ( rem quot )
344         DUP 0<> IF      ( if quotient <> 0 then )
345                 RECURSE 1+      ( return 1+recursive call )
346         ELSE
347                 DROP            ( drop the zero quotient )
348                 1               ( return 1 )
349         THEN
350 ;
351
352 : U.R           ( u width -- )
353         SWAP            ( width u )
354         DUP             ( width u u )
355         UWIDTH          ( width u uwidth )
356         -ROT            ( u uwidth width )
357         SWAP -          ( u width-uwidth )
358         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
359           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
360           a negative number of spaces anyway, so it's now safe to call SPACES ... )
361         SPACES
362         ( ... and then call the underlying implementation of U. )
363         U.
364 ;
365
366 (
367         .R prints a signed number, padded to a certain width.  We can't just print the sign
368         and call U.R because we want the sign to be next to the number ('-123' instead of '-  123').
369 )
370 : .R            ( n width -- )
371         SWAP            ( width n )
372         DUP 0< IF
373                 NEGATE          ( width u )
374                 1               ( save a flag to remember that it was negative | width n 1 )
375                 ROT             ( 1 width u )
376                 SWAP            ( 1 u width )
377                 1-              ( 1 u width-1 )
378         ELSE
379                 0               ( width u 0 )
380                 ROT             ( 0 width u )
381                 SWAP            ( 0 u width )
382         THEN
383         SWAP            ( flag width u )
384         DUP             ( flag width u u )
385         UWIDTH          ( flag width u uwidth )
386         -ROT            ( flag u uwidth width )
387         SWAP -          ( flag u width-uwidth )
388
389         SPACES          ( flag u )
390         SWAP            ( u flag )
391
392         IF                      ( was it negative? print the - character )
393                 '-' EMIT
394         THEN
395
396         U.
397 ;
398
399 ( Finally we can define word . in terms of .R, with a trailing space. )
400 : . 0 .R SPACE ;
401
402 ( The real U., note the trailing space. )
403 : U. U. SPACE ;
404
405 ( ? fetches the integer at an address and prints it. )
406 : ? ( addr -- ) @ . ;
407
408 ( c a b WITHIN returns true if a <= c and c < b )
409 : WITHIN
410         ROT             ( b c a )
411         OVER            ( b c a c )
412         <= IF
413                 > IF            ( b c -- )
414                         TRUE
415                 ELSE
416                         FALSE
417                 THEN
418         ELSE
419                 2DROP           ( b c -- )
420                 FALSE
421         THEN
422 ;
423
424 ( DEPTH returns the depth of the stack. )
425 : DEPTH         ( -- n )
426         S0 @ DSP@ -
427         4-                      ( adjust because S0 was on the stack when we pushed DSP )
428 ;
429
430 (
431         ALIGNED takes an address and rounds it up (aligns it) to the next 4 byte boundary.
432 )
433 : ALIGNED       ( addr -- addr )
434         3 + 3 INVERT AND        ( (addr+3) & ~3 )
435 ;
436
437 (
438         ALIGN aligns the HERE pointer, so the next word appended will be aligned properly.
439 )
440 : ALIGN HERE @ ALIGNED HERE ! ;
441
442 (
443         STRINGS ----------------------------------------------------------------------
444
445         S" string" is used in FORTH to define strings.  It leaves the address of the string and
446         its length on the stack, (length at the top of stack).  The space following S" is the normal
447         space between FORTH words and is not a part of the string.
448
449         This is tricky to define because it has to do different things depending on whether
450         we are compiling or in immediate mode.  (Thus the word is marked IMMEDIATE so it can
451         detect this and do different things).
452
453         In compile mode we append
454                 LITSTRING <string length> <string rounded up 4 bytes>
455         to the current word.  The primitive LITSTRING does the right thing when the current
456         word is executed.
457
458         In immediate mode there isn't a particularly good place to put the string, but in this
459         case we put the string at HERE (but we _don't_ change HERE).  This is meant as a temporary
460         location, likely to be overwritten soon after.
461 )
462 : S" IMMEDIATE          ( -- addr len )
463         STATE @ IF      ( compiling? )
464                 ' LITSTRING ,   ( compile LITSTRING )
465                 HERE @          ( save the address of the length word on the stack )
466                 0 ,             ( dummy length - we don't know what it is yet )
467                 BEGIN
468                         KEY             ( get next character of the string )
469                         DUP '"' <>
470                 WHILE
471                         HERE @ C!       ( store the character in the compiled image )
472                         1 HERE +!       ( increment HERE pointer by 1 byte )
473                 REPEAT
474                 DROP            ( drop the double quote character at the end )
475                 DUP             ( get the saved address of the length word )
476                 HERE @ SWAP -   ( calculate the length )
477                 4-              ( subtract 4 (because we measured from the start of the length word) )
478                 SWAP !          ( and back-fill the length location )
479                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
480         ELSE            ( immediate mode )
481                 HERE @          ( get the start address of the temporary space )
482                 BEGIN
483                         KEY
484                         DUP '"' <>
485                 WHILE
486                         OVER C!         ( save next character )
487                         1+              ( increment address )
488                 REPEAT
489                 DROP            ( drop the final " character )
490                 HERE @ -        ( calculate the length )
491                 HERE @          ( push the start address )
492                 SWAP            ( addr len )
493         THEN
494 ;
495
496 (
497         ." is the print string operator in FORTH.  Example: ." Something to print"
498         The space after the operator is the ordinary space required between words and is not
499         a part of what is printed.
500
501         In immediate mode we just keep reading characters and printing them until we get to
502         the next double quote.
503
504         In compile mode we use S" to store the string, then add TELL afterwards:
505                 LITSTRING <string length> <string rounded up to 4 bytes> TELL
506
507         It may be interesting to note the use of [COMPILE] to turn the call to the immediate
508         word S" into compilation of that word.  It compiles it into the definition of .",
509         not into the definition of the word being compiled when this is running (complicated
510         enough for you?)
511 )
512 : ." IMMEDIATE          ( -- )
513         STATE @ IF      ( compiling? )
514                 [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
515                 ' TELL ,        ( compile the final TELL )
516         ELSE
517                 ( In immediate mode, just read characters and print them until we get
518                   to the ending double quote. )
519                 BEGIN
520                         KEY
521                         DUP '"' = IF
522                                 DROP    ( drop the double quote character )
523                                 EXIT    ( return from this function )
524                         THEN
525                         EMIT
526                 AGAIN
527         THEN
528 ;
529
530 (
531         CONSTANTS AND VARIABLES ----------------------------------------------------------------------
532
533         In FORTH, global constants and variables are defined like this:
534
535         10 CONSTANT TEN         when TEN is executed, it leaves the integer 10 on the stack
536         VARIABLE VAR            when VAR is executed, it leaves the address of VAR on the stack
537
538         Constants can be read but not written, eg:
539
540         TEN . CR                prints 10
541
542         You can read a variable (in this example called VAR) by doing:
543
544         VAR @                   leaves the value of VAR on the stack
545         VAR @ . CR              prints the value of VAR
546         VAR ? CR                same as above, since ? is the same as @ .
547
548         and update the variable by doing:
549
550         20 VAR !                sets VAR to 20
551
552         Note that variables are uninitialised (but see VALUE later on which provides initialised
553         variables with a slightly simpler syntax).
554
555         How can we define the words CONSTANT and VARIABLE?
556
557         The trick is to define a new word for the variable itself (eg. if the variable was called
558         'VAR' then we would define a new word called VAR).  This is easy to do because we exposed
559         dictionary entry creation through the CREATE word (part of the definition of : above).
560         A call to CREATE TEN leaves the dictionary entry:
561
562                                    +--- HERE
563                                    |
564                                    V
565         +---------+---+---+---+---+
566         | LINK    | 3 | T | E | N |
567         +---------+---+---+---+---+
568                    len
569
570         For CONSTANT we can continue by appending DOCOL (the codeword), then LIT followed by
571         the constant itself and then EXIT, forming a little word definition that returns the
572         constant:
573
574         +---------+---+---+---+---+------------+------------+------------+------------+
575         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
576         +---------+---+---+---+---+------------+------------+------------+------------+
577                    len              codeword
578
579         Notice that this word definition is exactly the same as you would have got if you had
580         written : TEN 10 ;
581
582         Note for people reading the code below: DOCOL is a constant word which we defined in the
583         assembler part which returns the value of the assembler symbol of the same name.
584 )
585 : CONSTANT
586         CREATE          ( make the dictionary entry (the name follows CONSTANT) )
587         DOCOL ,         ( append DOCOL (the codeword field of this word) )
588         ' LIT ,         ( append the codeword LIT )
589         ,               ( append the value on the top of the stack )
590         ' EXIT ,        ( append the codeword EXIT )
591 ;
592
593 (
594         VARIABLE is a little bit harder because we need somewhere to put the variable.  There is
595         nothing particularly special about the 'user definitions area' (the area of memory pointed
596         to by HERE where we have previously just stored new word definitions).  We can slice off
597         bits of this memory area to store anything we want, so one possible definition of
598         VARIABLE might create this:
599
600            +--------------------------------------------------------------+
601            |                                                              |
602            V                                                              |
603         +---------+---------+---+---+---+---+------------+------------+---|--------+------------+
604         | <var>   | LINK    | 3 | V | A | R | DOCOL      | LIT        | <addr var> | EXIT       |
605         +---------+---------+---+---+---+---+------------+------------+------------+------------+
606                              len              codeword
607
608         where <var> is the place to store the variable, and <addr var> points back to it.
609
610         To make this more general let's define a couple of words which we can use to allocate
611         arbitrary memory from the user definitions area.
612
613         First ALLOT, where n ALLOT allocates n bytes of memory.  (Note when calling this that
614         it's a very good idea to make sure that n is a multiple of 4, or at least that next time
615         a word is compiled that HERE has been left as a multiple of 4).
616 )
617 : ALLOT         ( n -- addr )
618         HERE @ SWAP     ( here n )
619         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
620 ;
621
622 (
623         Second, CELLS.  In FORTH the phrase 'n CELLS ALLOT' means allocate n integers of whatever size
624         is the natural size for integers on this machine architecture.  On this 32 bit machine therefore
625         CELLS just multiplies the top of stack by 4.
626 )
627 : CELLS ( n -- n ) 4 * ;
628
629 (
630         So now we can define VARIABLE easily in much the same way as CONSTANT above.  Refer to the
631         diagram above to see what the word that this creates will look like.
632 )
633 : VARIABLE
634         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
635         CREATE          ( make the dictionary entry (the name follows VARIABLE) )
636         DOCOL ,         ( append DOCOL (the codeword field of this word) )
637         ' LIT ,         ( append the codeword LIT )
638         ,               ( append the pointer to the new memory )
639         ' EXIT ,        ( append the codeword EXIT )
640 ;
641
642 (
643         VALUES ----------------------------------------------------------------------
644
645         VALUEs are like VARIABLEs but with a simpler syntax.  You would generally use them when you
646         want a variable which is read often, and written infrequently.
647
648         20 VALUE VAL    creates VAL with initial value 20
649         VAL             pushes the value directly on the stack
650         30 TO VAL       updates VAL, setting it to 30
651
652         Notice that 'VAL' on its own doesn't return the address of the value, but the value itself,
653         making values simpler and more obvious to use than variables (no indirection through '@').
654         The price is a more complicated implementation, although despite the complexity there is no
655         performance penalty at runtime.
656
657         A naive implementation of 'TO' would be quite slow, involving a dictionary search each time.
658         But because this is FORTH we have complete control of the compiler so we can compile TO more
659         efficiently, turning:
660                 TO VAL
661         into:
662                 LIT <addr> !
663         and calculating <addr> (the address of the value) at compile time.
664
665         Now this is the clever bit.  We'll compile our value like this:
666
667         +---------+---+---+---+---+------------+------------+------------+------------+
668         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
669         +---------+---+---+---+---+------------+------------+------------+------------+
670                    len              codeword
671
672         where <value> is the actual value itself.  Note that when VAL executes, it will push the
673         value on the stack, which is what we want.
674
675         But what will TO use for the address <addr>?  Why of course a pointer to that <value>:
676
677                 code compiled   - - - - --+------------+------------+------------+-- - - - -
678                 by TO VAL                 | LIT        | <addr>     | !          |
679                                 - - - - --+------------+-----|------+------------+-- - - - -
680                                                              |
681                                                              V
682         +---------+---+---+---+---+------------+------------+------------+------------+
683         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
684         +---------+---+---+---+---+------------+------------+------------+------------+
685                    len              codeword
686
687         In other words, this is a kind of self-modifying code.
688
689         (Note to the people who want to modify this FORTH to add inlining: values defined this
690         way cannot be inlined).
691 )
692 : VALUE         ( n -- )
693         CREATE          ( make the dictionary entry (the name follows VALUE) )
694         DOCOL ,         ( append DOCOL )
695         ' LIT ,         ( append the codeword LIT )
696         ,               ( append the initial value )
697         ' EXIT ,        ( append the codeword EXIT )
698 ;
699
700 : TO IMMEDIATE  ( n -- )
701         WORD            ( get the name of the value )
702         FIND            ( look it up in the dictionary )
703         >DFA            ( get a pointer to the first data field (the 'LIT') )
704         4+              ( increment to point at the value )
705         STATE @ IF      ( compiling? )
706                 ' LIT ,         ( compile LIT )
707                 ,               ( compile the address of the value )
708                 ' ! ,           ( compile ! )
709         ELSE            ( immediate mode )
710                 !               ( update it straightaway )
711         THEN
712 ;
713
714 ( x +TO VAL adds x to VAL )
715 : +TO IMMEDIATE
716         WORD            ( get the name of the value )
717         FIND            ( look it up in the dictionary )
718         >DFA            ( get a pointer to the first data field (the 'LIT') )
719         4+              ( increment to point at the value )
720         STATE @ IF      ( compiling? )
721                 ' LIT ,         ( compile LIT )
722                 ,               ( compile the address of the value )
723                 ' +! ,          ( compile +! )
724         ELSE            ( immediate mode )
725                 +!              ( update it straightaway )
726         THEN
727 ;
728
729 (
730         PRINTING THE DICTIONARY ----------------------------------------------------------------------
731
732         ID. takes an address of a dictionary entry and prints the word's name.
733
734         For example: LATEST @ ID. would print the name of the last word that was defined.
735 )
736 : ID.
737         4+              ( skip over the link pointer )
738         DUP C@          ( get the flags/length byte )
739         F_LENMASK AND   ( mask out the flags - just want the length )
740
741         BEGIN
742                 DUP 0>          ( length > 0? )
743         WHILE
744                 SWAP 1+         ( addr len -- len addr+1 )
745                 DUP C@          ( len addr -- len addr char | get the next character)
746                 EMIT            ( len addr char -- len addr | and print it)
747                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
748         REPEAT
749         2DROP           ( len addr -- )
750 ;
751
752 (
753         'WORD word FIND ?HIDDEN' returns true if 'word' is flagged as hidden.
754
755         'WORD word FIND ?IMMEDIATE' returns true if 'word' is flagged as immediate.
756 )
757 : ?HIDDEN
758         4+              ( skip over the link pointer )
759         C@              ( get the flags/length byte )
760         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
761 ;
762 : ?IMMEDIATE
763         4+              ( skip over the link pointer )
764         C@              ( get the flags/length byte )
765         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
766 ;
767
768 (
769         WORDS prints all the words defined in the dictionary, starting with the word defined most recently.
770         However it doesn't print hidden words.
771
772         The implementation simply iterates backwards from LATEST using the link pointers.
773 )
774 : WORDS
775         LATEST @        ( start at LATEST dictionary entry )
776         BEGIN
777                 DUP 0<>         ( while link pointer is not null )
778         WHILE
779                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
780                         DUP ID.         ( but if not hidden, print the word )
781                 THEN
782                 SPACE
783                 @               ( dereference the link pointer - go to previous word )
784         REPEAT
785         DROP
786         CR
787 ;
788
789 (
790         FORGET ----------------------------------------------------------------------
791
792         So far we have only allocated words and memory.  FORTH provides a rather primitive method
793         to deallocate.
794
795         'FORGET word' deletes the definition of 'word' from the dictionary and everything defined
796         after it, including any variables and other memory allocated after.
797
798         The implementation is very simple - we look up the word (which returns the dictionary entry
799         address).  Then we set HERE to point to that address, so in effect all future allocations
800         and definitions will overwrite memory starting at the word.  We also need to set LATEST to
801         point to the previous word.
802
803         Note that you cannot FORGET built-in words (well, you can try but it will probably cause
804         a segfault).
805
806         XXX: Because we wrote VARIABLE to store the variable in memory allocated before the word,
807         in the current implementation VARIABLE FOO FORGET FOO will leak 1 cell of memory.
808 )
809 : FORGET
810         WORD FIND       ( find the word, gets the dictionary entry address )
811         DUP @ LATEST !  ( set LATEST to point to the previous word )
812         HERE !          ( and store HERE with the dictionary address )
813 ;
814
815 (
816         DUMP ----------------------------------------------------------------------
817
818         DUMP is used to dump out the contents of memory, in the 'traditional' hexdump format.
819
820         Notice that the parameters to DUMP (address, length) are compatible with string words
821         such as WORD and S".
822 )
823 : DUMP          ( addr len -- )
824         BASE @ ROT              ( save the current BASE at the bottom of the stack )
825         HEX                     ( and switch the hexadecimal mode )
826
827         BEGIN
828                 DUP 0>          ( while len > 0 )
829         WHILE
830                 OVER 8 U.R      ( print the address )
831                 SPACE
832
833                 ( print up to 16 words on this line )
834                 2DUP            ( addr len addr len )
835                 1- 15 AND 1+    ( addr len addr linelen )
836                 BEGIN
837                         DUP 0>          ( while linelen > 0 )
838                 WHILE
839                         SWAP            ( addr len linelen addr )
840                         DUP C@          ( addr len linelen addr byte )
841                         2 .R SPACE      ( print the byte )
842                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
843                 REPEAT
844                 2DROP           ( addr len )
845
846                 ( print the ASCII equivalents )
847                 2DUP 1- 15 AND 1+ ( addr len addr linelen )
848                 BEGIN
849                         DUP 0>          ( while linelen > 0)
850                 WHILE
851                         SWAP            ( addr len linelen addr )
852                         DUP C@          ( addr len linelen addr byte )
853                         DUP 32 128 WITHIN IF    ( 32 <= c < 128? )
854                                 EMIT
855                         ELSE
856                                 DROP '.' EMIT
857                         THEN
858                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
859                 REPEAT
860                 2DROP           ( addr len )
861                 CR
862
863                 DUP 1- 15 AND 1+ ( addr len linelen )
864                 DUP             ( addr len linelen linelen )
865                 ROT             ( addr linelen len linelen )
866                 -               ( addr linelen len-linelen )
867                 ROT             ( len-linelen addr linelen )
868                 +               ( len-linelen addr+linelen )
869                 SWAP            ( addr-linelen len-linelen )
870         REPEAT
871
872         2DROP                   ( restore stack )
873         BASE !                  ( restore saved BASE )
874 ;
875
876 (
877         CASE ----------------------------------------------------------------------
878
879         CASE...ENDCASE is how we do switch statements in FORTH.  There is no generally
880         agreed syntax for this, so I've gone for the syntax mandated by the ISO standard
881         FORTH (ANS-FORTH).
882
883         ( some value on the stack )
884         CASE
885         test1 OF ... ENDOF
886         test2 OF ... ENDOF
887         testn OF ... ENDOF
888         ... ( default case )
889         ENDCASE
890
891         The CASE statement tests the value on the stack by comparing it for equality with
892         test1, test2, ..., testn and executes the matching piece of code within OF ... ENDOF.
893         If none of the test values match then the default case is executed.  Inside the ... of
894         the default case, the value is still at the top of stack (it is implicitly DROP-ed
895         by ENDCASE).  When ENDOF is executed it jumps after ENDCASE (ie. there is no "fall-through"
896         and no need for a break statement like in C).
897
898         The default case may be omitted.  In fact the tests may also be omitted so that you
899         just have a default case, although this is probably not very useful.
900
901         An example (assuming that 'q', etc. are words which push the ASCII value of the letter
902         on the stack):
903
904         0 VALUE QUIT
905         0 VALUE SLEEP
906         KEY CASE
907                 'q' OF 1 TO QUIT ENDOF
908                 's' OF 1 TO SLEEP ENDOF
909                 ( default case: )
910                 ." Sorry, I didn't understand key <" DUP EMIT ." >, try again." CR
911         ENDCASE
912
913         (In some versions of FORTH, more advanced tests are supported, such as ranges, etc.
914         Other versions of FORTH need you to write OTHERWISE to indicate the default case.
915         As I said above, this FORTH tries to follow the ANS FORTH standard).
916
917         The implementation of CASE...ENDCASE is somewhat non-trivial.  I'm following the
918         implementations from here:
919         http://www.uni-giessen.de/faq/archiv/forthfaq.case_endcase/msg00000.html
920
921         The general plan is to compile the code as a series of IF statements:
922
923         CASE                            (push 0 on the immediate-mode parameter stack)
924         test1 OF ... ENDOF              test1 OVER = IF DROP ... ELSE
925         test2 OF ... ENDOF              test2 OVER = IF DROP ... ELSE
926         testn OF ... ENDOF              testn OVER = IF DROP ... ELSE
927         ... ( default case )            ...
928         ENDCASE                         DROP THEN [THEN [THEN ...]]
929
930         The CASE statement pushes 0 on the immediate-mode parameter stack, and that number
931         is used to count how many THEN statements we need when we get to ENDCASE so that each
932         IF has a matching THEN.  The counting is done implicitly.  If you recall from the
933         implementation above of IF, each IF pushes a code address on the immediate-mode stack,
934         and these addresses are non-zero, so by the time we get to ENDCASE the stack contains
935         some number of non-zeroes, followed by a zero.  The number of non-zeroes is how many
936         times IF has been called, so how many times we need to match it with THEN.
937
938         This code uses [COMPILE] so that we compile calls to IF, ELSE, THEN instead of
939         actually calling them while we're compiling the words below.
940
941         As is the case with all of our control structures, they only work within word
942         definitions, not in immediate mode.
943 )
944 : CASE IMMEDIATE
945         0               ( push 0 to mark the bottom of the stack )
946 ;
947
948 : OF IMMEDIATE
949         ' OVER ,        ( compile OVER )
950         ' = ,           ( compile = )
951         [COMPILE] IF    ( compile IF )
952         ' DROP ,        ( compile DROP )
953 ;
954
955 : ENDOF IMMEDIATE
956         [COMPILE] ELSE  ( ENDOF is the same as ELSE )
957 ;
958
959 : ENDCASE IMMEDIATE
960         ' DROP ,        ( compile DROP )
961
962         ( keep compiling THEN until we get to our zero marker )
963         BEGIN
964                 ?DUP
965         WHILE
966                 [COMPILE] THEN
967         REPEAT
968 ;
969
970 (
971         DECOMPILER ----------------------------------------------------------------------
972
973         CFA> is the opposite of >CFA.  It takes a codeword and tries to find the matching
974         dictionary definition.
975
976         In this FORTH this is not so easy.  In fact we have to search through the dictionary
977         because we don't have a convenient back-pointer (as is often the case in other versions
978         of FORTH).
979
980         This word returns 0 if it doesn't find a match.
981 )
982 : CFA>
983         LATEST @        ( start at LATEST dictionary entry )
984         BEGIN
985                 DUP 0<>         ( while link pointer is not null )
986         WHILE
987                 DUP >CFA        ( cfa curr curr-cfa )
988                 2 PICK          ( cfa curr curr-cfa cfa )
989                 = IF            ( found a match? )
990                         NIP             ( leave curr dictionary entry on the stack )
991                         EXIT            ( and return from the function )
992                 THEN
993                 @               ( follow link pointer back )
994         REPEAT
995         2DROP           ( restore stack )
996         0               ( sorry, nothing found )
997 ;
998
999 (
1000         SEE decompiles a FORTH word.
1001
1002         We search for the dictionary entry of the word, then search again for the next
1003         word (effectively, the end of the compiled word).  This results in two pointers:
1004
1005         +---------+---+---+---+---+------------+------------+------------+------------+
1006         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
1007         +---------+---+---+---+---+------------+------------+------------+------------+
1008          ^                                                                             ^
1009          |                                                                             |
1010         Start of word                                                         End of word
1011
1012         With this information we can have a go at decompiling the word.  We need to
1013         recognise "meta-words" like LIT, LITSTRING, BRANCH, etc. and treat those separately.
1014 )
1015 : SEE
1016         WORD FIND       ( find the dictionary entry to decompile )
1017
1018         ( Now we search again, looking for the next word in the dictionary.  This gives us
1019           the length of the word that we will be decompiling.  (Well, mostly it does). )
1020         HERE @          ( address of the end of the last compiled word )
1021         LATEST @        ( word last curr )
1022         BEGIN
1023                 2 PICK          ( word last curr word )
1024                 OVER            ( word last curr word curr )
1025                 <>              ( word last curr word<>curr? )
1026         WHILE                   ( word last curr )
1027                 NIP             ( word curr )
1028                 DUP @           ( word curr prev (which becomes: word last curr) )
1029         REPEAT
1030
1031         DROP            ( at this point, the stack is: start-of-word end-of-word )
1032         SWAP            ( end-of-word start-of-word )
1033
1034         ( begin the definition with : NAME [IMMEDIATE] )
1035         ':' EMIT SPACE DUP ID. SPACE
1036         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN
1037
1038         >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
1039
1040         ( now we start decompiling until we hit the end of the word )
1041         BEGIN           ( end start )
1042                 2DUP >
1043         WHILE
1044                 DUP @           ( end start codeword )
1045
1046                 CASE
1047                 ' LIT OF                ( is it LIT ? )
1048                         4 + DUP @               ( get next word which is the integer constant )
1049                         .                       ( and print it )
1050                 ENDOF
1051                 ' LITSTRING OF          ( is it LITSTRING ? )
1052                         [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
1053                         4 + DUP @               ( get the length word )
1054                         SWAP 4 + SWAP           ( end start+4 length )
1055                         2DUP TELL               ( print the string )
1056                         '"' EMIT SPACE          ( finish the string with a final quote )
1057                         + ALIGNED               ( end start+4+len, aligned )
1058                         4 -                     ( because we're about to add 4 below )
1059                 ENDOF
1060                 ' 0BRANCH OF            ( is it 0BRANCH ? )
1061                         ." 0BRANCH ( "
1062                         4 + DUP @               ( print the offset )
1063                         .
1064                         ')' EMIT SPACE
1065                 ENDOF
1066                 ' BRANCH OF             ( is it BRANCH ? )
1067                         ." BRANCH ( "
1068                         4 + DUP @               ( print the offset )
1069                         .
1070                         ')' EMIT SPACE
1071                 ENDOF
1072                 ' ' OF                  ( is it ' (TICK) ? )
1073                         [ CHAR ' ] LITERAL EMIT SPACE
1074                         4 + DUP @               ( get the next codeword )
1075                         CFA>                    ( and force it to be printed as a dictionary entry )
1076                         ID. SPACE
1077                 ENDOF
1078                 ' EXIT OF               ( is it EXIT? )
1079                         ( We expect the last word to be EXIT, and if it is then we don't print it
1080                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
1081                           of words, and then it needs to be printed. )
1082                         2DUP                    ( end start end start )
1083                         4 +                     ( end start end start+4 )
1084                         <> IF                   ( end start | we're not at the end )
1085                                 ." EXIT "
1086                         THEN
1087                 ENDOF
1088                                         ( default case: )
1089                         DUP                     ( in the default case we always need to DUP before using )
1090                         CFA>                    ( look up the codeword to get the dictionary entry )
1091                         ID. SPACE               ( and print it )
1092                 ENDCASE
1093
1094                 4 +             ( end start+4 )
1095         REPEAT
1096
1097         ';' EMIT CR
1098
1099         2DROP           ( restore stack )
1100 ;
1101
1102 (
1103         DOES> ----------------------------------------------------------------------
1104
1105         CREATE ... DOES> is a tricky construct allowing you to create words which create other words.
1106         For example CONSTANT (defined above) is a word which creates words, and it could have been
1107         written as follows:
1108
1109                 : CONSTANT CREATE DOCOL , , DOES> @ ;
1110
1111         Even explaining what DOES> is supposed to do is tricky.  It's possible that the implementation
1112         is easier to understand than the explanation.
1113
1114         If we look at the definition of CONSTANT here, and remember that when it is called the value
1115         of the constant is on the stack and the name follows.  So first CREATE makes the header of a
1116         new word with the name.  Secondly the codeword is set to DOCOL.  Thirdly , (COMMA) takes the
1117         value off the stack and adds it to the definition.  At this point (just before executing DOES>)
1118         the word looks like this:
1119
1120           ________ CREATE _______   _ DOCOL ,_   ____ , ___
1121          /                       \ /          \ /          \
1122         +---------+---+---+---+---+------------+------------+
1123         | LINK    | 3 | T | E | N | DOCOL      | 10         |
1124         +---------+---+---+---+---+------------+------------+
1125             ^      len              codeword
1126             |
1127           LATEST
1128
1129         
1130 )
1131
1132
1133
1134
1135 : DOES>
1136         R> LATEST @ >DFA !
1137 ;
1138
1139 (
1140         C STRINGS ----------------------------------------------------------------------
1141
1142         FORTH strings are represented by a start address and length kept on the stack or in memory.
1143
1144         Most FORTHs don't handle C strings, but we need them in order to access the process arguments
1145         and environment left on the stack by the Linux kernel.
1146
1147         The main function we need is STRLEN which works out the length of a C string.  DUP STRLEN is
1148         a common idiom which 'converts' a C string into a FORTH string.  (For example, DUP STRLEN TELL
1149         prints a C string).
1150 )
1151
1152 ( STRLEN returns the length of a C string )
1153 : STRLEN        ( str -- len )
1154         DUP             ( save start address )
1155         BEGIN
1156                 DUP C@ 0<>      ( zero byte found? )
1157         WHILE
1158                 1+
1159         REPEAT
1160
1161         SWAP -          ( calculate the length )
1162 ;
1163
1164 (
1165         STRNCMP compares two strings up to a length.  As with C's strncmp it returns 0 if they
1166         are equal, or a number > 0 or < 0 indicating their order.
1167 )
1168 : STRNCMP       ( str1 str2 len -- eq? )
1169         BEGIN
1170                 ?DUP
1171         WHILE
1172                 ROT             ( len str1 str2 )
1173                 DUP C@          ( len str1 str2 char2 )
1174                 2 PICK C@       ( len str1 str2 char2 char1 )
1175                 OVER            ( len str1 str2 char2 char1 char2 )
1176                 -               ( len str1 str2 char2 char1-char2 )
1177
1178                 ?DUP IF         ( strings not the same at this position? )
1179                         NIP             ( len str1 str2 diff )
1180                         ROT             ( len diff str1 str2 )
1181                         DROP DROP       ( len diff )
1182                         NIP             ( diff )
1183                         EXIT
1184                 THEN
1185
1186                 0= IF           ( characters are equal, but is this the end of the C string? )
1187                         DROP DROP DROP
1188                         0
1189                         EXIT
1190                 THEN
1191
1192                 1+              ( len str1 str2+1 )
1193                 ROT             ( str2+1 len str1 )
1194                 1+ ROT          ( str1+1 str2+1 len )
1195                 1-              ( str1+1 str2+1 len-1 )
1196         REPEAT
1197
1198         2DROP           ( restore stack )
1199         0               ( equal )
1200 ;
1201
1202 (
1203         THE ENVIRONMENT ----------------------------------------------------------------------
1204
1205         Linux makes the process arguments and environment available to us on the stack.
1206
1207         The top of stack pointer is saved by the early assembler code when we start up in the FORTH
1208         variable S0, and starting at this pointer we can read out the command line arguments and the
1209         environment.
1210
1211         Starting at S0, S0 itself points to argc (the number of command line arguments).
1212
1213         S0+4 points to argv[0], S0+8 points to argv[1] etc up to argv[argc-1].
1214
1215         argv[argc] is a NULL pointer.
1216
1217         After that the stack contains environment variables, a set of pointers to strings of the
1218         form NAME=VALUE and on until we get to another NULL pointer.
1219
1220         The first word that we define, ARGC, pushes the number of command line arguments (note that
1221         as with C argc, this includes the name of the command).
1222 )
1223 : ARGC
1224         S0 @ @
1225 ;
1226
1227 (
1228         n ARGV gets the nth command line argument.
1229
1230         For example to print the command name you would do:
1231                 0 ARGV TELL CR
1232 )
1233 : ARGV ( n -- str u )
1234         1+ CELLS S0 @ + ( get the address of argv[n] entry )
1235         @               ( get the address of the string )
1236         DUP STRLEN      ( and get its length / turn it into a FORTH string )
1237 ;
1238
1239 (
1240         ENVIRON returns the address of the first environment string.  The list of strings ends
1241         with a NULL pointer.
1242
1243         For example to print the first string in the environment you could do:
1244                 ENVIRON @ DUP STRLEN TELL
1245 )
1246 : ENVIRON       ( -- addr )
1247         ARGC            ( number of command line parameters on the stack to skip )
1248         2 +             ( skip command line count and NULL pointer after the command line args )
1249         CELLS           ( convert to an offset )
1250         S0 @ +          ( add to base stack address )
1251 ;
1252
1253 (
1254         ANS FORTH ----------------------------------------------------------------------
1255
1256         From this point we're trying to fill in the missing parts of the ISO standard, commonly
1257         referred to as ANS FORTH.
1258
1259         http://www.taygeta.com/forth/dpans.html
1260         http://www.taygeta.com/forth/dpansf.htm (list of words)
1261 )
1262 ( BL pushes the ASCII character code of space on the stack. )
1263 : BL 32 ;
1264
1265 ( C, writes a byte at the HERE pointer. )
1266 : C, HERE @ C! 1 HERE +! ;
1267
1268
1269
1270 ( Finally print the welcome prompt. )
1271 ." JONESFORTH VERSION " VERSION . CR
1272 ." OK "