2bd959d2eb59c9648fd92a5c76f799c10f12763d
[debian/pforth] / fth / system.fth
1 : FIRST_COLON ;
2
3 : LATEST context @ ;
4
5 : FLAG_IMMEDIATE 64 ;
6
7 : IMMEDIATE
8         latest dup c@ flag_immediate OR
9         swap c!
10 ;
11
12 : (   41 word drop ; immediate
13 ( That was the definition for the comment word. )
14 ( Now we can add comments to what we are doing! )
15 ( Note that we are in decimal numeric input mode. )
16
17 : \ ( <line> -- , comment out rest of line )
18         EOL word drop
19 ; immediate
20
21 \ 1 echo !  \ Uncomment this line to echo Forth code while compiling.
22
23 \ *********************************************************************
24 \ This is another style of comment that is common in Forth.
25 \ pFORTH - Portable Forth System
26 \ Based on HMSL Forth
27 \
28 \ Author: Phil Burk
29 \ Copyright 1994 3DO, Phil Burk, Larry Polansky, David Rosenboom
30 \
31 \ Permission to use, copy, modify, and/or distribute this
32 \ software for any purpose with or without fee is hereby granted.
33 \
34 \ THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL
35 \ WARRANTIES WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED
36 \ WARRANTIES OF MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL
37 \ THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, INDIRECT, OR
38 \ CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING
39 \ FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
40 \ CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
41 \ OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
42 \ *********************************************************************
43
44 : COUNT  dup 1+ swap c@ ;
45
46 \ Miscellaneous support words
47 : ON ( addr -- , set true )
48         -1 swap !
49 ;
50 : OFF ( addr -- , set false )
51         0 swap !
52 ;
53
54 : CELL+ ( n -- n+cell )  cell + ;
55 : CELL- ( n -- n+cell )  cell - ;
56 : CELL* ( n -- n*cell )  cells ;
57
58 : CHAR+ ( n -- n+size_of_char ) 1+ ;
59 : CHARS ( n -- n*size_of_char , don't do anything)  ; immediate
60
61 \ useful stack manipulation words
62 : -ROT ( a b c -- c a b )
63         rot rot
64 ;
65 : 3DUP ( a b c -- a b c a b c )
66         2 pick 2 pick 2 pick
67 ;
68 : 2DROP ( a b -- )
69         drop drop
70 ;
71 : NIP ( a b -- b )
72         swap drop
73 ;
74 : TUCK ( a b -- b a b )
75         swap over
76 ;
77
78 : <= ( a b -- f , true if A <= b )
79         > 0=
80 ;
81 : >= ( a b -- f , true if A >= b )
82         < 0=
83 ;
84
85 : INVERT ( n -- 1'comp )
86     -1 xor
87 ;
88
89 : NOT ( n -- !n , logical negation )
90         0=
91 ;
92
93 : NEGATE ( n -- -n )
94         0 swap -
95 ;
96
97 : DNEGATE ( d -- -d , negate by doing 0-d )
98         0 0 2swap d-
99 ;
100
101
102 \ --------------------------------------------------------------------
103
104 : ID.   ( nfa -- )
105     count 31 and type
106 ;
107
108 : DECIMAL   10 base !  ;
109 : OCTAL      8 base !  ;
110 : HEX       16 base !  ;
111 : BINARY     2 base !  ;
112
113 : PAD ( -- addr )
114         here 128 +
115 ;
116
117 : $MOVE ( $src $dst -- )
118         over c@ 1+ cmove
119 ;
120 : BETWEEN ( n lo hi -- flag , true if between lo & hi )
121         >r over r> > >r
122         < r> or 0=
123 ;
124 : [ ( -- , enter interpreter mode )
125         0 state !
126 ; immediate
127 : ] ( -- enter compile mode )
128         1 state !
129 ;
130
131 : EVEN-UP  ( n -- n | n+1 , make even )  dup 1 and +  ;
132 : ALIGNED  ( addr -- a-addr )
133         [ cell 1- ] literal +
134         [ cell 1- invert ] literal and
135 ;
136 : ALIGN ( -- , align DP )  dp @ aligned dp ! ;
137 : ALLOT ( nbytes -- , allot space in dictionary ) dp +! ( align ) ;
138
139 : C,    ( c -- )  here c! 1 chars dp +! ;
140 : W,    ( w -- )  dp @ even-up dup dp !    w!  2 chars dp +! ;
141 : , ( n -- , lay into dictionary )  align here !  cell allot ;
142
143 \ Dictionary conversions ------------------------------------------
144
145 : N>NEXTLINK  ( nfa -- nextlink , traverses name field )
146         dup c@ 31 and 1+ + aligned
147 ;
148
149 : NAMEBASE  ( -- base-of-names )
150         Headers-Base @
151 ;
152 : CODEBASE  ( -- base-of-code dictionary )
153         Code-Base @
154 ;
155
156 : NAMELIMIT  ( -- limit-of-names )
157         Headers-limit @
158 ;
159 : CODELIMIT  ( -- limit-of-code, last address in dictionary )
160         Code-limit @
161 ;
162
163 : NAMEBASE+   ( rnfa -- nfa , convert relocatable nfa to actual )
164         namebase +
165 ;
166
167 : >CODE ( xt -- secondary_code_address, not valid for primitives )
168         codebase +
169 ;
170
171 : CODE> ( secondary_code_address -- xt , not valid for primitives )
172         codebase -
173 ;
174
175 : N>LINK  ( nfa -- lfa )
176         2 CELLS -
177 ;
178
179 : >BODY   ( xt -- pfa )
180     >code body_offset +
181 ;
182
183 : BODY>   ( pfa -- xt )
184     body_offset - code>
185 ;
186
187 \ convert between addresses useable by @, and relocatable addresses.
188 : USE->REL  ( useable_addr -- rel_addr )
189         codebase -
190 ;
191 : REL->USE  ( rel_addr -- useable_addr )
192         codebase +
193 ;
194
195 \ for JForth code
196 \ : >REL  ( adr -- adr )  ; immediate
197 \ : >ABS  ( adr -- adr )  ; immediate
198
199 : X@ ( addr -- xt , fetch execution token from relocatable )   @ ;
200 : X! ( addr -- xt , store execution token as relocatable )   ! ;
201
202 \ Compiler support ------------------------------------------------
203 : COMPILE, ( xt -- , compile call to xt )
204         ,
205 ;
206
207 ( Compiler support , based on FIG )
208 : [COMPILE]  ( <name> -- , compile now even if immediate )
209     ' compile,
210 ;  IMMEDIATE
211
212 : (COMPILE) ( xt -- , postpone compilation of token )
213         [compile] literal       ( compile a call to literal )
214         ( store xt of word to be compiled )
215
216         [ ' compile, ] literal   \ compile call to compile,
217         compile,
218 ;
219
220 : COMPILE  ( <name> -- , save xt and compile later )
221     ' (compile)
222 ; IMMEDIATE
223
224
225 : :NONAME ( -- xt , begin compilation of headerless secondary )
226         align
227         here code>   \ convert here to execution token
228         ]
229 ;
230
231 \ Error codes defined in ANSI Exception word set.
232 : ERR_ABORT         -1 ;   \ general abort
233 : ERR_ABORTQ        -2 ;   \ for abort"
234 : ERR_EXECUTING    -14 ;   \ compile time word while not compiling
235 : ERR_PAIRS        -22 ;   \ mismatch in conditional
236 : ERR_DEFER       -258 ;  \ not a deferred word
237
238 : ABORT ( i*x -- )
239     ERR_ABORT throw
240 ;
241
242 \ Conditionals in '83 form -----------------------------------------
243 : CONDITIONAL_KEY ( -- , lazy constant ) 29521 ;
244 : ?CONDITION   ( f -- )  conditional_key - err_pairs ?error ;
245 : >MARK      ( -- addr )   here 0 ,  ;
246 : >RESOLVE   ( addr -- )   here over - swap !  ;
247 : <MARK      ( -- addr )   here  ;
248 : <RESOLVE   ( addr -- )   here - ,  ;
249
250 : ?COMP  ( -- , error if not compiling )
251         state @ 0= err_executing ?error
252 ;
253 : ?PAIRS ( n m -- )
254         - err_pairs ?error
255 ;
256 \ conditional primitives
257 : IF     ( -- f orig )  ?comp compile 0branch  conditional_key >mark     ; immediate
258 : THEN   ( f orig -- )  swap ?condition  >resolve   ; immediate
259 : BEGIN  ( -- f dest )  ?comp conditional_key <mark   ; immediate
260 : AGAIN  ( f dest -- )  compile branch  swap ?condition  <resolve  ; immediate
261 : UNTIL  ( f dest -- )  compile 0branch swap ?condition  <resolve  ; immediate
262 : AHEAD  ( -- f orig )  compile branch   conditional_key >mark     ; immediate
263
264 \ conditionals built from primitives
265 : ELSE   ( f orig1 -- f orig2 )
266     [compile] AHEAD  2swap [compile] THEN  ; immediate
267 : WHILE  ( f dest -- f orig f dest )  [compile]  if   2swap ; immediate
268 : REPEAT ( -- f orig f dest ) [compile] again  [compile] then  ; immediate
269
270 : [']  ( <name> -- xt , define compile time tick )
271         ?comp ' [compile] literal
272 ; immediate
273
274 \ for example:
275 \ compile time:  compile create , (does>) then ;
276 \ execution time:  create <name>, ',' data, then patch pi to point to @
277 \    : con create , does> @ ;
278 \    345 con pi
279 \    pi
280 \
281 : (DOES>)  ( xt -- , modify previous definition to execute code at xt )
282         latest name> >code \ get address of code for new word
283         cell + \ offset to second cell in create word
284         !      \ store execution token of DOES> code in new word
285 ;
286
287 : DOES>   ( -- , define execution code for CREATE word )
288         0 [compile] literal \ dummy literal to hold xt
289         here cell-          \ address of zero in literal
290         compile (does>)     \ call (DOES>) from new creation word
291         >r                  \ move addrz to return stack so ; doesn't see stack garbage
292         [compile] ;         \ terminate part of code before does>
293         r>
294         :noname       ( addrz xt )
295         swap !              \ save execution token in literal
296 ; immediate
297
298 : VARIABLE  ( <name> -- )
299     CREATE 0 , \ IMMEDIATE
300 \       DOES> [compile] aliteral  \ %Q This could be optimised
301 ;
302
303 : 2VARIABLE  ( <name> -c- ) ( -x- addr )
304         create 0 , 0 ,
305 ;
306
307 : CONSTANT  ( n <name> -c- ) ( -x- n )
308         CREATE , ( n -- )
309         DOES> @ ( -- n )
310 ;
311
312
313
314 0 1- constant -1
315 0 2- constant -2
316
317 : 2! ( x1 x2 addr -- , store x2 followed by x1 )
318         swap over ! cell+ !
319 ;
320 : 2@ ( addr -- x1 x2 )
321         dup cell+ @ swap @
322 ;
323
324
325 : ABS ( n -- |n| )
326         dup 0<
327         IF negate
328         THEN
329 ;
330 : DABS ( d -- |d| )
331         dup 0<
332         IF dnegate
333         THEN
334 ;
335
336 : S>D  ( s -- d , extend signed single precision to double )
337         dup 0<
338         IF -1
339         ELSE 0
340         THEN
341 ;
342
343 : D>S ( d -- s ) drop ;
344
345 : /MOD ( a b -- rem quo , unsigned version, FIXME )
346         >r s>d r> um/mod
347 ;
348
349 : MOD ( a b -- rem )
350         /mod drop
351 ;
352
353 : 2* ( n -- n*2 )
354         1 lshift
355 ;
356 : 2/ ( n -- n/2 )
357         1 arshift
358 ;
359
360 : D2*  ( d -- d*2 )
361         2* over
362         cell 8 * 1- rshift or  swap
363         2* swap
364 ;
365
366 : D= ( xd1 xd2 -- flag )
367         rot = -rot = and
368 ;
369
370 : D< ( d1 d2 -- flag )
371     d- nip 0<
372 ;
373
374 : D> ( d1 d2 -- flag )
375     2swap d<
376 ;
377
378 \ define some useful constants ------------------------------
379 1 0= constant FALSE
380 0 0= constant TRUE
381 32 constant BL
382
383
384 \ Store and Fetch relocatable data addresses. ---------------
385 : IF.USE->REL  ( use -- rel , preserve zero )
386         dup IF use->rel THEN
387 ;
388 : IF.REL->USE  ( rel -- use , preserve zero )
389         dup IF rel->use THEN
390 ;
391
392 : A!  ( dictionary_address addr -- )
393     >r if.use->rel r> !
394 ;
395 : A@  ( addr -- dictionary_address )
396     @ if.rel->use
397 ;
398
399 : A, ( dictionary_address -- )
400     if.use->rel ,
401 ;
402
403 \ Stack data structure ----------------------------------------
404 \ This is a general purpose stack utility used to implement necessary
405 \ stacks for the compiler or the user.  Not real fast.
406 \ These stacks grow up which is different then normal.
407 \   cell 0 - stack pointer, offset from pfa of word
408 \   cell 1 - limit for range checking
409 \   cell 2 - first data location
410
411 : :STACK   ( #cells -- )
412         CREATE  2 cells ,          ( offset of first data location )
413                 dup ,              ( limit for range checking, not currently used )
414                 cells cell+ allot  ( allot an extra cell for safety )
415 ;
416
417 : >STACK  ( n stack -- , push onto stack, postincrement )
418         dup @ 2dup cell+ swap ! ( -- n stack offset )
419         + !
420 ;
421
422 : STACK>  ( stack -- n , pop , predecrement )
423         dup @ cell- 2dup swap !
424         + @
425 ;
426
427 : STACK@ ( stack -- n , copy )
428         dup @ cell- + @
429 ;
430
431 : STACK.PICK ( index stack -- n , grab Nth from top of stack )
432         dup @ cell- +
433         swap cells -   \ offset for index
434         @
435 ;
436 : STACKP ( stack -- ptr , to next empty location on stack )
437     dup @ +
438 ;
439
440 : 0STACKP  ( stack -- , clear stack)
441     8 swap !
442 ;
443
444 32 :stack ustack
445 ustack 0stackp
446
447 \ Define JForth like words.
448 : >US ustack >stack ;
449 : US> ustack stack> ;
450 : US@ ustack stack@ ;
451 : 0USP ustack 0stackp ;
452
453
454 \ DO LOOP ------------------------------------------------
455
456 3 constant do_flag
457 4 constant leave_flag
458 5 constant ?do_flag
459
460 : DO    ( -- , loop-back do_flag jump-from ?do_flag )
461         ?comp
462         compile  (do)
463         here >us do_flag  >us  ( for backward branch )
464 ; immediate
465
466 : ?DO    ( -- , loop-back do_flag jump-from ?do_flag  , on user stack )
467         ?comp
468         ( leave address to set for forward branch )
469         compile  (?do)
470         here 0 ,
471         here >us do_flag  >us  ( for backward branch )
472         >us ( for forward branch ) ?do_flag >us
473 ; immediate
474
475 : LEAVE  ( -- addr leave_flag )
476         compile (leave)
477         here 0 , >us
478         leave_flag >us
479 ; immediate
480
481 : LOOP-FORWARD  ( -us- jump-from ?do_flag -- )
482         BEGIN
483                 us@ leave_flag =
484                 us@ ?do_flag =
485                 OR
486         WHILE
487                 us> leave_flag =
488                 IF
489                         us> here over - cell+ swap !
490                 ELSE
491                         us> dup
492                         here swap -
493                         cell+ swap !
494                 THEN
495         REPEAT
496 ;
497
498 : LOOP-BACK  (  loop-addr do_flag -us- )
499         us> do_flag ?pairs
500         us> here -  here
501         !
502         cell allot
503 ;
504
505 : LOOP    ( -- , loop-back do_flag jump-from ?do_flag )
506    compile  (loop)
507    loop-forward loop-back
508 ; immediate
509
510 \ : DOTEST 5 0 do 333 . loop 888 . ;
511 \ : ?DOTEST0 0 0 ?do 333 . loop 888 . ;
512 \ : ?DOTEST1 5 0 ?do 333 . loop 888 . ;
513
514 : +LOOP    ( -- , loop-back do_flag jump-from ?do_flag )
515    compile  (+loop)
516    loop-forward loop-back
517 ; immediate
518
519 : UNLOOP ( loop-sys -r- )
520         r> \ save return pointer
521         rdrop rdrop
522         >r
523 ;
524
525 : RECURSE ( ? -- ? , call the word currently being defined )
526         latest  name> compile,
527 ; immediate
528
529
530
531 : SPACE  bl emit ;
532 : SPACES  512 min 0 max 0 ?DO space LOOP ;
533 : 0SP depth 0 ?do drop loop ;
534
535 : >NEWLINE ( -- , CR if needed )
536         out @ 0>
537         IF cr
538         THEN
539 ;
540
541
542 \ Support for DEFER --------------------
543 : CHECK.DEFER  ( xt -- , error if not a deferred word by comparing to type )
544     >code @
545         ['] emit >code @
546         - err_defer ?error
547 ;
548
549 : >is ( xt -- address_of_vector )
550         >code
551         cell +
552 ;
553
554 : (IS)  ( xt_do xt_deferred -- )
555         >is !
556 ;
557
558 : IS  ( xt <name> -- , act like normal IS )
559         '  \ xt
560         dup check.defer
561         state @
562         IF [compile] literal compile (is)
563         ELSE (is)
564         THEN
565 ; immediate
566
567 : (WHAT'S)  ( xt -- xt_do )
568         >is @
569 ;
570 : WHAT'S  ( <name> -- xt , what will deferred word call? )
571         '  \ xt
572         dup check.defer
573         state @
574         IF [compile] literal compile (what's)
575         ELSE (what's)
576         THEN
577 ; immediate
578
579 : /STRING   ( addr len n -- addr' len' )
580    over min  rot over   +  -rot  -
581 ;
582 : PLACE   ( addr len to -- , move string )
583    3dup  1+  swap cmove  c! drop
584 ;
585
586 : PARSE-WORD   ( char -- addr len )
587    >r  source tuck >in @ /string  r@ skip over swap r> scan
588    >r  over -  rot r>  dup 0<> + - >in !
589 ;
590 : PARSE   ( char -- addr len )
591    >r  source >in @  /string  over swap  r> scan
592    >r  over -  dup r> 0<>  -  >in +!
593 ;
594
595 : LWORD  ( char -- addr )
596         parse-word here place here \ 00002 , use PARSE-WORD
597 ;
598
599 : ASCII ( <char> -- char , state smart )
600         bl parse drop c@
601         state @
602         IF [compile] literal
603         THEN
604 ; immediate
605
606 : CHAR ( <char> -- char , interpret mode )
607         bl parse drop c@
608 ;
609
610 : [CHAR] ( <char> -- char , for compile mode )
611         char [compile] literal
612 ; immediate
613
614 : $TYPE  ( $string -- )
615         count type
616 ;
617
618 : 'word   ( -- addr )   here ;
619
620 : EVEN    ( addr -- addr' )   dup 1 and +  ;
621
622 : (C")   ( -- $addr , some Forths return addr AND count, OBSOLETE?)
623         r> dup count + aligned >r
624 ;
625 : (S")   ( -- c-addr cnt )
626         r> count 2dup + aligned >r
627 ;
628
629 : (.")  ( -- , type following string )
630         r> count 2dup + aligned >r type
631 ;
632
633 : ",  ( adr len -- , place string into dictionary )
634          tuck 'word place 1+ allot align
635 ;
636 : ,"   ( -- )
637    [char] " parse ",
638 ;
639
640 : .(  ( <string> -- , type string delimited by parentheses )
641     [CHAR] ) PARSE TYPE
642 ; IMMEDIATE
643
644 : ."   ( <string> -- , type string )
645         state @
646         IF      compile (.")  ,"
647         ELSE [char] " parse type
648         THEN
649 ; immediate
650
651
652 : .'   ( <string> -- , type string delimited by single quote )
653         state @
654         IF    compile (.")  [char] ' parse ",
655         ELSE [char] ' parse type
656         THEN
657 ; immediate
658
659 : C"    ( <string> -- addr , return string address, ANSI )
660         state @
661         IF compile (c")   ,"
662         ELSE [char] " parse pad place pad
663         THEN
664 ; immediate
665
666 : S"    ( <string> -- , -- addr , return string address, ANSI )
667         state @
668         IF compile (s")   ,"
669         ELSE [char] " parse pad place pad count
670         THEN
671 ; immediate
672
673 : "    ( <string> -- , -- addr , return string address )
674         [compile] C"
675 ; immediate
676 : P"    ( <string> -- , -- addr , return string address )
677         [compile] C"
678 ; immediate
679
680 : ""  ( <string> -- addr )
681         state @
682         IF
683                 compile (C")
684                 bl parse-word  ",
685         ELSE
686                 bl parse-word pad place pad
687         THEN
688 ; immediate
689
690 : SLITERAL ( addr cnt -- , compile string )
691     compile (S")
692     ",
693 ; IMMEDIATE
694
695 : $APPEND ( addr count $1 -- , append text to $1 )
696     over >r
697         dup >r
698     count +  ( -- a2 c2 end1 )
699     swap cmove
700     r> dup c@  ( a1 c1 )
701     r> + ( -- a1 totalcount )
702     swap c!
703 ;
704
705
706 \ ANSI word to replace [COMPILE] and COMPILE ----------------
707 : POSTPONE  ( <name> -- )
708     bl word find
709     dup 0=
710     IF
711         ." Postpone could not find " count type cr abort
712     ELSE
713         0>
714         IF compile,  \ immediate
715         ELSE (compile)  \ normal
716         THEN
717     THEN
718 ; immediate
719
720 \ -----------------------------------------------------------------
721 \ Auto Initialization
722 : AUTO.INIT  ( -- )
723 \ Kernel finds AUTO.INIT and executes it after loading dictionary.
724 \   ." Begin AUTO.INIT ------" cr
725 ;
726 : AUTO.TERM  ( -- )
727 \ Kernel finds AUTO.TERM and executes it on bye.
728 \   ." End AUTO.TERM ------" cr
729 ;
730
731 \ -------------- INCLUDE ------------------------------------------
732 variable TRACE-INCLUDE
733
734 : INCLUDE.MARK.START  ( c-addr u -- , mark start of include for FILE?)
735     dup 5 + allocate throw >r
736     " ::::" r@ $move
737     r@ $append
738     r@ ['] noop (:)
739     r> free throw
740 ;
741
742 : INCLUDE.MARK.END  ( -- , mark end of include )
743     " ;;;;" ['] noop (:)
744 ;
745
746 : INCLUDED ( c-addr u -- )
747         \ Print messages.
748         trace-include @
749         IF
750                 >newline ." Include " 2dup type cr
751         THEN
752         here >r
753         2dup r/o open-file
754         IF  ( -- c-addr u bad-fid )
755                 drop ." Could not find file " type cr abort
756         ELSE ( -- c-addr u good-fid )
757                 -rot include.mark.start
758                 depth >r
759                 include-file    \ will also close the file
760                 depth 1+ r> -
761                 IF
762                         ." Warning: stack depth changed during include!" cr
763                         .s cr
764                         0sp
765                 THEN
766                 include.mark.end
767         THEN
768         trace-include @
769         IF
770                 ."     include added " here r@ - . ." bytes,"
771                 codelimit here - . ." left." cr
772         THEN
773         rdrop
774 ;
775
776 : $INCLUDE ( $filename -- ) count included ;
777
778 create INCLUDE-SAVE-NAME 128 allot
779 : INCLUDE ( <fname> -- )
780         BL lword
781         dup include-save-name $move  \ save for RI
782         $include
783 ;
784
785 : RI ( -- , ReInclude previous file as a convenience )
786         include-save-name $include
787 ;
788
789 : INCLUDE? ( <word> <file> -- , load file if word not defined )
790         bl word find
791         IF drop bl word drop  ( eat word from source )
792         ELSE drop include
793         THEN
794 ;
795
796 \ desired sizes for dictionary loaded after SAVE-FORTH
797 variable HEADERS-SIZE
798 variable CODE-SIZE
799
800 : AUTO.INIT
801     auto.init
802     codelimit codebase - code-size !
803     namelimit namebase - headers-size !
804 ;
805 auto.init
806
807 : SAVE-FORTH ( $name -- )
808     0                                    \ Entry point
809     headers-ptr @ namebase - 65536 +     \ NameSize
810     headers-size @ MAX
811     here codebase - 131072 +              \ CodeSize
812     code-size @ MAX
813     (save-forth)
814     IF
815         ." SAVE-FORTH failed!" cr abort
816     THEN
817 ;
818
819 : TURNKEY ( $name entry-token-- )
820     0     \ NameSize = 0, names not saved in turnkey dictionary
821     here codebase - 131072 +             \ CodeSize, remember that base is HEX
822     (save-forth)
823     IF
824         ." TURNKEY failed!" cr abort
825     THEN
826 ;
827
828 \ Now that we can load from files, load remainder of dictionary.
829
830 trace-include on
831 \ Turn this OFF if you do not want to see the contents of the stack after each entry.
832 trace-stack off
833
834 include loadp4th.fth
835
836 decimal
837
838 : ;;;; ;  \ Mark end of this file so FILE? can find things in here.
839 FREEZE    \ prevent forgetting below this point
840
841 .( Dictionary compiled, save in "pforth.dic".) cr
842 \ 300000 headers-size !
843 \ 700000 code-size !
844 c" pforth.dic" save-forth