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