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