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