Rename @b -> C@ etc.
[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.4 2007-09-25 21:48:20 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 : 'A' [ CHAR A ] LITERAL ;
107 : '0' [ CHAR 0 ] LITERAL ;
108 : '-' [ CHAR - ] LITERAL ;
109
110 \ While compiling, '[COMPILE] word' compiles 'word' if it would otherwise be IMMEDIATE.
111 : [COMPILE] IMMEDIATE
112         WORD            \ get the next word
113         FIND            \ find it in the dictionary
114         >CFA            \ get its codeword
115         ,               \ and compile that
116 ;
117
118 \ RECURSE makes a recursive call to the current word that is being compiled.
119 \
120 \ Normally while a word is being compiled, it is marked HIDDEN so that references to the
121 \ same word within are calls to the previous definition of the word.  However we still have
122 \ access to the word which we are currently compiling through the LATEST pointer so we
123 \ can use that to compile a recursive call.
124 : RECURSE IMMEDIATE
125         LATEST @        \ LATEST points to the word being compiled at the moment
126         >CFA            \ get the codeword
127         ,               \ compile it
128 ;
129
130 \ So far we have defined only very simple definitions.  Before we can go further, we really need to
131 \ make some control structures, like IF ... THEN and loops.  Luckily we can define arbitrary control
132 \ structures directly in FORTH.
133 \
134 \ Please note that the control structures as I have defined them here will only work inside compiled
135 \ words.  If you try to type in expressions using IF, etc. in immediate mode, then they won't work.
136 \ Making these work in immediate mode is left as an exercise for the reader.
137
138 \ condition IF true-part THEN rest
139 \       -- compiles to: --> condition 0BRANCH OFFSET true-part rest
140 \       where OFFSET is the offset of 'rest'
141 \ condition IF true-part ELSE false-part THEN
142 \       -- compiles to: --> condition 0BRANCH OFFSET true-part BRANCH OFFSET2 false-part rest
143 \       where OFFSET if the offset of false-part and OFFSET2 is the offset of rest
144
145 \ IF is an IMMEDIATE word which compiles 0BRANCH followed by a dummy offset, and places
146 \ the address of the 0BRANCH on the stack.  Later when we see THEN, we pop that address
147 \ off the stack, calculate the offset, and back-fill the offset.
148 : IF IMMEDIATE
149         ' 0BRANCH ,     \ compile 0BRANCH
150         HERE @          \ save location of the offset on the stack
151         0 ,             \ compile a dummy offset
152 ;
153
154 : THEN IMMEDIATE
155         DUP
156         HERE @ SWAP -   \ calculate the offset from the address saved on the stack
157         SWAP !          \ store the offset in the back-filled location
158 ;
159
160 : ELSE IMMEDIATE
161         ' BRANCH ,      \ definite branch to just over the false-part
162         HERE @          \ save location of the offset on the stack
163         0 ,             \ compile a dummy offset
164         SWAP            \ now back-fill the original (IF) offset
165         DUP             \ same as for THEN word above
166         HERE @ SWAP -
167         SWAP !
168 ;
169
170 \ BEGIN loop-part condition UNTIL
171 \       -- compiles to: --> loop-part condition 0BRANCH OFFSET
172 \       where OFFSET points back to the loop-part
173 \ This is like do { loop-part } while (condition) in the C language
174 : BEGIN IMMEDIATE
175         HERE @          \ save location on the stack
176 ;
177
178 : UNTIL IMMEDIATE
179         ' 0BRANCH ,     \ compile 0BRANCH
180         HERE @ -        \ calculate the offset from the address saved on the stack
181         ,               \ compile the offset here
182 ;
183
184 \ BEGIN loop-part AGAIN
185 \       -- compiles to: --> loop-part BRANCH OFFSET
186 \       where OFFSET points back to the loop-part
187 \ In other words, an infinite loop which can only be returned from with EXIT
188 : AGAIN IMMEDIATE
189         ' BRANCH ,      \ compile BRANCH
190         HERE @ -        \ calculate the offset back
191         ,               \ compile the offset here
192 ;
193
194 \ BEGIN condition WHILE loop-part REPEAT
195 \       -- compiles to: --> condition 0BRANCH OFFSET2 loop-part BRANCH OFFSET
196 \       where OFFSET points back to condition (the beginning) and OFFSET2 points to after the whole piece of code
197 \ So this is like a while (condition) { loop-part } loop in the C language
198 : WHILE IMMEDIATE
199         ' 0BRANCH ,     \ compile 0BRANCH
200         HERE @          \ save location of the offset2 on the stack
201         0 ,             \ compile a dummy offset2
202 ;
203
204 : REPEAT IMMEDIATE
205         ' BRANCH ,      \ compile BRANCH
206         SWAP            \ get the original offset (from BEGIN)
207         HERE @ - ,      \ and compile it after BRANCH
208         DUP
209         HERE @ SWAP -   \ calculate the offset2
210         SWAP !          \ and back-fill it in the original location
211 ;
212
213 \ FORTH allows ( ... ) as comments within function definitions.  This works by having an IMMEDIATE
214 \ word called ( which just drops input characters until it hits the corresponding ).
215 : ( IMMEDIATE
216         1               \ allowed nested parens by keeping track of depth
217         BEGIN
218                 KEY             \ read next character
219                 DUP '(' = IF    \ open paren?
220                         DROP            \ drop the open paren
221                         1+              \ depth increases
222                 ELSE
223                         ')' = IF        \ close paren?
224                                 1-              \ depth decreases
225                         THEN
226                 THEN
227         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
228         DROP            \ drop the depth counter
229 ;
230
231 (
232         From now on we can use ( ... ) for comments.
233
234         In FORTH style we can also use ( ... -- ... ) to show the effects that a word has on the
235         parameter stack.  For example:
236
237         ( n -- )        means that the word consumes an integer (n) from the parameter stack.
238         ( b a -- c )    means that the word uses two integers (a and b, where a is at the top of stack)
239                                 and returns a single integer (c).
240         ( -- )          means the word has no effect on the stack
241 )
242
243 ( Standard words for manipulating BASE. )
244 : DECIMAL ( -- ) 10 BASE ! ;
245 : HEX ( -- ) 16 BASE ! ;
246
247 (
248         The standard FORTH word . (DOT) is very important.  It takes the number at the top
249         of the stack and prints it out.  However first I'm going to implement some lower-level
250         FORTH words:
251
252         U.R     ( u width -- )  which prints an unsigned number, padded to a certain width
253         U.      ( u -- )        which prints an unsigned number
254         .R      ( n width -- )  which prints a signed number, padded to a certain width.
255
256         For example:
257                 -123 6 .R
258         will print out these characters:
259                 <space> <space> - 1 2 3
260
261         In other words, the number padded left to a certain number of characters.
262
263         The full number is printed even if it is wider than width, and this is what allows us to
264         define the ordinary functions U. and . (we just set width to zero knowing that the full
265         number will be printed anyway).
266
267         Another wrinkle of . and friends is that they obey the current base in the variable BASE.
268         BASE can be anything in the range 2 to 36.
269 )
270 : U.R           ( u width -- )
271         ( DROP XXX )
272         BASE @ /MOD     ( width rem quot )
273         DUP 0<> IF      ( if quotient <> 0 then )
274                 RECURSE         ( print the quotient )
275         ELSE
276                 DROP            ( drop the zero quotient )
277         THEN
278
279         ( print the remainder )
280         DUP 10 < IF
281                 '0'             ( decimal digits 0..9 )
282         ELSE
283                 10 -            ( hex and beyond digits A..Z )
284                 'A'
285         THEN
286         +
287         EMIT
288 ;
289
290 ( U. is easy to define in terms of U.R  Note the trailing space. )
291 : U. 0 U.R SPACE ;
292
293 ( .R is easy, we just need to print the sign and then call U.R )
294 : .R            ( n width -- )
295         SWAP            ( width n )
296         DUP 0< IF
297                 '-' EMIT        ( print the sign )
298                 NEGATE          ( negate the number so we can use U.R )
299                 SWAP 1-         ( n width-1 )
300         ELSE
301                 SWAP            ( n width )
302         THEN
303         DROP ( XXX )
304         U.R
305 ;
306
307 ( Finally we can define word . in terms of .R, with a trailing space. )
308 : . 0 .R SPACE ;
309
310 ( ? fetches the integer at an address and prints it. )
311 : ? @ . ;
312
313 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
314 : SPACES        ( n -- )
315         BEGIN
316                 DUP 0>          ( while n > 0 )
317         WHILE
318                 SPACE           ( print a space )
319                 1-              ( until we count down to 0 )
320         REPEAT
321         DROP
322 ;
323
324 ( c a b WITHIN returns true if a <= c and c < b )
325 : WITHIN
326         ROT             ( b c a )
327         OVER            ( b c a c )
328         <= IF
329                 > IF            ( b c -- )
330                         TRUE
331                 ELSE
332                         FALSE
333                 THEN
334         ELSE
335                 2DROP           ( b c -- )
336                 FALSE
337         THEN
338 ;
339
340 ( .S prints the contents of the stack.  Very useful for debugging. )
341 : .S            ( -- )
342         DSP@            ( get current stack pointer )
343         BEGIN
344                 DUP S0 @ <
345         WHILE
346                 DUP @ .         ( print the stack element )
347                 4+              ( move up )
348         REPEAT
349         DROP
350 ;
351
352 ( DEPTH returns the depth of the stack. )
353 : DEPTH         ( -- n )
354         S0 @ DSP@ -
355         4-                      ( adjust because S0 was on the stack when we pushed DSP )
356 ;
357
358 (
359         ALIGNED takes an address and rounds it up (aligns it) to the next 4 byte boundary.
360 )
361 : ALIGNED       ( addr -- addr )
362         3 + 3 INVERT AND        ( (addr+3) & ~3 )
363 ;
364
365 (
366         ALIGN aligns the HERE pointer, so the next word appended will be aligned properly.
367 )
368 : ALIGN HERE @ ALIGNED HERE ! ;
369
370 (
371         S" string" is used in FORTH to define strings.  It leaves the address of the string and
372         its length on the stack, with the address at the top.  The space following S" is the normal
373         space between FORTH words and is not a part of the string.
374
375         This is tricky to define because it has to do different things depending on whether
376         we are compiling or in immediate mode.  (Thus the word is marked IMMEDIATE so it can
377         detect this and do different things).
378
379         In compile mode we append
380                 LITSTRING <string length> <string rounded up 4 bytes>
381         to the current word.  The primitive LITSTRING does the right thing when the current
382         word is executed.
383
384         In immediate mode there isn't a particularly good place to put the string, but in this
385         case we put the string at HERE (but we _don't_ change HERE).  This is meant as a temporary
386         location, likely to be overwritten soon after.
387 )
388 : S" IMMEDIATE          ( -- len addr )
389         STATE @ IF      ( compiling? )
390                 ' LITSTRING ,   ( compile LITSTRING )
391                 HERE @          ( save the address of the length word on the stack )
392                 0 ,             ( dummy length - we don't know what it is yet )
393                 BEGIN
394                         KEY             ( get next character of the string )
395                         DUP '"' <>
396                 WHILE
397                         HERE @ C!       ( store the character in the compiled image )
398                         1 HERE +!       ( increment HERE pointer by 1 byte )
399                 REPEAT
400                 DROP            ( drop the double quote character at the end )
401                 DUP             ( get the saved address of the length word )
402                 HERE @ SWAP -   ( calculate the length )
403                 4-              ( subtract 4 (because we measured from the start of the length word) )
404                 SWAP !          ( and back-fill the length location )
405                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
406         ELSE            ( immediate mode )
407                 HERE @          ( get the start address of the temporary space )
408                 BEGIN
409                         KEY
410                         DUP '"' <>
411                 WHILE
412                         OVER C!         ( save next character )
413                         1+              ( increment address )
414                 REPEAT
415                 DROP            ( drop the final " character )
416                 HERE @ -        ( calculate the length )
417                 HERE @          ( push the start address )
418         THEN
419 ;
420
421 (
422         ." is the print string operator in FORTH.  Example: ." Something to print"
423         The space after the operator is the ordinary space required between words and is not
424         a part of what is printed.
425
426         In immediate mode we just keep reading characters and printing them until we get to
427         the next double quote.
428
429         In compile mode we use S" to store the string, then add EMITSTRING afterwards:
430                 LITSTRING <string length> <string rounded up to 4 bytes> EMITSTRING
431
432         It may be interesting to note the use of [COMPILE] to turn the call to the immediate
433         word S" into compilation of that word.  It compiles it into the definition of .",
434         not into the definition of the word being compiled when this is running (complicated
435         enough for you?)
436 )
437 : ." IMMEDIATE          ( -- )
438         STATE @ IF      ( compiling? )
439                 [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
440                 ' EMITSTRING ,  ( compile the final EMITSTRING )
441         ELSE
442                 ( In immediate mode, just read characters and print them until we get
443                   to the ending double quote. )
444                 BEGIN
445                         KEY
446                         DUP '"' = IF
447                                 DROP    ( drop the double quote character )
448                                 EXIT    ( return from this function )
449                         THEN
450                         EMIT
451                 AGAIN
452         THEN
453 ;
454
455 (
456         In FORTH, global constants and variables are defined like this:
457
458         10 CONSTANT TEN         when TEN is executed, it leaves the integer 10 on the stack
459         VARIABLE VAR            when VAR is executed, it leaves the address of VAR on the stack
460
461         Constants can be read but not written, eg:
462
463         TEN . CR                prints 10
464
465         You can read a variable (in this example called VAR) by doing:
466
467         VAR @                   leaves the value of VAR on the stack
468         VAR @ . CR              prints the value of VAR
469         VAR ? CR                same as above, since ? is the same as @ .
470
471         and update the variable by doing:
472
473         20 VAR !                sets VAR to 20
474
475         Note that variables are uninitialised (but see VALUE later on which provides initialised
476         variables with a slightly simpler syntax).
477
478         How can we define the words CONSTANT and VARIABLE?
479
480         The trick is to define a new word for the variable itself (eg. if the variable was called
481         'VAR' then we would define a new word called VAR).  This is easy to do because we exposed
482         dictionary entry creation through the CREATE word (part of the definition of : above).
483         A call to CREATE TEN leaves the dictionary entry:
484
485                                    +--- HERE
486                                    |
487                                    V
488         +---------+---+---+---+---+
489         | LINK    | 3 | T | E | N |
490         +---------+---+---+---+---+
491                    len
492
493         For CONSTANT we can continue by appending DOCOL (the codeword), then LIT followed by
494         the constant itself and then EXIT, forming a little word definition that returns the
495         constant:
496
497         +---------+---+---+---+---+------------+------------+------------+------------+
498         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
499         +---------+---+---+---+---+------------+------------+------------+------------+
500                    len              codeword
501
502         Notice that this word definition is exactly the same as you would have got if you had
503         written : TEN 10 ;
504
505         Note for people reading the code below: DOCOL is a constant word which we defined in the
506         assembler part which returns the value of the assembler symbol of the same name.
507 )
508 : CONSTANT
509         CREATE          ( make the dictionary entry (the name follows CONSTANT) )
510         DOCOL ,         ( append DOCOL (the codeword field of this word) )
511         ' LIT ,         ( append the codeword LIT )
512         ,               ( append the value on the top of the stack )
513         ' EXIT ,        ( append the codeword EXIT )
514 ;
515
516 (
517         VARIABLE is a little bit harder because we need somewhere to put the variable.  There is
518         nothing particularly special about the 'user definitions area' (the area of memory pointed
519         to by HERE where we have previously just stored new word definitions).  We can slice off
520         bits of this memory area to store anything we want, so one possible definition of
521         VARIABLE might create this:
522
523            +--------------------------------------------------------------+
524            |                                                              |
525            V                                                              |
526         +---------+---------+---+---+---+---+------------+------------+---|--------+------------+
527         | <var>   | LINK    | 3 | V | A | R | DOCOL      | LIT        | <addr var> | EXIT       |
528         +---------+---------+---+---+---+---+------------+------------+------------+------------+
529                              len              codeword
530
531         where <var> is the place to store the variable, and <addr var> points back to it.
532
533         To make this more general let's define a couple of words which we can use to allocate
534         arbitrary memory from the user definitions area.
535
536         First ALLOT, where n ALLOT allocates n bytes of memory.  (Note when calling this that
537         it's a very good idea to make sure that n is a multiple of 4, or at least that next time
538         a word is compiled that HERE has been left as a multiple of 4).
539 )
540 : ALLOT         ( n -- addr )
541         HERE @ SWAP     ( here n )
542         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
543 ;
544
545 (
546         Second, CELLS.  In FORTH the phrase 'n CELLS ALLOT' means allocate n integers of whatever size
547         is the natural size for integers on this machine architecture.  On this 32 bit machine therefore
548         CELLS just multiplies the top of stack by 4.
549 )
550 : CELLS ( n -- n ) 4 * ;
551
552 (
553         So now we can define VARIABLE easily in much the same way as CONSTANT above.  Refer to the
554         diagram above to see what the word that this creates will look like.
555 )
556 : VARIABLE
557         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
558         CREATE          ( make the dictionary entry (the name follows VARIABLE) )
559         DOCOL ,         ( append DOCOL (the codeword field of this word) )
560         ' LIT ,         ( append the codeword LIT )
561         ,               ( append the pointer to the new memory )
562         ' EXIT ,        ( append the codeword EXIT )
563 ;
564
565 (
566         VALUEs are like VARIABLEs but with a simpler syntax.  You would generally use them when you
567         want a variable which is read often, and written infrequently.
568
569         20 VALUE VAL    creates VAL with initial value 20
570         VAL             pushes the value directly on the stack
571         30 TO VAL       updates VAL, setting it to 30
572
573         Notice that 'VAL' on its own doesn't return the address of the value, but the value itself,
574         making values simpler and more obvious to use than variables (no indirection through '@').
575         The price is a more complicated implementation, although despite the complexity there is no
576         performance penalty at runtime.
577
578         A naive implementation of 'TO' would be quite slow, involving a dictionary search each time.
579         But because this is FORTH we have complete control of the compiler so we can compile TO more
580         efficiently, turning:
581                 TO VAL
582         into:
583                 LIT <addr> !
584         and calculating <addr> (the address of the value) at compile time.
585
586         Now this is the clever bit.  We'll compile our value like this:
587
588         +---------+---+---+---+---+------------+------------+------------+------------+
589         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
590         +---------+---+---+---+---+------------+------------+------------+------------+
591                    len              codeword
592
593         where <value> is the actual value itself.  Note that when VAL executes, it will push the
594         value on the stack, which is what we want.
595
596         But what will TO use for the address <addr>?  Why of course a pointer to that <value>:
597
598                 code compiled   - - - - --+------------+------------+------------+-- - - - -
599                 by TO VAL                 | LIT        | <addr>     | !          |
600                                 - - - - --+------------+-----|------+------------+-- - - - -
601                                                              |
602                                                              V
603         +---------+---+---+---+---+------------+------------+------------+------------+
604         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
605         +---------+---+---+---+---+------------+------------+------------+------------+
606                    len              codeword
607
608         In other words, this is a kind of self-modifying code.
609
610         (Note to the people who want to modify this FORTH to add inlining: values defined this
611         way cannot be inlined).
612 )
613 : VALUE         ( n -- )
614         CREATE          ( make the dictionary entry (the name follows VALUE) )
615         DOCOL ,         ( append DOCOL )
616         ' LIT ,         ( append the codeword LIT )
617         ,               ( append the initial value )
618         ' EXIT ,        ( append the codeword EXIT )
619 ;
620
621 : TO IMMEDIATE  ( n -- )
622         WORD            ( get the name of the value )
623         FIND            ( look it up in the dictionary )
624         >DFA            ( get a pointer to the first data field (the 'LIT') )
625         4+              ( increment to point at the value )
626         STATE @ IF      ( compiling? )
627                 ' LIT ,         ( compile LIT )
628                 ,               ( compile the address of the value )
629                 ' ! ,           ( compile ! )
630         ELSE            ( immediate mode )
631                 !               ( update it straightaway )
632         THEN
633 ;
634
635 ( x +TO VAL adds x to VAL )
636 : +TO IMMEDIATE
637         WORD            ( get the name of the value )
638         FIND            ( look it up in the dictionary )
639         >DFA            ( get a pointer to the first data field (the 'LIT') )
640         4+              ( increment to point at the value )
641         STATE @ IF      ( compiling? )
642                 ' LIT ,         ( compile LIT )
643                 ,               ( compile the address of the value )
644                 ' +! ,          ( compile +! )
645         ELSE            ( immediate mode )
646                 +!              ( update it straightaway )
647         THEN
648 ;
649
650 (
651         ID. takes an address of a dictionary entry and prints the word's name.
652
653         For example: LATEST @ ID. would print the name of the last word that was defined.
654 )
655 : ID.
656         4+              ( skip over the link pointer )
657         DUP C@          ( get the flags/length byte )
658         F_LENMASK AND   ( mask out the flags - just want the length )
659
660         BEGIN
661                 DUP 0>          ( length > 0? )
662         WHILE
663                 SWAP 1+         ( addr len -- len addr+1 )
664                 DUP C@          ( len addr -- len addr char | get the next character)
665                 EMIT            ( len addr char -- len addr | and print it)
666                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
667         REPEAT
668         2DROP           ( len addr -- )
669 ;
670
671 (
672         'WORD word FIND ?HIDDEN' returns true if 'word' is flagged as hidden.
673
674         'WORD word FIND ?IMMEDIATE' returns true if 'word' is flagged as immediate.
675 )
676 : ?HIDDEN
677         4+              ( skip over the link pointer )
678         C@              ( get the flags/length byte )
679         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
680 ;
681 : ?IMMEDIATE
682         4+              ( skip over the link pointer )
683         C@              ( get the flags/length byte )
684         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
685 ;
686
687 (
688         WORDS prints all the words defined in the dictionary, starting with the word defined most recently.
689         However it doesn't print hidden words.
690
691         The implementation simply iterates backwards from LATEST using the link pointers.
692 )
693 : WORDS
694         LATEST @        ( start at LATEST dictionary entry )
695         BEGIN
696                 DUP 0<>         ( while link pointer is not null )
697         WHILE
698                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
699                         DUP ID.         ( but if not hidden, print the word )
700                 THEN
701                 SPACE
702                 @               ( dereference the link pointer - go to previous word )
703         REPEAT
704         DROP
705         CR
706 ;
707
708 (
709         So far we have only allocated words and memory.  FORTH provides a rather primitive method
710         to deallocate.
711
712         'FORGET word' deletes the definition of 'word' from the dictionary and everything defined
713         after it, including any variables and other memory allocated after.
714
715         The implementation is very simple - we look up the word (which returns the dictionary entry
716         address).  Then we set HERE to point to that address, so in effect all future allocations
717         and definitions will overwrite memory starting at the word.  We also need to set LATEST to
718         point to the previous word.
719
720         Note that you cannot FORGET built-in words (well, you can try but it will probably cause
721         a segfault).
722
723         XXX: Because we wrote VARIABLE to store the variable in memory allocated before the word,
724         in the current implementation VARIABLE FOO FORGET FOO will leak 1 cell of memory.
725 )
726 : FORGET
727         WORD FIND       ( find the word, gets the dictionary entry address )
728         DUP @ LATEST !  ( set LATEST to point to the previous word )
729         HERE !          ( and store HERE with the dictionary address )
730 ;
731
732 (
733         DUMP is used to dump out the contents of memory, in the 'traditional' hexdump format.
734 )
735 : DUMP          ( addr len -- )
736         BASE @ ROT              ( save the current BASE at the bottom of the stack )
737         HEX                     ( and switch the hexadecimal mode )
738
739         BEGIN
740                 DUP 0>          ( while len > 0 )
741         WHILE
742                 OVER 8 .R       ( print the address )
743                 SPACE
744
745                 ( print up to 16 words on this line )
746                 2DUP            ( addr len addr len )
747                 1- 15 AND 1+    ( addr len addr linelen )
748                 BEGIN
749                         DUP 0>          ( while linelen > 0 )
750                 WHILE
751                         SWAP            ( addr len linelen addr )
752                         DUP C@          ( addr len linelen addr byte )
753                         2 .R SPACE      ( print the byte )
754                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
755                 REPEAT
756                 2DROP           ( addr len )
757
758                 ( print the ASCII equivalents )
759                 2DUP 1- 15 AND 1+ ( addr len addr linelen )
760                 BEGIN
761                         DUP 0>          ( while linelen > 0)
762                 WHILE
763                         SWAP            ( addr len linelen addr )
764                         DUP C@          ( addr len linelen addr byte )
765                         DUP 32 128 WITHIN IF    ( 32 <= c < 128? )
766                                 EMIT
767                         ELSE
768                                 DROP [ CHAR ? ] LITERAL EMIT
769                         THEN
770                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
771                 REPEAT
772                 2DROP           ( addr len )
773                 CR
774
775                 DUP 1- 15 AND 1+ ( addr len linelen )
776                 DUP             ( addr len linelen linelen )
777                 ROT             ( addr linelen len linelen )
778                 -               ( addr linelen len-linelen )
779                 ROT             ( len-linelen addr linelen )
780                 +               ( len-linelen addr+linelen )
781                 SWAP            ( addr-linelen len-linelen )
782         REPEAT
783
784         2DROP                   ( restore stack )
785         BASE !                  ( restore saved BASE )
786 ;
787
788 ( Finally print the welcome prompt. )
789 ." JONESFORTH VERSION " VERSION . CR
790 ." OK "