Implemented FILL and ERASE.
[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
175 \ CASE ------------------------------------------------------------------------
176
177 : CASE IMMEDIATE
178         0               \ push 0 to mark the bottom of the stack
179 ;
180
181 : OF IMMEDIATE
182         ['] OVER ,        \ compile OVER
183         ['] = ,           \ compile =
184         [COMPILE] IF      \ compile IF
185         ['] DROP ,        \ compile DROP
186 ;
187
188 : ENDOF IMMEDIATE
189         [COMPILE] ELSE    \ ENDOF is the same as ELSE
190 ;
191
192 : ENDCASE IMMEDIATE
193         ['] DROP ,        \ compile DROP
194
195         \ keep compiling THEN until we get to our zero marker
196         BEGIN
197                 ?DUP
198         WHILE
199                 [COMPILE] THEN
200         REPEAT
201 ;
202
203
204 \ COMMENTS ----------------------------------------------------------------------
205
206 : ( IMMEDIATE
207         1               \ allowed nested parens by keeping track of depth
208         BEGIN
209                 KEY             \ read next character
210                 DUP '(' = IF    \ open paren?
211                         DROP            \ drop the open paren
212                         1+              \ depth increases
213                 ELSE
214                         ')' = IF        \ close paren?
215                                 1-              \ depth decreases
216                         THEN
217                 THEN
218         DUP 0= UNTIL            \ continue until we reach matching close paren, depth 0
219         DROP            \ drop the depth counter
220 ;
221
222 ( Some more complicated stack examples, showing the stack notation. )
223 : NIP ( x y -- y ) SWAP DROP ;
224 : TUCK ( x y -- y x y ) DUP -ROT ;
225 : PICK ( x_u ... x_1 x_0 u -- x_u ... x_1 x_0 x_u )
226         1+              ( add one because of 'u' on the stack )
227         PSP@ SWAP -     ( add to the stack pointer )
228         @               ( and fetch )
229 ;
230 : ROLL ( x_u x_u-1... x_0 u -- x_u-1 ... x_0 x_u )
231         1+ DUP PICK SWAP    ( x_u x_u-1 ... x_0 x_u u+1 )
232         PSP@ 1- SWAP - PSP@ 2- SWAP
233         DO
234             i 1+ @ i !
235         LOOP
236         SWAP DROP
237 ;
238
239 ( With the looping constructs, we can now write SPACES, which writes n spaces to stdout. )
240 : SPACES        ( n -- )
241         DUP 0> IF
242             0 DO SPACE LOOP
243         ELSE
244             DROP
245         THEN
246 ;
247
248 ( Standard words for manipulating BASE. )
249 : DECIMAL ( -- ) 10 BASE ! ;
250 : HEX ( -- ) 16 BASE ! ;
251
252 ( Compute absolute value. )
253 : ABS           ( n -- |n| )
254         dup 0< if
255                 negate
256         then
257 ;
258
259 : MAX           ( n m -- max )
260         2dup - 0< if
261                 swap drop
262         else
263                 drop
264         then
265 ;
266
267 : MIN           ( n m -- max )
268         2dup - 0> if
269                 swap drop
270         else
271                 drop
272         then
273 ;
274
275 ( PRINTING NUMBERS ---------------------------------------------------------------------- )
276
277 ( This is the underlying recursive definition of U. )
278 : U.            ( u -- )
279         BASE @ /MOD     ( width rem quot )
280         ?DUP IF                 ( if quotient <> 0 then )
281                 RECURSE         ( print the quotient )
282         THEN
283
284         ( print the remainder )
285         DUP 10 < IF
286                 '0'             ( decimal digits 0..9 )
287         ELSE
288                 10 -            ( hex and beyond digits A..Z )
289                 'A'
290         THEN
291         +
292         EMIT
293 ;
294
295 ( This word returns the width (in characters) of an unsigned number in the current base )
296 : UWIDTH        ( u -- width )
297         BASE @ /        ( rem quot )
298         ?DUP IF         ( if quotient <> 0 then )
299                 RECURSE 1+      ( return 1+recursive call )
300         ELSE
301                 1               ( return 1 )
302         THEN
303 ;
304
305 : U.R           ( u width -- )
306         SWAP            ( width u )
307         DUP             ( width u u )
308         UWIDTH          ( width u uwidth )
309         ROT            ( u uwidth width )
310         SWAP -          ( u width-uwidth )
311         ( At this point if the requested width is narrower, we'll have a negative number on the stack.
312           Otherwise the number on the stack is the number of spaces to print.  But SPACES won't print
313           a negative number of spaces anyway, so it's now safe to call SPACES ... )
314         SPACES
315         ( ... and then call the underlying implementation of U. )
316         U.
317 ;
318
319 : .R            ( n width -- )
320         SWAP            ( width n )
321         DUP 0< IF
322                 NEGATE          ( width u )
323                 1               ( save a flag to remember that it was negative | width n 1 )
324                 -ROT             ( 1 width u )
325                 SWAP            ( 1 u width )
326                 1-              ( 1 u width-1 )
327         ELSE
328                 0               ( width u 0 )
329                 -ROT             ( 0 width u )
330                 SWAP            ( 0 u width )
331         THEN
332         SWAP            ( flag width u )
333         DUP             ( flag width u u )
334         UWIDTH          ( flag width u uwidth )
335         ROT            ( flag u uwidth width )
336         SWAP -          ( flag u width-uwidth )
337
338         SPACES          ( flag u )
339         SWAP            ( u flag )
340
341         IF                      ( was it negative? print the - character )
342                 '-' EMIT
343         THEN
344
345         U.
346 ;
347
348 : . 0 .R SPACE ;
349
350 : .S            ( -- )
351         '<' EMIT DEPTH U. '>' EMIT SPACE
352         PSP0 @ 1+
353         BEGIN
354                 DUP PSP@ 2 - <=
355         WHILE
356                 DUP @ .
357                 1+
358         REPEAT
359         DROP
360 ;
361
362 : U. U. SPACE ;
363
364 ( ? fetches the integer at an address and prints it. )
365 : ? ( addr -- ) @ . ;
366
367 ( c a b WITHIN returns true if a <= c and c < b )
368 : WITHIN
369         -ROT             ( b c a )
370         OVER            ( b c a c )
371         <= IF
372                 > IF            ( b c -- )
373                         TRUE
374                 ELSE
375                         FALSE
376                 THEN
377         ELSE
378                 2DROP           ( b c -- )
379                 FALSE
380         THEN
381 ;
382
383
384 ( STRINGS ---------------------------------------------------------------------- )
385
386 ( Since the smallest unit of memory in our system is 64 bits and since strings
387   are stored as arrays of 64 bit integers, the character store/fetch words are
388   just aliases of the standard store/fetch words. )
389 : C! ! ;
390 : C@ @ ;
391
392 ( Block copy, however, is important and novel: )
393 : CMOVE ( src dest length -- )
394
395         DUP 0<= IF
396                 EXIT
397         THEN
398
399         -ROT OVER -         ( length src (dest-src) )
400         -ROT DUP ROT + SWAP ( (dest-src) (src+length) src )
401     
402         DO
403                 I @         ( (dest-src) i@ )
404                 OVER I +    ( (dest-src) i@ (dest-src+i) )
405                 !           ( (dest-src) )
406         LOOP
407
408         DROP
409 ;
410
411 ( C, appends a byte to the current compiled word. )
412 : C,
413         HERE @ C!
414         1 HERE +!
415 ;
416
417 : S" IMMEDIATE          ( -- addr len )
418         STATE @ IF      ( compiling? )
419                 ['] LITSTRING ,   ( compile LITSTRING )
420                 HERE @          ( save the address of the length word on the stack )
421                 0 ,             ( dummy length - we don't know what it is yet )
422                 KEY DROP
423                 BEGIN
424                         KEY             ( get next character of the string )
425                         DUP '"' <>
426                 WHILE
427                         C,              ( copy character )
428                 REPEAT
429                 DROP            ( drop the double quote character at the end )
430                 DUP             ( get the saved address of the length word )
431                 HERE @ SWAP -   ( calculate the length )
432                 1-              ( subtract 1 (because we measured from the start of the length word) )
433                 SWAP !          ( and back-fill the length location )
434         ELSE            ( immediate mode )
435                 HERE @          ( get the start address of the temporary space )
436                 KEY DROP
437                 BEGIN
438                         KEY
439                         DUP '"' <>
440                 WHILE
441                         OVER C!         ( save next character )
442                         1+              ( increment address )
443                 REPEAT
444                 DROP            ( drop the final " character )
445                 HERE @ -        ( calculate the length )
446                 HERE @          ( push the start address )
447                 SWAP            ( addr len )
448         THEN
449 ;
450
451 : ." IMMEDIATE          ( -- )
452         [COMPILE] S"    ( read the string, and compile LITSTRING, etc. )
453         ['] TELL ,      ( compile the final TELL )
454 ;
455
456 : .( 
457         KEY DROP
458         BEGIN
459                 KEY
460                 DUP ')' = IF
461                         DROP    ( drop the double quote character )
462                         EXIT    ( return from this function )
463                 THEN
464                 EMIT
465         AGAIN
466 ;
467
468
469 ( CONSTANTS AND VARIABLES ------------------------------------------------------ )
470
471 : CONSTANT
472         WORD HEADER     ( make dictionary entry (the name follows CONSTANT) )
473         DOCOL ,         ( append DOCOL (the codeword field of this word) )
474         ['] LIT ,       ( append the codeword LIT )
475         ,               ( append the value on the top of the stack )
476         ['] EXIT ,      ( append the codeword EXIT )
477 ;
478
479 : ALLOT         ( n -- )
480         HERE +!         ( adds n to HERE, after this the old value of HERE is still on the stack )
481 ;
482
483 : VARIABLE
484         CREATE
485         1 CELLS ALLOT   ( allocate 1 cell of memory, push the pointer to this memory )
486 ;
487
488
489 : VALUE         ( n -- )
490         WORD HEADER     ( make the dictionary entry (the name follows VALUE) )
491         DOCOL ,         ( append DOCOL )
492         ['] LIT ,       ( append the codeword LIT )
493         ,               ( append the initial value )
494         ['] EXIT ,      ( append the codeword EXIT )
495 ;
496
497 : TO IMMEDIATE  ( n -- )
498         WORD            ( get the name of the value )
499         FIND            ( look it up in the dictionary )
500         >DFA            ( get a pointer to the first data field (the 'LIT') )
501         1+              ( increment to point at the value )
502         STATE @ IF      ( compiling? )
503                 ['] LIT ,         ( compile LIT )
504                 ,               ( compile the address of the value )
505                 ['] ! ,           ( compile ! )
506         ELSE            ( immediate mode )
507                 !               ( update it straightaway )
508         THEN
509 ;
510
511 ( x +TO VAL adds x to VAL )
512 : +TO IMMEDIATE
513         WORD            ( get the name of the value )
514         FIND            ( look it up in the dictionary )
515         >DFA            ( get a pointer to the first data field (the 'LIT') )
516         1+              ( increment to point at the value )
517         STATE @ IF      ( compiling? )
518                 ['] LIT ,         ( compile LIT )
519                 ,               ( compile the address of the value )
520                 ['] +! ,          ( compile +! )
521         ELSE            ( immediate mode )
522                 +!              ( update it straightaway )
523         THEN
524 ;
525
526 ( Fill u ints, starting at a, with the value b )
527 : FILL          ( a u b -- )
528         -ROT OVER + SWAP ?DO
529                 DUP I !
530         LOOP
531         DROP
532 ;
533
534 : ERASE         ( a u -- )
535         0 FILL
536 ;
537
538 ( PRINTING THE DICTIONARY ------------------------------------------------------ )
539
540 : ID.
541         1+              ( skip over the link pointer )
542         DUP @           ( get the flags/length byte )
543         F_LENMASK AND   ( mask out the flags - just want the length )
544
545         BEGIN
546                 DUP 0>          ( length > 0? )
547         WHILE
548                 SWAP 1+         ( addr len -- len addr+1 )
549                 DUP @           ( len addr -- len addr char | get the next character)
550                 DUP 32 >= OVER 127 <= AND IF
551                         EMIT    ( len addr char -- len addr | and print it)
552                 ELSE
553                         BASE @ SWAP HEX
554                         ." \x" 0 .R
555                         BASE !
556                 THEN
557                 SWAP 1-         ( len addr -- addr len-1    | subtract one from length )
558         REPEAT
559         2DROP           ( len addr -- )
560 ;
561
562 : ?HIDDEN
563         1+              ( skip over the link pointer )
564         @               ( get the flags/length byte )
565         F_HIDDEN AND    ( mask the F_HIDDEN flag and return it (as a truth value) )
566 ;
567 : ?IMMEDIATE
568         1+              ( skip over the link pointer )
569         @               ( get the flags/length byte )
570         F_IMMED AND     ( mask the F_IMMED flag and return it (as a truth value) )
571 ;
572
573 : WORDS
574         LATEST @        ( start at LATEST dictionary entry )
575         BEGIN
576                 ?DUP            ( while link pointer is not null )
577         WHILE
578                 DUP ?HIDDEN NOT IF      ( ignore hidden words )
579                         DUP ID.         ( but if not hidden, print the word )
580                         SPACE
581                 THEN
582                 @               ( dereference the link pointer - go to previous word )
583         REPEAT
584         CR
585 ;
586
587
588 ( FORGET ---------------------------------------------------------------------- )
589
590 : FORGET
591         WORD FIND       ( find the word, gets the dictionary entry address )
592         DUP @ LATEST !  ( set LATEST to point to the previous word )
593         HERE !          ( and store HERE with the dictionary address )
594 ;
595
596 ( DUMP ------------------------------------------------------------------------ )
597
598 \ TODO!
599
600
601 ( DECOMPILER ------------------------------------------------------------------ )
602
603 : CFA>
604         LATEST @        ( start at LATEST dictionary entry )
605         BEGIN
606                 ?DUP            ( while link pointer is not null )
607         WHILE
608                 2DUP SWAP       ( cfa curr curr cfa )
609                 < IF            ( current dictionary entry < cfa? )
610                         NIP             ( leave curr dictionary entry on the stack )
611                         EXIT
612                 THEN
613                 @               ( follow link pointer back )
614         REPEAT
615         DROP            ( restore stack )
616         0               ( sorry, nothing found )
617 ;
618
619 : SEE
620         WORD FIND       ( find the dictionary entry to decompile )
621
622         ( Now we search again, looking for the next word in the dictionary.  This gives us
623           the length of the word that we will be decompiling.  (Well, mostly it does). )
624         HERE @          ( address of the end of the last compiled word )
625         LATEST @        ( word last curr )
626         BEGIN
627                 2 PICK          ( word last curr word )
628                 OVER            ( word last curr word curr )
629                 <>              ( word last curr word<>curr? )
630         WHILE                   ( word last curr )
631                 NIP             ( word curr )
632                 DUP @           ( word curr prev (which becomes: word last curr) )
633         REPEAT
634
635         DROP            ( at this point, the stack is: start-of-word end-of-word )
636         SWAP            ( end-of-word start-of-word )
637
638         DUP >CFA @ CASE
639                 DOCOL OF
640                         \ Colon definition
641                         ':' EMIT SPACE DUP ID. SPACE
642                         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN CR
643                 ENDOF
644                 DOVAR OF
645                         \ Variable definition
646                         ." Variable " DUP ID. CR
647                         2DROP EXIT
648                 ENDOF
649                 DOCON OF
650                         \ Constant definition
651                         ." Constant " DUP ID. CR
652                         2DROP EXIT
653                 ENDOF
654
655                 \ Unknown codeword
656                 ." Primitive or word with unrecognized codeword." CR 
657                 DROP 2DROP EXIT
658         ENDCASE
659
660         ( begin the definition with : NAME [IMMEDIATE] )
661         ( ':' EMIT SPACE DUP ID. SPACE
662         DUP ?IMMEDIATE IF ." IMMEDIATE " THEN CR 4 )
663
664         4 SPACES
665
666         >DFA            ( get the data address, ie. points after DOCOL | end-of-word start-of-data )
667
668         ( now we start decompiling until we hit the end of the word )
669         BEGIN           ( end start )
670                 2DUP >
671         WHILE
672                 DUP @           ( end start codeword )
673
674                 CASE
675                 ['] LIT OF                ( is it LIT ? )
676                         1+ DUP @                ( get next word which is the integer constant )
677                         .                       ( and print it )
678                 ENDOF
679                 ['] LITSTRING OF          ( is it LITSTRING ? )
680                         [ CHAR S ] LITERAL EMIT '"' EMIT SPACE ( print S"<space> )
681                         1+ DUP @                ( get the length word )
682                         SWAP 1+ SWAP            ( end start+1 length )
683                         2DUP TELL               ( print the string )
684                         '"' EMIT SPACE          ( finish the string with a final quote )
685                         +                       ( end start+1+len, aligned )
686                         1-                     ( because we're about to add 4 below )
687                 ENDOF
688                 ['] 0BRANCH OF            ( is it 0BRANCH ? )
689                         ." 0BRANCH ( "
690                         1+ DUP @               ( print the offset )
691                         .
692                         ." ) "
693                 ENDOF
694                 ['] BRANCH OF             ( is it BRANCH ? )
695                         ." BRANCH ( "
696                         1+ DUP @               ( print the offset )
697                         .
698                         ." ) "
699                 ENDOF
700                 ['] ['] OF                  ( is it ['] ? )
701                         ." ['] "
702                         1+ DUP @               ( get the next codeword )
703                         CFA>                    ( and force it to be printed as a dictionary entry )
704                         ID. SPACE
705                 ENDOF
706                 ['] EXIT OF               ( is it EXIT? )
707                         ( We expect the last word to be EXIT, and if it is then we don't print it
708                           because EXIT is normally implied by ;.  EXIT can also appear in the middle
709                           of words, and then it needs to be printed. )
710                         2DUP                    ( end start end start )
711                         1+                     ( end start end start+1 )
712                         <> IF                   ( end start | we're not at the end )
713                                 ." EXIT "
714                         THEN
715                 ENDOF
716                                         ( default case: )
717                         DUP                     ( in the default case we always need to DUP before using )
718                         CFA>                    ( look up the codeword to get the dictionary entry )
719                         ID. SPACE               ( and print it )
720                 ENDCASE
721
722                 1+             ( end start+1 )
723         REPEAT
724
725         ';' EMIT CR
726
727         2DROP           ( restore stack )
728 ;
729
730
731 ( MEMORY  ------------------------------------------------------------------ )
732
733 : UNUSED  ( -- cells )
734         MEMSIZE HERE @ - ;