TICK problem solved. (Split into ['] and '.)
[forth.jl.git] / src / lib.4th
1 : / /MOD SWAP DROP ;
2 : MOD /MOD DROP ;
3 : */ -ROT * SWAP / ;
4
5 : NEGATE 0 SWAP - ;
6
7 : TRUE -1 ;
8 : FALSE 0 ;
9 : NOT 0= ;
10
11 : CELLS ; \ Allow for slightly more portable code
12
13 : DEPTH PSP@ PSP0 @ - ;
14
15 : '\n' 10 ;
16 : BL 32 ;
17
18 : LITERAL IMMEDIATE ['] LIT , , ;
19
20 : ':' [ CHAR : ] LITERAL ;
21 : ';' [ CHAR ; ] LITERAL ;
22 : '(' [ CHAR ( ] LITERAL ;
23 : ')' [ CHAR ) ] LITERAL ;
24 : '<' [ CHAR < ] LITERAL ;
25 : '>' [ CHAR > ] LITERAL ;
26 : '"' [ CHAR " ] LITERAL ;
27 : 'A' [ CHAR A ] LITERAL ;
28 : '0' [ CHAR 0 ] LITERAL ;
29 : '-' [ CHAR - ] LITERAL ;
30 : '.' [ CHAR . ] LITERAL ;
31
32 : CR '\n' emit ;
33 : SPACE BL emit ;
34
35 : [COMPILE] IMMEDIATE
36         WORD            \ get the next word
37         FIND            \ find it in the dictionary
38         >CFA            \ get its codeword
39         ,               \ and compile that
40 ;
41
42 : RECURSE IMMEDIATE
43         LATEST @        \ LATEST points to the word being compiled at the moment
44         >CFA            \ get the codeword
45         ,               \ compile it
46 ;
47
48 : DEBUGON TRUE DEBUG ! ;
49 : DEBUGOFF FALSE DEBUG ! ;
50
51 \ CONTROL STRUCTURES ----------------------------------------------------------------------
52
53 : IF IMMEDIATE
54         ['] 0BRANCH ,     \ compile 0BRANCH
55         HERE @          \ save location of the offset on the stack
56         0 ,             \ compile a dummy offset
57 ;
58
59 : THEN IMMEDIATE
60         DUP
61         HERE @ SWAP -   \ calculate the offset from the address saved on the stack
62         SWAP !          \ store the offset in the back-filled location
63 ;
64
65 : ELSE IMMEDIATE
66         ['] BRANCH ,      \ definite branch to just over the false-part
67         HERE @          \ save location of the offset on the stack
68         0 ,             \ compile a dummy offset
69         SWAP            \ now back-fill the original (IF) offset
70         DUP             \ same as for THEN word above
71         HERE @ SWAP -
72         SWAP !
73 ;
74
75 : BEGIN IMMEDIATE
76         HERE @          \ save location on the stack
77 ;
78
79 : UNTIL IMMEDIATE
80         ['] 0BRANCH ,     \ compile 0BRANCH
81         HERE @ -        \ calculate the offset from the address saved on the stack
82         ,               \ compile the offset here
83 ;
84
85 : AGAIN IMMEDIATE
86         ['] BRANCH ,      \ compile BRANCH
87         HERE @ -        \ calculate the offset back
88         ,               \ compile the offset here
89 ;
90
91 : WHILE IMMEDIATE
92         ['] 0BRANCH ,     \ compile 0BRANCH
93         HERE @          \ save location of the offset2 on the stack
94         0 ,             \ compile a dummy offset2
95 ;
96
97 : REPEAT IMMEDIATE
98         ['] BRANCH ,      \ compile BRANCH
99         SWAP            \ get the original offset (from BEGIN)
100         HERE @ - ,      \ and compile it after BRANCH
101         DUP
102         HERE @ SWAP -   \ calculate the offset2
103         SWAP !          \ and back-fill it in the original location
104 ;
105
106 : UNLESS IMMEDIATE
107         ['] NOT ,         \ compile NOT (to reverse the test)
108         [COMPILE] IF    \ continue by calling the normal IF
109 ;
110
111 : DO IMMEDIATE
112         ['] LIT , -1 , [COMPILE] IF
113         ['] >R , ['] >R ,
114         ['] LIT , HERE @ 0 , ['] >R ,
115         HERE @
116 ;
117
118 : ?DO IMMEDIATE
119         ['] 2DUP , ['] - , [COMPILE] IF
120         ['] >R , ['] >R ,
121         ['] LIT , HERE @ 0 , ['] >R ,
122         HERE @
123 ;
124
125 : I RSP@ 3 - @ ;
126
127 : J RSP@ 6 - @ ;
128
129 : ?LEAVE IMMEDIATE
130         ['] 0BRANCH , 13 ,
131         ['] R> , ['] RDROP , ['] RDROP ,
132         ['] LIT ,  HERE @ 7 + , ['] DUP , ['] -ROT , ['] - , ['] SWAP , ['] ! ,
133         ['] BRANCH ,
134         0 ,
135 ;
136
137 : LEAVE IMMEDIATE
138         ['] LIT , -1 ,
139         [COMPILE] ?LEAVE
140 ;
141
142 : +LOOP IMMEDIATE
143         ['] DUP , \ Store copy of increment
144
145         ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] R> , ['] SWAP , ['] + , ['] 2DUP , ['] - ,
146         ['] SWAP , ['] >R , ['] SWAP , ['] >R , ['] SWAP , ['] >R ,
147
148         \ Condition differently depending on sign of increment
149         ['] SWAP , ['] 0>= , [COMPILE] IF
150             ['] 0<= ,
151         [COMPILE] ELSE
152             ['] 0> ,
153         [COMPILE] THEN
154
155         \ Branch back to begining of loop kernel
156         ['] 0BRANCH , HERE @ - ,
157
158         \ Clean up
159         ['] RDROP , ['] RDROP , ['] RDROP ,
160
161         \ Record address of loop end for any LEAVEs to use
162         HERE @ SWAP !
163
164         [COMPILE] ELSE
165             ['] 2DROP , \ Clean up if loop was entirely skipped (?DO)
166         [COMPILE] THEN
167 ;
168
169 : LOOP IMMEDIATE
170         ['] LIT , 1 ,
171         [COMPILE] +LOOP
172 ;
173
174 \ COMMENTS ----------------------------------------------------------------------
175
176 : ( IMMEDIATE
177         1               \ allowed nested parens by keeping track of depth
178         BEGIN
179                 KEY             \ read next character
180                 DUP '(' = IF    \ open paren?
181                         DROP            \ drop the open paren
182                         1+              \ depth increases
183                 ELSE
184                         ')' = IF        \ close paren?
185                                 1-              \ depth decreases
186                         THEN
187                 THEN
188         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
189         DROP            \ drop the depth counter
190 ;
191
192 ( Some more complicated stack examples, showing the stack notation. )
193 : NIP ( x y -- y ) SWAP DROP ;
194 : TUCK ( x y -- y x y ) DUP -ROT ;
195 : PICK ( x_u ... x_1 x_0 u -- x_u ... x_1 x_0 x_u )
196         1+              ( add one because of 'u' on the stack )
197         PSP@ SWAP -     ( add to the stack pointer )
198         @               ( and fetch )
199 ;
200 : ROLL ( x_u x_u-1... x_0 u -- x_u-1 ... x_0 x_u )
201         1+ DUP PICK SWAP    ( x_u x_u-1 ... x_0 x_u u+1 )
202         PSP@ 1- SWAP - PSP@ 2- SWAP
203         DO
204             i 1+ @ i !
205         LOOP
206         SWAP DROP
207 ;
208
209 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
210 : SPACES        ( n -- )
211         DUP 0> IF
212             0 DO SPACE LOOP
213         ELSE
214             DROP
215         THEN
216 ;
217
218 ( Standard words for manipulating BASE. )
219 : DECIMAL ( -- ) 10 BASE ! ;
220 : HEX ( -- ) 16 BASE ! ;
221
222 ( Compute absolute value. )
223 : ABS           ( n -- |n| )
224         dup 0< if
225                 negate
226         then
227 ;
228
229 : MAX           ( n m -- max )
230         2dup - 0< if
231                 swap drop
232         else
233                 drop
234         then
235 ;
236
237 : MIN           ( n m -- max )
238         2dup - 0> if
239                 swap drop
240         else
241                 drop
242         then
243 ;
244
245 ( PRINTING NUMBERS ---------------------------------------------------------------------- )
246
247 ( This is the underlying recursive definition of U. )
248 : U.            ( u -- )
249         BASE @ /MOD     ( width rem quot )
250         ?DUP IF                 ( if quotient <> 0 then )
251                 RECURSE         ( print the quotient )
252         THEN
253
254         ( print the remainder )
255         DUP 10 < IF
256                 '0'             ( decimal digits 0..9 )
257         ELSE
258                 10 -            ( hex and beyond digits A..Z )
259                 'A'
260         THEN
261         +
262         EMIT
263 ;
264
265 ( This word returns the width (in characters) of an unsigned number in the current base )
266 : UWIDTH        ( u -- width )
267         BASE @ /        ( rem quot )
268         ?DUP IF         ( if quotient <> 0 then )
269                 RECURSE 1+      ( return 1+recursive call )
270         ELSE
271                 1               ( return 1 )
272         THEN
273 ;
274
275 : U.R           ( u width -- )
276         SWAP            ( width u )
277         DUP             ( width u u )
278         UWIDTH          ( width u uwidth )
279         ROT            ( u uwidth width )
280         SWAP -          ( u width-uwidth )
281         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
282           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
283           a negative number of spaces anyway, so it's now safe to call SPACES ... )
284         SPACES
285         ( ... and then call the underlying implementation of U. )
286         U.
287 ;
288
289 : .R            ( n width -- )
290         SWAP            ( width n )
291         DUP 0< IF
292                 NEGATE          ( width u )
293                 1               ( save a flag to remember that it was negative | width n 1 )
294                 -ROT             ( 1 width u )
295                 SWAP            ( 1 u width )
296                 1-              ( 1 u width-1 )
297         ELSE
298                 0               ( width u 0 )
299                 -ROT             ( 0 width u )
300                 SWAP            ( 0 u width )
301         THEN
302         SWAP            ( flag width u )
303         DUP             ( flag width u u )
304         UWIDTH          ( flag width u uwidth )
305         ROT            ( flag u uwidth width )
306         SWAP -          ( flag u width-uwidth )
307
308         SPACES          ( flag u )
309         SWAP            ( u flag )
310
311         IF                      ( was it negative? print the - character )
312                 '-' EMIT
313         THEN
314
315         U.
316 ;
317
318 : . 0 .R SPACE ;
319
320 : .S            ( -- )
321         '<' EMIT DEPTH U. '>' EMIT SPACE
322         PSP0 @ 1+
323         BEGIN
324                 DUP PSP@ 2 - <=
325         WHILE
326                 DUP @ .
327                 1+
328         REPEAT
329         DROP
330 ;
331
332 : U. U. SPACE ;
333
334 ( ? fetches the integer at an address and prints it. )
335 : ? ( addr -- ) @ . ;
336
337 ( c a b WITHIN returns true if a <= c and c < b )
338 : WITHIN
339         -ROT             ( b c a )
340         OVER            ( b c a c )
341         <= IF
342                 > IF            ( b c -- )
343                         TRUE
344                 ELSE
345                         FALSE
346                 THEN
347         ELSE
348                 2DROP           ( b c -- )
349                 FALSE
350         THEN
351 ;
352
353
354 ( STRINGS ---------------------------------------------------------------------- )
355
356 ( Since the smallest unit of memory in our system is 64 bits and since strings
357   are stored as arrays of 64 bit integers, the character store/fetch words are
358   just aliases of the standard store/fetch words. )
359 : C! ! ;
360 : C@ @ ;
361
362 ( Block copy, however, is important and novel: )
363 : CMOVE ( src dest length -- )
364
365         DUP 0<= IF
366                 EXIT
367         THEN
368
369         -ROT OVER -         ( length src (dest-src) )
370         -ROT DUP ROT + SWAP ( (dest-src) (src+length) src )
371     
372         DO
373                 I @         ( (dest-src) i@ )
374                 OVER I +    ( (dest-src) i@ (dest-src+i) )
375                 !           ( (dest-src) )
376         LOOP
377
378         DROP
379 ;
380
381 ( C, appends a byte to the current compiled word. )
382 : C,
383         HERE @ C!
384         1 HERE +!
385 ;
386
387 : S" IMMEDIATE          ( -- addr len )
388         STATE @ IF      ( compiling? )
389                 ['] LITSTRING ,   ( compile LITSTRING )
390                 HERE @          ( save the address of the length word on the stack )
391                 0 ,             ( dummy length - we don't know what it is yet )
392                 KEY DROP
393                 BEGIN
394                         KEY             ( get next character of the string )
395                         DUP '"' <>
396                 WHILE
397                         C,              ( copy character )
398                 REPEAT
399                 DROP            ( drop the double quote character at the end )
400                 DUP             ( get the saved address of the length word )
401                 HERE @ SWAP -   ( calculate the length )
402                 1-              ( subtract 1 (because we measured from the start of the length word) )
403                 SWAP !          ( and back-fill the length location )
404         ELSE            ( immediate mode )
405                 HERE @          ( get the start address of the temporary space )
406                 KEY DROP
407                 BEGIN
408                         KEY
409                         DUP '"' <>
410                 WHILE
411                         OVER C!         ( save next character )
412                         1+              ( increment address )
413                 REPEAT
414                 DROP            ( drop the final " character )
415                 HERE @ -        ( calculate the length )
416                 HERE @          ( push the start address )
417                 SWAP            ( addr len )
418         THEN
419 ;
420
421 : ." IMMEDIATE          ( -- )
422         STATE @ IF      ( compiling? )
423                 [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
424                 ['] TELL ,        ( compile the final TELL )
425         ELSE
426                 ( In immediate mode, just read characters and print them until we get
427                   to the ending double quote. )
428                 KEY DROP
429                 BEGIN
430                         KEY
431                         DUP '"' = IF
432                                 DROP    ( drop the double quote character )
433                                 EXIT    ( return from this function )
434                         THEN
435                         EMIT
436                 AGAIN
437         THEN
438 ;
439
440 ( CONSTANTS AND VARIABLES ------------------------------------------------------ )
441
442 : CONSTANT
443         WORD            ( get the name (the name follows CONSTANT) )
444         CREATE          ( make the dictionary entry )
445         DOCOL ,         ( append DOCOL (the codeword field of this word) )
446         ['] LIT ,       ( append the codeword LIT )
447         ,               ( append the value on the top of the stack )
448         ['] EXIT ,      ( append the codeword EXIT )
449 ;
450
451 : ALLOT         ( n -- addr )
452         HERE @ SWAP     ( here n )
453         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
454 ;
455
456 : VARIABLE
457         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
458         WORD CREATE     ( make the dictionary entry (the name follows VARIABLE) )
459         DOCOL ,         ( append DOCOL (the codeword field of this word) )
460         ['] LIT ,         ( append the codeword LIT )
461         ,               ( append the pointer to the new memory )
462         ['] EXIT ,        ( append the codeword EXIT )
463 ;
464
465
466 : VALUE         ( n -- )
467         WORD CREATE     ( make the dictionary entry (the name follows VALUE) )
468         DOCOL ,         ( append DOCOL )
469         ['] LIT ,       ( append the codeword LIT )
470         ,               ( append the initial value )
471         ['] EXIT ,      ( append the codeword EXIT )
472 ;
473
474 : TO IMMEDIATE  ( n -- )
475         WORD            ( get the name of the value )
476         FIND            ( look it up in the dictionary )
477         >DFA            ( get a pointer to the first data field (the 'LIT') )
478         1+              ( increment to point at the value )
479         STATE @ IF      ( compiling? )
480                 ['] LIT ,         ( compile LIT )
481                 ,               ( compile the address of the value )
482                 ['] ! ,           ( compile ! )
483         ELSE            ( immediate mode )
484                 !               ( update it straightaway )
485         THEN
486 ;
487
488 ( x +TO VAL adds x to VAL )
489 : +TO IMMEDIATE
490         WORD            ( get the name of the value )
491         FIND            ( look it up in the dictionary )
492         >DFA            ( get a pointer to the first data field (the 'LIT') )
493         1+              ( increment to point at the value )
494         STATE @ IF      ( compiling? )
495                 ['] LIT ,         ( compile LIT )
496                 ,               ( compile the address of the value )
497                 ['] +! ,          ( compile +! )
498         ELSE            ( immediate mode )
499                 +!              ( update it straightaway )
500         THEN
501 ;
502
503
504 ( PRINTING THE DICTIONARY ------------------------------------------------------ )
505
506 : ID.
507         1+              ( skip over the link pointer )
508         DUP @           ( get the flags/length byte )
509         F_LENMASK AND   ( mask out the flags - just want the length )
510
511         BEGIN
512                 DUP 0>          ( length > 0? )
513         WHILE
514                 SWAP 1+         ( addr len -- len addr+1 )
515                 DUP @           ( len addr -- len addr char | get the next character)
516                 EMIT            ( len addr char -- len addr | and print it)
517                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
518         REPEAT
519         2DROP           ( len addr -- )
520 ;
521
522 : ?HIDDEN
523         1+              ( skip over the link pointer )
524         @               ( get the flags/length byte )
525         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
526 ;
527 : ?IMMEDIATE
528         1+              ( skip over the link pointer )
529         @               ( get the flags/length byte )
530         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
531 ;
532
533 : WORDS
534         LATEST @        ( start at LATEST dictionary entry )
535         BEGIN
536                 ?DUP            ( while link pointer is not null )
537         WHILE
538                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
539                         DUP ID.         ( but if not hidden, print the word )
540                         SPACE
541                 THEN
542                 @               ( dereference the link pointer - go to previous word )
543         REPEAT
544         CR
545 ;
546
547 ( FORGET ---------------------------------------------------------------------- )
548
549 : FORGET
550         WORD FIND       ( find the word, gets the dictionary entry address )
551         DUP @ LATEST !  ( set LATEST to point to the previous word )
552         HERE !          ( and store HERE with the dictionary address )
553 ;
554
555 ( DUMP ------------------------------------------------------------------------ )
556
557 \ TODO!
558
559 ( CASE ------------------------------------------------------------------------ )
560
561 : CASE IMMEDIATE
562         0               ( push 0 to mark the bottom of the stack )
563 ;
564
565 : OF IMMEDIATE
566         ['] OVER ,        ( compile OVER )
567         ['] = ,           ( compile = )
568         [COMPILE] IF    ( compile IF )
569         ['] DROP ,        ( compile DROP )
570 ;
571
572 : ENDOF IMMEDIATE
573         [COMPILE] ELSE  ( ENDOF is the same as ELSE )
574 ;
575
576 : ENDCASE IMMEDIATE
577         ['] DROP ,        ( compile DROP )
578
579         ( keep compiling THEN until we get to our zero marker )
580         BEGIN
581                 ?DUP
582         WHILE
583                 [COMPILE] THEN
584         REPEAT
585 ;
586
587
588 ( DECOMPILER ------------------------------------------------------------------ )
589
590 : CFA>
591         LATEST @        ( start at LATEST dictionary entry )
592         BEGIN
593                 ?DUP            ( while link pointer is not null )
594         WHILE
595                 2DUP SWAP       ( cfa curr curr cfa )
596                 < IF            ( current dictionary entry < cfa? )
597                         NIP             ( leave curr dictionary entry on the stack )
598                         EXIT
599                 THEN
600                 @               ( follow link pointer back )
601         REPEAT
602         DROP            ( restore stack )
603         0               ( sorry, nothing found )
604 ;
605
606 : SEE
607         WORD FIND       ( find the dictionary entry to decompile )
608
609         ( Now we search again, looking for the next word in the dictionary.  This gives us
610           the length of the word that we will be decompiling.  (Well, mostly it does). )
611         HERE @          ( address of the end of the last compiled word )
612         LATEST @        ( word last curr )
613         BEGIN
614                 2 PICK          ( word last curr word )
615                 OVER            ( word last curr word curr )
616                 <>              ( word last curr word<>curr? )
617         WHILE                   ( word last curr )
618                 NIP             ( word curr )
619                 DUP @           ( word curr prev (which becomes: word last curr) )
620         REPEAT
621
622         DROP            ( at this point, the stack is: start-of-word end-of-word )
623         SWAP            ( end-of-word start-of-word )
624
625         ( begin the definition with : NAME [IMMEDIATE] )
626         ':' EMIT SPACE DUP ID. SPACE
627         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN
628
629         >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
630
631         ( now we start decompiling until we hit the end of the word )
632         BEGIN           ( end start )
633                 2DUP >
634         WHILE
635                 DUP @           ( end start codeword )
636
637                 CASE
638                 ['] LIT OF                ( is it LIT ? )
639                         1+ DUP @                ( get next word which is the integer constant )
640                         .                       ( and print it )
641                 ENDOF
642                 ['] LITSTRING OF          ( is it LITSTRING ? )
643                         [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
644                         1+ DUP @                ( get the length word )
645                         SWAP 1+ SWAP            ( end start+1 length )
646                         2DUP TELL               ( print the string )
647                         '"' EMIT SPACE          ( finish the string with a final quote )
648                         +                       ( end start+1+len, aligned )
649                         1-                     ( because we're about to add 4 below )
650                 ENDOF
651                 ['] 0BRANCH OF            ( is it 0BRANCH ? )
652                         ." 0BRANCH ( "
653                         1+ DUP @               ( print the offset )
654                         .
655                         ." ) "
656                 ENDOF
657                 ['] BRANCH OF             ( is it BRANCH ? )
658                         ." BRANCH ( "
659                         1+ DUP @               ( print the offset )
660                         .
661                         ." ) "
662                 ENDOF
663                 ['] ['] OF                  ( is it ['] ? )
664                         [ CHAR ' ] LITERAL EMIT SPACE
665                         1+ DUP @               ( get the next codeword )
666                         CFA>                    ( and force it to be printed as a dictionary entry )
667                         ID. SPACE
668                 ENDOF
669                 ['] EXIT OF               ( is it EXIT? )
670                         ( We expect the last word to be EXIT, and if it is then we don't print it
671                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
672                           of words, and then it needs to be printed. )
673                         2DUP                    ( end start end start )
674                         1+                     ( end start end start+1 )
675                         <> IF                   ( end start | we're not at the end )
676                                 ." EXIT "
677                         THEN
678                 ENDOF
679                                         ( default case: )
680                         DUP                     ( in the default case we always need to DUP before using )
681                         CFA>                    ( look up the codeword to get the dictionary entry )
682                         ID. SPACE               ( and print it )
683                 ENDCASE
684
685                 1+             ( end start+1 )
686         REPEAT
687
688         ';' EMIT CR
689
690         2DROP           ( restore stack )
691 ;
692
693
694 ( WELCOME MESSAGE ------------------------------------------------------------- )
695
696 CR CR ."  --- TimForth initialized  --- "
697
698