'SPACE' -> BL (standard FORTH word)
[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.11 2007-09-29 23:13:45 rich Exp $
6 \
7 \       The first part of this tutorial is in jonesforth.S.  Get if from http://annexia.org/forth
8 \
9 \       PUBLIC DOMAIN ----------------------------------------------------------------------
10 \
11 \       I, the copyright holder of this work, hereby release it into the public domain. This applies worldwide.
12 \
13 \       In case this is not legally possible, I grant any entity the right to use this work for any purpose,
14 \       without any conditions, unless such conditions are required by law.
15 \
16 \       SETTING UP ----------------------------------------------------------------------
17 \
18 \       Let's get a few housekeeping things out of the way.  Firstly because I need to draw lots of
19 \       ASCII-art diagrams to explain concepts, the best way to look at this is using a window which
20 \       uses a fixed width font and is at least this wide:
21 \
22 \<------------------------------------------------------------------------------------------------------------------------>
23 \
24 \       Secondly make sure TABS are set to 8 characters.  The following should be a vertical
25 \       line.  If not, sort out your tabs.
26 \
27 \       |
28 \       |
29 \       |
30 \
31 \       Thirdly I assume that your screen is at least 50 characters high.
32 \
33 \       START OF FORTH CODE ----------------------------------------------------------------------
34 \
35 \       We've now reached the stage where the FORTH system is running and self-hosting.  All further
36 \       words can be written as FORTH itself, including words like IF, THEN, .", etc which in most
37 \       languages would be considered rather fundamental.
38 \
39 \       Some notes about the code:
40 \
41 \       I use indenting to show structure.  The amount of whitespace has no meaning to FORTH however
42 \       except that you must use at least one whitespace character between words, and words themselves
43 \       cannot contain whitespace.
44 \
45 \       FORTH is case-sensitive.  Use capslock!
46
47 \ The primitive word /MOD (DIVMOD) leaves both the quotient and the remainder on the stack.  (On
48 \ i386, the idivl instruction gives both anyway).  Now we can define the / and MOD in terms of /MOD
49 \ and a few other primitives.
50 : / /MOD SWAP DROP ;
51 : MOD /MOD DROP ;
52
53 \ Define some character constants
54 : '\n' 10 ;
55 : BL   32 ; \ BL (BLank) is a standard FORTH word for space.
56
57 \ CR prints a carriage return
58 : CR '\n' EMIT ;
59
60 \ SPACE prints a space
61 : SPACE BL EMIT ;
62
63 \ 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 IF                 ( if quotient <> 0 then )
309                 RECURSE         ( print the quotient )
310         THEN
311
312         ( print the remainder )
313         DUP 10 < IF
314                 '0'             ( decimal digits 0..9 )
315         ELSE
316                 10 -            ( hex and beyond digits A..Z )
317                 'A'
318         THEN
319         +
320         EMIT
321 ;
322
323 (
324         FORTH word .S prints the contents of the stack.  It doesn't alter the stack.
325         Very useful for debugging.
326 )
327 : .S            ( -- )
328         DSP@            ( get current stack pointer )
329         BEGIN
330                 DUP S0 @ <
331         WHILE
332                 DUP @ U.        ( print the stack element )
333                 SPACE
334                 4+              ( move up )
335         REPEAT
336         DROP
337 ;
338
339 ( This word returns the width (in characters) of an unsigned number in the current base )
340 : UWIDTH        ( u -- width )
341         BASE @ /        ( rem quot )
342         ?DUP IF         ( if quotient <> 0 then )
343                 RECURSE 1+      ( return 1+recursive call )
344         ELSE
345                 1               ( return 1 )
346         THEN
347 ;
348
349 : U.R           ( u width -- )
350         SWAP            ( width u )
351         DUP             ( width u u )
352         UWIDTH          ( width u uwidth )
353         -ROT            ( u uwidth width )
354         SWAP -          ( u width-uwidth )
355         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
356           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
357           a negative number of spaces anyway, so it's now safe to call SPACES ... )
358         SPACES
359         ( ... and then call the underlying implementation of U. )
360         U.
361 ;
362
363 (
364         .R prints a signed number, padded to a certain width.  We can't just print the sign
365         and call U.R because we want the sign to be next to the number ('-123' instead of '-  123').
366 )
367 : .R            ( n width -- )
368         SWAP            ( width n )
369         DUP 0< IF
370                 NEGATE          ( width u )
371                 1               ( save a flag to remember that it was negative | width n 1 )
372                 ROT             ( 1 width u )
373                 SWAP            ( 1 u width )
374                 1-              ( 1 u width-1 )
375         ELSE
376                 0               ( width u 0 )
377                 ROT             ( 0 width u )
378                 SWAP            ( 0 u width )
379         THEN
380         SWAP            ( flag width u )
381         DUP             ( flag width u u )
382         UWIDTH          ( flag width u uwidth )
383         -ROT            ( flag u uwidth width )
384         SWAP -          ( flag u width-uwidth )
385
386         SPACES          ( flag u )
387         SWAP            ( u flag )
388
389         IF                      ( was it negative? print the - character )
390                 '-' EMIT
391         THEN
392
393         U.
394 ;
395
396 ( Finally we can define word . in terms of .R, with a trailing space. )
397 : . 0 .R SPACE ;
398
399 ( The real U., note the trailing space. )
400 : U. U. SPACE ;
401
402 ( ? fetches the integer at an address and prints it. )
403 : ? ( addr -- ) @ . ;
404
405 ( c a b WITHIN returns true if a <= c and c < b )
406 : WITHIN
407         ROT             ( b c a )
408         OVER            ( b c a c )
409         <= IF
410                 > IF            ( b c -- )
411                         TRUE
412                 ELSE
413                         FALSE
414                 THEN
415         ELSE
416                 2DROP           ( b c -- )
417                 FALSE
418         THEN
419 ;
420
421 ( DEPTH returns the depth of the stack. )
422 : DEPTH         ( -- n )
423         S0 @ DSP@ -
424         4-                      ( adjust because S0 was on the stack when we pushed DSP )
425 ;
426
427 (
428         ALIGNED takes an address and rounds it up (aligns it) to the next 4 byte boundary.
429 )
430 : ALIGNED       ( addr -- addr )
431         3 + 3 INVERT AND        ( (addr+3) & ~3 )
432 ;
433
434 (
435         ALIGN aligns the HERE pointer, so the next word appended will be aligned properly.
436 )
437 : ALIGN HERE @ ALIGNED HERE ! ;
438
439 (
440         STRINGS ----------------------------------------------------------------------
441
442         S" string" is used in FORTH to define strings.  It leaves the address of the string and
443         its length on the stack, (length at the top of stack).  The space following S" is the normal
444         space between FORTH words and is not a part of the string.
445
446         This is tricky to define because it has to do different things depending on whether
447         we are compiling or in immediate mode.  (Thus the word is marked IMMEDIATE so it can
448         detect this and do different things).
449
450         In compile mode we append
451                 LITSTRING <string length> <string rounded up 4 bytes>
452         to the current word.  The primitive LITSTRING does the right thing when the current
453         word is executed.
454
455         In immediate mode there isn't a particularly good place to put the string, but in this
456         case we put the string at HERE (but we _don't_ change HERE).  This is meant as a temporary
457         location, likely to be overwritten soon after.
458 )
459 : S" IMMEDIATE          ( -- addr len )
460         STATE @ IF      ( compiling? )
461                 ' LITSTRING ,   ( compile LITSTRING )
462                 HERE @          ( save the address of the length word on the stack )
463                 0 ,             ( dummy length - we don't know what it is yet )
464                 BEGIN
465                         KEY             ( get next character of the string )
466                         DUP '"' <>
467                 WHILE
468                         HERE @ C!       ( store the character in the compiled image )
469                         1 HERE +!       ( increment HERE pointer by 1 byte )
470                 REPEAT
471                 DROP            ( drop the double quote character at the end )
472                 DUP             ( get the saved address of the length word )
473                 HERE @ SWAP -   ( calculate the length )
474                 4-              ( subtract 4 (because we measured from the start of the length word) )
475                 SWAP !          ( and back-fill the length location )
476                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
477         ELSE            ( immediate mode )
478                 HERE @          ( get the start address of the temporary space )
479                 BEGIN
480                         KEY
481                         DUP '"' <>
482                 WHILE
483                         OVER C!         ( save next character )
484                         1+              ( increment address )
485                 REPEAT
486                 DROP            ( drop the final " character )
487                 HERE @ -        ( calculate the length )
488                 HERE @          ( push the start address )
489                 SWAP            ( addr len )
490         THEN
491 ;
492
493 (
494         ." is the print string operator in FORTH.  Example: ." Something to print"
495         The space after the operator is the ordinary space required between words and is not
496         a part of what is printed.
497
498         In immediate mode we just keep reading characters and printing them until we get to
499         the next double quote.
500
501         In compile mode we use S" to store the string, then add TELL afterwards:
502                 LITSTRING <string length> <string rounded up to 4 bytes> TELL
503
504         It may be interesting to note the use of [COMPILE] to turn the call to the immediate
505         word S" into compilation of that word.  It compiles it into the definition of .",
506         not into the definition of the word being compiled when this is running (complicated
507         enough for you?)
508 )
509 : ." IMMEDIATE          ( -- )
510         STATE @ IF      ( compiling? )
511                 [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
512                 ' TELL ,        ( compile the final TELL )
513         ELSE
514                 ( In immediate mode, just read characters and print them until we get
515                   to the ending double quote. )
516                 BEGIN
517                         KEY
518                         DUP '"' = IF
519                                 DROP    ( drop the double quote character )
520                                 EXIT    ( return from this function )
521                         THEN
522                         EMIT
523                 AGAIN
524         THEN
525 ;
526
527 (
528         CONSTANTS AND VARIABLES ----------------------------------------------------------------------
529
530         In FORTH, global constants and variables are defined like this:
531
532         10 CONSTANT TEN         when TEN is executed, it leaves the integer 10 on the stack
533         VARIABLE VAR            when VAR is executed, it leaves the address of VAR on the stack
534
535         Constants can be read but not written, eg:
536
537         TEN . CR                prints 10
538
539         You can read a variable (in this example called VAR) by doing:
540
541         VAR @                   leaves the value of VAR on the stack
542         VAR @ . CR              prints the value of VAR
543         VAR ? CR                same as above, since ? is the same as @ .
544
545         and update the variable by doing:
546
547         20 VAR !                sets VAR to 20
548
549         Note that variables are uninitialised (but see VALUE later on which provides initialised
550         variables with a slightly simpler syntax).
551
552         How can we define the words CONSTANT and VARIABLE?
553
554         The trick is to define a new word for the variable itself (eg. if the variable was called
555         'VAR' then we would define a new word called VAR).  This is easy to do because we exposed
556         dictionary entry creation through the CREATE word (part of the definition of : above).
557         A call to CREATE TEN leaves the dictionary entry:
558
559                                    +--- HERE
560                                    |
561                                    V
562         +---------+---+---+---+---+
563         | LINK    | 3 | T | E | N |
564         +---------+---+---+---+---+
565                    len
566
567         For CONSTANT we can continue by appending DOCOL (the codeword), then LIT followed by
568         the constant itself and then EXIT, forming a little word definition that returns the
569         constant:
570
571         +---------+---+---+---+---+------------+------------+------------+------------+
572         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
573         +---------+---+---+---+---+------------+------------+------------+------------+
574                    len              codeword
575
576         Notice that this word definition is exactly the same as you would have got if you had
577         written : TEN 10 ;
578
579         Note for people reading the code below: DOCOL is a constant word which we defined in the
580         assembler part which returns the value of the assembler symbol of the same name.
581 )
582 : CONSTANT
583         CREATE          ( make the dictionary entry (the name follows CONSTANT) )
584         DOCOL ,         ( append DOCOL (the codeword field of this word) )
585         ' LIT ,         ( append the codeword LIT )
586         ,               ( append the value on the top of the stack )
587         ' EXIT ,        ( append the codeword EXIT )
588 ;
589
590 (
591         VARIABLE is a little bit harder because we need somewhere to put the variable.  There is
592         nothing particularly special about the 'user definitions area' (the area of memory pointed
593         to by HERE where we have previously just stored new word definitions).  We can slice off
594         bits of this memory area to store anything we want, so one possible definition of
595         VARIABLE might create this:
596
597            +--------------------------------------------------------------+
598            |                                                              |
599            V                                                              |
600         +---------+---------+---+---+---+---+------------+------------+---|--------+------------+
601         | <var>   | LINK    | 3 | V | A | R | DOCOL      | LIT        | <addr var> | EXIT       |
602         +---------+---------+---+---+---+---+------------+------------+------------+------------+
603                              len              codeword
604
605         where <var> is the place to store the variable, and <addr var> points back to it.
606
607         To make this more general let's define a couple of words which we can use to allocate
608         arbitrary memory from the user definitions area.
609
610         First ALLOT, where n ALLOT allocates n bytes of memory.  (Note when calling this that
611         it's a very good idea to make sure that n is a multiple of 4, or at least that next time
612         a word is compiled that HERE has been left as a multiple of 4).
613 )
614 : ALLOT         ( n -- addr )
615         HERE @ SWAP     ( here n )
616         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
617 ;
618
619 (
620         Second, CELLS.  In FORTH the phrase 'n CELLS ALLOT' means allocate n integers of whatever size
621         is the natural size for integers on this machine architecture.  On this 32 bit machine therefore
622         CELLS just multiplies the top of stack by 4.
623 )
624 : CELLS ( n -- n ) 4 * ;
625
626 (
627         So now we can define VARIABLE easily in much the same way as CONSTANT above.  Refer to the
628         diagram above to see what the word that this creates will look like.
629 )
630 : VARIABLE
631         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
632         CREATE          ( make the dictionary entry (the name follows VARIABLE) )
633         DOCOL ,         ( append DOCOL (the codeword field of this word) )
634         ' LIT ,         ( append the codeword LIT )
635         ,               ( append the pointer to the new memory )
636         ' EXIT ,        ( append the codeword EXIT )
637 ;
638
639 (
640         VALUES ----------------------------------------------------------------------
641
642         VALUEs are like VARIABLEs but with a simpler syntax.  You would generally use them when you
643         want a variable which is read often, and written infrequently.
644
645         20 VALUE VAL    creates VAL with initial value 20
646         VAL             pushes the value directly on the stack
647         30 TO VAL       updates VAL, setting it to 30
648
649         Notice that 'VAL' on its own doesn't return the address of the value, but the value itself,
650         making values simpler and more obvious to use than variables (no indirection through '@').
651         The price is a more complicated implementation, although despite the complexity there is no
652         performance penalty at runtime.
653
654         A naive implementation of 'TO' would be quite slow, involving a dictionary search each time.
655         But because this is FORTH we have complete control of the compiler so we can compile TO more
656         efficiently, turning:
657                 TO VAL
658         into:
659                 LIT <addr> !
660         and calculating <addr> (the address of the value) at compile time.
661
662         Now this is the clever bit.  We'll compile our value like this:
663
664         +---------+---+---+---+---+------------+------------+------------+------------+
665         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
666         +---------+---+---+---+---+------------+------------+------------+------------+
667                    len              codeword
668
669         where <value> is the actual value itself.  Note that when VAL executes, it will push the
670         value on the stack, which is what we want.
671
672         But what will TO use for the address <addr>?  Why of course a pointer to that <value>:
673
674                 code compiled   - - - - --+------------+------------+------------+-- - - - -
675                 by TO VAL                 | LIT        | <addr>     | !          |
676                                 - - - - --+------------+-----|------+------------+-- - - - -
677                                                              |
678                                                              V
679         +---------+---+---+---+---+------------+------------+------------+------------+
680         | LINK    | 3 | V | A | L | DOCOL      | LIT        | <value>    | EXIT       |
681         +---------+---+---+---+---+------------+------------+------------+------------+
682                    len              codeword
683
684         In other words, this is a kind of self-modifying code.
685
686         (Note to the people who want to modify this FORTH to add inlining: values defined this
687         way cannot be inlined).
688 )
689 : VALUE         ( n -- )
690         CREATE          ( make the dictionary entry (the name follows VALUE) )
691         DOCOL ,         ( append DOCOL )
692         ' LIT ,         ( append the codeword LIT )
693         ,               ( append the initial value )
694         ' EXIT ,        ( append the codeword EXIT )
695 ;
696
697 : TO IMMEDIATE  ( n -- )
698         WORD            ( get the name of the value )
699         FIND            ( look it up in the dictionary )
700         >DFA            ( get a pointer to the first data field (the 'LIT') )
701         4+              ( increment to point at the value )
702         STATE @ IF      ( compiling? )
703                 ' LIT ,         ( compile LIT )
704                 ,               ( compile the address of the value )
705                 ' ! ,           ( compile ! )
706         ELSE            ( immediate mode )
707                 !               ( update it straightaway )
708         THEN
709 ;
710
711 ( x +TO VAL adds x to VAL )
712 : +TO IMMEDIATE
713         WORD            ( get the name of the value )
714         FIND            ( look it up in the dictionary )
715         >DFA            ( get a pointer to the first data field (the 'LIT') )
716         4+              ( increment to point at the value )
717         STATE @ IF      ( compiling? )
718                 ' LIT ,         ( compile LIT )
719                 ,               ( compile the address of the value )
720                 ' +! ,          ( compile +! )
721         ELSE            ( immediate mode )
722                 +!              ( update it straightaway )
723         THEN
724 ;
725
726 (
727         PRINTING THE DICTIONARY ----------------------------------------------------------------------
728
729         ID. takes an address of a dictionary entry and prints the word's name.
730
731         For example: LATEST @ ID. would print the name of the last word that was defined.
732 )
733 : ID.
734         4+              ( skip over the link pointer )
735         DUP C@          ( get the flags/length byte )
736         F_LENMASK AND   ( mask out the flags - just want the length )
737
738         BEGIN
739                 DUP 0>          ( length > 0? )
740         WHILE
741                 SWAP 1+         ( addr len -- len addr+1 )
742                 DUP C@          ( len addr -- len addr char | get the next character)
743                 EMIT            ( len addr char -- len addr | and print it)
744                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
745         REPEAT
746         2DROP           ( len addr -- )
747 ;
748
749 (
750         'WORD word FIND ?HIDDEN' returns true if 'word' is flagged as hidden.
751
752         'WORD word FIND ?IMMEDIATE' returns true if 'word' is flagged as immediate.
753 )
754 : ?HIDDEN
755         4+              ( skip over the link pointer )
756         C@              ( get the flags/length byte )
757         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
758 ;
759 : ?IMMEDIATE
760         4+              ( skip over the link pointer )
761         C@              ( get the flags/length byte )
762         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
763 ;
764
765 (
766         WORDS prints all the words defined in the dictionary, starting with the word defined most recently.
767         However it doesn't print hidden words.
768
769         The implementation simply iterates backwards from LATEST using the link pointers.
770 )
771 : WORDS
772         LATEST @        ( start at LATEST dictionary entry )
773         BEGIN
774                 ?DUP            ( while link pointer is not null )
775         WHILE
776                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
777                         DUP ID.         ( but if not hidden, print the word )
778                 THEN
779                 SPACE
780                 @               ( dereference the link pointer - go to previous word )
781         REPEAT
782         CR
783 ;
784
785 (
786         FORGET ----------------------------------------------------------------------
787
788         So far we have only allocated words and memory.  FORTH provides a rather primitive method
789         to deallocate.
790
791         'FORGET word' deletes the definition of 'word' from the dictionary and everything defined
792         after it, including any variables and other memory allocated after.
793
794         The implementation is very simple - we look up the word (which returns the dictionary entry
795         address).  Then we set HERE to point to that address, so in effect all future allocations
796         and definitions will overwrite memory starting at the word.  We also need to set LATEST to
797         point to the previous word.
798
799         Note that you cannot FORGET built-in words (well, you can try but it will probably cause
800         a segfault).
801
802         XXX: Because we wrote VARIABLE to store the variable in memory allocated before the word,
803         in the current implementation VARIABLE FOO FORGET FOO will leak 1 cell of memory.
804 )
805 : FORGET
806         WORD FIND       ( find the word, gets the dictionary entry address )
807         DUP @ LATEST !  ( set LATEST to point to the previous word )
808         HERE !          ( and store HERE with the dictionary address )
809 ;
810
811 (
812         DUMP ----------------------------------------------------------------------
813
814         DUMP is used to dump out the contents of memory, in the 'traditional' hexdump format.
815
816         Notice that the parameters to DUMP (address, length) are compatible with string words
817         such as WORD and S".
818 )
819 : DUMP          ( addr len -- )
820         BASE @ ROT              ( save the current BASE at the bottom of the stack )
821         HEX                     ( and switch the hexadecimal mode )
822
823         BEGIN
824                 DUP 0>          ( while len > 0 )
825         WHILE
826                 OVER 8 U.R      ( print the address )
827                 SPACE
828
829                 ( print up to 16 words on this line )
830                 2DUP            ( addr len addr len )
831                 1- 15 AND 1+    ( addr len addr linelen )
832                 BEGIN
833                         DUP 0>          ( while linelen > 0 )
834                 WHILE
835                         SWAP            ( addr len linelen addr )
836                         DUP C@          ( addr len linelen addr byte )
837                         2 .R SPACE      ( print the byte )
838                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
839                 REPEAT
840                 2DROP           ( addr len )
841
842                 ( print the ASCII equivalents )
843                 2DUP 1- 15 AND 1+ ( addr len addr linelen )
844                 BEGIN
845                         DUP 0>          ( while linelen > 0)
846                 WHILE
847                         SWAP            ( addr len linelen addr )
848                         DUP C@          ( addr len linelen addr byte )
849                         DUP 32 128 WITHIN IF    ( 32 <= c < 128? )
850                                 EMIT
851                         ELSE
852                                 DROP '.' EMIT
853                         THEN
854                         1+ SWAP 1-      ( addr len linelen addr -- addr len addr+1 linelen-1 )
855                 REPEAT
856                 2DROP           ( addr len )
857                 CR
858
859                 DUP 1- 15 AND 1+ ( addr len linelen )
860                 DUP             ( addr len linelen linelen )
861                 ROT             ( addr linelen len linelen )
862                 -               ( addr linelen len-linelen )
863                 ROT             ( len-linelen addr linelen )
864                 +               ( len-linelen addr+linelen )
865                 SWAP            ( addr-linelen len-linelen )
866         REPEAT
867
868         2DROP                   ( restore stack )
869         BASE !                  ( restore saved BASE )
870 ;
871
872 (
873         CASE ----------------------------------------------------------------------
874
875         CASE...ENDCASE is how we do switch statements in FORTH.  There is no generally
876         agreed syntax for this, so I've gone for the syntax mandated by the ISO standard
877         FORTH (ANS-FORTH).
878
879         ( some value on the stack )
880         CASE
881         test1 OF ... ENDOF
882         test2 OF ... ENDOF
883         testn OF ... ENDOF
884         ... ( default case )
885         ENDCASE
886
887         The CASE statement tests the value on the stack by comparing it for equality with
888         test1, test2, ..., testn and executes the matching piece of code within OF ... ENDOF.
889         If none of the test values match then the default case is executed.  Inside the ... of
890         the default case, the value is still at the top of stack (it is implicitly DROP-ed
891         by ENDCASE).  When ENDOF is executed it jumps after ENDCASE (ie. there is no "fall-through"
892         and no need for a break statement like in C).
893
894         The default case may be omitted.  In fact the tests may also be omitted so that you
895         just have a default case, although this is probably not very useful.
896
897         An example (assuming that 'q', etc. are words which push the ASCII value of the letter
898         on the stack):
899
900         0 VALUE QUIT
901         0 VALUE SLEEP
902         KEY CASE
903                 'q' OF 1 TO QUIT ENDOF
904                 's' OF 1 TO SLEEP ENDOF
905                 ( default case: )
906                 ." Sorry, I didn't understand key <" DUP EMIT ." >, try again." CR
907         ENDCASE
908
909         (In some versions of FORTH, more advanced tests are supported, such as ranges, etc.
910         Other versions of FORTH need you to write OTHERWISE to indicate the default case.
911         As I said above, this FORTH tries to follow the ANS FORTH standard).
912
913         The implementation of CASE...ENDCASE is somewhat non-trivial.  I'm following the
914         implementations from here:
915         http://www.uni-giessen.de/faq/archiv/forthfaq.case_endcase/msg00000.html
916
917         The general plan is to compile the code as a series of IF statements:
918
919         CASE                            (push 0 on the immediate-mode parameter stack)
920         test1 OF ... ENDOF              test1 OVER = IF DROP ... ELSE
921         test2 OF ... ENDOF              test2 OVER = IF DROP ... ELSE
922         testn OF ... ENDOF              testn OVER = IF DROP ... ELSE
923         ... ( default case )            ...
924         ENDCASE                         DROP THEN [THEN [THEN ...]]
925
926         The CASE statement pushes 0 on the immediate-mode parameter stack, and that number
927         is used to count how many THEN statements we need when we get to ENDCASE so that each
928         IF has a matching THEN.  The counting is done implicitly.  If you recall from the
929         implementation above of IF, each IF pushes a code address on the immediate-mode stack,
930         and these addresses are non-zero, so by the time we get to ENDCASE the stack contains
931         some number of non-zeroes, followed by a zero.  The number of non-zeroes is how many
932         times IF has been called, so how many times we need to match it with THEN.
933
934         This code uses [COMPILE] so that we compile calls to IF, ELSE, THEN instead of
935         actually calling them while we're compiling the words below.
936
937         As is the case with all of our control structures, they only work within word
938         definitions, not in immediate mode.
939 )
940 : CASE IMMEDIATE
941         0               ( push 0 to mark the bottom of the stack )
942 ;
943
944 : OF IMMEDIATE
945         ' OVER ,        ( compile OVER )
946         ' = ,           ( compile = )
947         [COMPILE] IF    ( compile IF )
948         ' DROP ,        ( compile DROP )
949 ;
950
951 : ENDOF IMMEDIATE
952         [COMPILE] ELSE  ( ENDOF is the same as ELSE )
953 ;
954
955 : ENDCASE IMMEDIATE
956         ' DROP ,        ( compile DROP )
957
958         ( keep compiling THEN until we get to our zero marker )
959         BEGIN
960                 ?DUP
961         WHILE
962                 [COMPILE] THEN
963         REPEAT
964 ;
965
966 (
967         DECOMPILER ----------------------------------------------------------------------
968
969         CFA> is the opposite of >CFA.  It takes a codeword and tries to find the matching
970         dictionary definition.
971
972         In this FORTH this is not so easy.  In fact we have to search through the dictionary
973         because we don't have a convenient back-pointer (as is often the case in other versions
974         of FORTH).
975
976         This word returns 0 if it doesn't find a match.
977 )
978 : CFA>
979         LATEST @        ( start at LATEST dictionary entry )
980         BEGIN
981                 ?DUP            ( while link pointer is not null )
982         WHILE
983                 DUP >CFA        ( cfa curr curr-cfa )
984                 2 PICK          ( cfa curr curr-cfa cfa )
985                 = IF            ( found a match? )
986                         NIP             ( leave curr dictionary entry on the stack )
987                         EXIT            ( and return from the function )
988                 THEN
989                 @               ( follow link pointer back )
990         REPEAT
991         DROP            ( restore stack )
992         0               ( sorry, nothing found )
993 ;
994
995 (
996         SEE decompiles a FORTH word.
997
998         We search for the dictionary entry of the word, then search again for the next
999         word (effectively, the end of the compiled word).  This results in two pointers:
1000
1001         +---------+---+---+---+---+------------+------------+------------+------------+
1002         | LINK    | 3 | T | E | N | DOCOL      | LIT        | 10         | EXIT       |
1003         +---------+---+---+---+---+------------+------------+------------+------------+
1004          ^                                                                             ^
1005          |                                                                             |
1006         Start of word                                                         End of word
1007
1008         With this information we can have a go at decompiling the word.  We need to
1009         recognise "meta-words" like LIT, LITSTRING, BRANCH, etc. and treat those separately.
1010 )
1011 : SEE
1012         WORD FIND       ( find the dictionary entry to decompile )
1013
1014         ( Now we search again, looking for the next word in the dictionary.  This gives us
1015           the length of the word that we will be decompiling.  (Well, mostly it does). )
1016         HERE @          ( address of the end of the last compiled word )
1017         LATEST @        ( word last curr )
1018         BEGIN
1019                 2 PICK          ( word last curr word )
1020                 OVER            ( word last curr word curr )
1021                 <>              ( word last curr word<>curr? )
1022         WHILE                   ( word last curr )
1023                 NIP             ( word curr )
1024                 DUP @           ( word curr prev (which becomes: word last curr) )
1025         REPEAT
1026
1027         DROP            ( at this point, the stack is: start-of-word end-of-word )
1028         SWAP            ( end-of-word start-of-word )
1029
1030         ( begin the definition with : NAME [IMMEDIATE] )
1031         ':' EMIT SPACE DUP ID. SPACE
1032         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN
1033
1034         >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
1035
1036         ( now we start decompiling until we hit the end of the word )
1037         BEGIN           ( end start )
1038                 2DUP >
1039         WHILE
1040                 DUP @           ( end start codeword )
1041
1042                 CASE
1043                 ' LIT OF                ( is it LIT ? )
1044                         4 + DUP @               ( get next word which is the integer constant )
1045                         .                       ( and print it )
1046                 ENDOF
1047                 ' LITSTRING OF          ( is it LITSTRING ? )
1048                         [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
1049                         4 + DUP @               ( get the length word )
1050                         SWAP 4 + SWAP           ( end start+4 length )
1051                         2DUP TELL               ( print the string )
1052                         '"' EMIT SPACE          ( finish the string with a final quote )
1053                         + ALIGNED               ( end start+4+len, aligned )
1054                         4 -                     ( because we're about to add 4 below )
1055                 ENDOF
1056                 ' 0BRANCH OF            ( is it 0BRANCH ? )
1057                         ." 0BRANCH ( "
1058                         4 + DUP @               ( print the offset )
1059                         .
1060                         ." ) "
1061                 ENDOF
1062                 ' BRANCH OF             ( is it BRANCH ? )
1063                         ." BRANCH ( "
1064                         4 + DUP @               ( print the offset )
1065                         .
1066                         ." ) "
1067                 ENDOF
1068                 ' ' OF                  ( is it ' (TICK) ? )
1069                         [ CHAR ' ] LITERAL EMIT SPACE
1070                         4 + DUP @               ( get the next codeword )
1071                         CFA>                    ( and force it to be printed as a dictionary entry )
1072                         ID. SPACE
1073                 ENDOF
1074                 ' EXIT OF               ( is it EXIT? )
1075                         ( We expect the last word to be EXIT, and if it is then we don't print it
1076                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
1077                           of words, and then it needs to be printed. )
1078                         2DUP                    ( end start end start )
1079                         4 +                     ( end start end start+4 )
1080                         <> IF                   ( end start | we're not at the end )
1081                                 ." EXIT "
1082                         THEN
1083                 ENDOF
1084                                         ( default case: )
1085                         DUP                     ( in the default case we always need to DUP before using )
1086                         CFA>                    ( look up the codeword to get the dictionary entry )
1087                         ID. SPACE               ( and print it )
1088                 ENDCASE
1089
1090                 4 +             ( end start+4 )
1091         REPEAT
1092
1093         ';' EMIT CR
1094
1095         2DROP           ( restore stack )
1096 ;
1097
1098 (
1099         C STRINGS ----------------------------------------------------------------------
1100
1101         FORTH strings are represented by a start address and length kept on the stack or in memory.
1102
1103         Most FORTHs don't handle C strings, but we need them in order to access the process arguments
1104         and environment left on the stack by the Linux kernel.
1105
1106         The main function we need is STRLEN which works out the length of a C string.  DUP STRLEN is
1107         a common idiom which 'converts' a C string into a FORTH string.  (For example, DUP STRLEN TELL
1108         prints a C string).
1109 )
1110
1111 (
1112         Z" .." is like S" ..." except that the string is terminated by an ASCII NUL character.
1113
1114         To make it more like a C string, at runtime Z" just leaves the address of the string
1115         on the stack (not address & length as with S").  To implement this we need to add the
1116         extra NUL to the string and also a DROP instruction afterwards.  Apart from that the
1117         implementation just a modified S".
1118 )
1119 : Z" IMMEDIATE
1120         STATE @ IF      ( compiling? )
1121                 ' LITSTRING ,   ( compile LITSTRING )
1122                 HERE @          ( save the address of the length word on the stack )
1123                 0 ,             ( dummy length - we don't know what it is yet )
1124                 BEGIN
1125                         KEY             ( get next character of the string )
1126                         DUP '"' <>
1127                 WHILE
1128                         HERE @ C!       ( store the character in the compiled image )
1129                         1 HERE +!       ( increment HERE pointer by 1 byte )
1130                 REPEAT
1131                 0 HERE @ C!     ( add the ASCII NUL byte )
1132                 1 HERE +!
1133                 DROP            ( drop the double quote character at the end )
1134                 DUP             ( get the saved address of the length word )
1135                 HERE @ SWAP -   ( calculate the length )
1136                 4-              ( subtract 4 (because we measured from the start of the length word) )
1137                 SWAP !          ( and back-fill the length location )
1138                 ALIGN           ( round up to next multiple of 4 bytes for the remaining code )
1139                 ' DROP ,        ( compile DROP (to drop the length) )
1140         ELSE            ( immediate mode )
1141                 HERE @          ( get the start address of the temporary space )
1142                 BEGIN
1143                         KEY
1144                         DUP '"' <>
1145                 WHILE
1146                         OVER C!         ( save next character )
1147                         1+              ( increment address )
1148                 REPEAT
1149                 DROP            ( drop the final " character )
1150                 0 SWAP C!       ( store final ASCII NUL )
1151                 HERE @          ( push the start address )
1152         THEN
1153 ;
1154
1155 ( STRLEN returns the length of a C string )
1156 : STRLEN        ( str -- len )
1157         DUP             ( save start address )
1158         BEGIN
1159                 DUP C@ 0<>      ( zero byte found? )
1160         WHILE
1161                 1+
1162         REPEAT
1163
1164         SWAP -          ( calculate the length )
1165 ;
1166
1167 (
1168         STRNCMP compares two strings up to a length.  As with C's strncmp it returns 0 if they
1169         are equal, or a number > 0 or < 0 indicating their order.
1170 )
1171 : STRNCMP       ( str1 str2 len -- eq? )
1172         BEGIN
1173                 ?DUP
1174         WHILE
1175                 ROT             ( len str1 str2 )
1176                 DUP C@          ( len str1 str2 char2 )
1177                 2 PICK C@       ( len str1 str2 char2 char1 )
1178                 OVER            ( len str1 str2 char2 char1 char2 )
1179                 -               ( len str1 str2 char2 char1-char2 )
1180
1181                 ?DUP IF         ( strings not the same at this position? )
1182                         NIP             ( len str1 str2 diff )
1183                         ROT             ( len diff str1 str2 )
1184                         DROP DROP       ( len diff )
1185                         NIP             ( diff )
1186                         EXIT
1187                 THEN
1188
1189                 0= IF           ( characters are equal, but is this the end of the C string? )
1190                         DROP DROP DROP
1191                         0
1192                         EXIT
1193                 THEN
1194
1195                 1+              ( len str1 str2+1 )
1196                 ROT             ( str2+1 len str1 )
1197                 1+ ROT          ( str1+1 str2+1 len )
1198                 1-              ( str1+1 str2+1 len-1 )
1199         REPEAT
1200
1201         2DROP           ( restore stack )
1202         0               ( equal )
1203 ;
1204
1205 (
1206         THE ENVIRONMENT ----------------------------------------------------------------------
1207
1208         Linux makes the process arguments and environment available to us on the stack.
1209
1210         The top of stack pointer is saved by the early assembler code when we start up in the FORTH
1211         variable S0, and starting at this pointer we can read out the command line arguments and the
1212         environment.
1213
1214         Starting at S0, S0 itself points to argc (the number of command line arguments).
1215
1216         S0+4 points to argv[0], S0+8 points to argv[1] etc up to argv[argc-1].
1217
1218         argv[argc] is a NULL pointer.
1219
1220         After that the stack contains environment variables, a set of pointers to strings of the
1221         form NAME=VALUE and on until we get to another NULL pointer.
1222
1223         The first word that we define, ARGC, pushes the number of command line arguments (note that
1224         as with C argc, this includes the name of the command).
1225 )
1226 : ARGC
1227         S0 @ @
1228 ;
1229
1230 (
1231         n ARGV gets the nth command line argument.
1232
1233         For example to print the command name you would do:
1234                 0 ARGV TELL CR
1235 )
1236 : ARGV ( n -- str u )
1237         1+ CELLS S0 @ + ( get the address of argv[n] entry )
1238         @               ( get the address of the string )
1239         DUP STRLEN      ( and get its length / turn it into a FORTH string )
1240 ;
1241
1242 (
1243         ENVIRON returns the address of the first environment string.  The list of strings ends
1244         with a NULL pointer.
1245
1246         For example to print the first string in the environment you could do:
1247                 ENVIRON @ DUP STRLEN TELL
1248 )
1249 : ENVIRON       ( -- addr )
1250         ARGC            ( number of command line parameters on the stack to skip )
1251         2 +             ( skip command line count and NULL pointer after the command line args )
1252         CELLS           ( convert to an offset )
1253         S0 @ +          ( add to base stack address )
1254 ;
1255
1256 (
1257         SYSTEM CALLS ----------------------------------------------------------------------
1258
1259         Some wrappers around Linux system calls
1260 )
1261
1262 ( BYE exits by calling the Linux exit(2) syscall. )
1263 : BYE           ( -- )
1264         0
1265         0
1266         0               ( return code (0) )
1267         SYS_EXIT        ( system call number )
1268         SYSCALL3
1269 ;
1270
1271 (
1272         OPEN, CREAT and CLOSE are just like the Linux syscalls open(2), creat(2) and close(2).
1273
1274         Notice that they take C strings and may return error codes (-errno).
1275 )
1276 : OPEN          ( mode flags c-pathname -- ret )
1277         SYS_OPEN
1278         SYSCALL3
1279 ;
1280
1281 : CREAT         ( mode c-pathname -- ret )
1282         0 ROT
1283         SYS_CREAT
1284         SYSCALL3
1285 ;
1286
1287 : CLOSE         ( fd -- ret )
1288         0 ROT 0 ROT
1289         SYS_CLOSE
1290         SYSCALL3
1291 ;
1292
1293 ( READ and WRITE system calls. )
1294 : READ          ( len buffer fd -- ret )
1295         SYS_READ
1296         SYSCALL3
1297 ;       
1298
1299 : WRITE         ( len buffer fd -- ret )
1300         SYS_WRITE
1301         SYSCALL3
1302 ;       
1303
1304 (
1305         ANS FORTH ----------------------------------------------------------------------
1306
1307         From this point we're trying to fill in the missing parts of the ISO standard, commonly
1308         referred to as ANS FORTH.
1309
1310         http://www.taygeta.com/forth/dpans.html
1311         http://www.taygeta.com/forth/dpansf.htm (list of words)
1312 )
1313
1314 ( C, writes a byte at the HERE pointer. )
1315 : C, HERE @ C! 1 HERE +! ;
1316
1317
1318
1319
1320
1321
1322
1323
1324
1325 (
1326         NOTES ----------------------------------------------------------------------
1327
1328         DOES> isn't possible to implement with this FORTH because we don't have a separate
1329         data pointer.
1330 )
1331
1332 (
1333         WELCOME MESSAGE ----------------------------------------------------------------------
1334
1335         Print the version and OK prompt.
1336 )
1337
1338 ." JONESFORTH VERSION " VERSION . CR
1339 ." OK "