Define backward compatible version of WORD
[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
363\ define some useful constants ------------------------------
3641 0= constant FALSE
3650 0= constant TRUE
36632 constant BL
367
368
369\ Store and Fetch relocatable data addresses. ---------------
370: IF.USE->REL ( use -- rel , preserve zero )
371 dup IF use->rel THEN
372;
373: IF.REL->USE ( rel -- use , preserve zero )
374 dup IF rel->use THEN
375;
376
377: A! ( dictionary_address addr -- )
378 >r if.use->rel r> !
379;
380: A@ ( addr -- dictionary_address )
381 @ if.rel->use
382;
383
384: A, ( dictionary_address -- )
385 if.use->rel ,
386;
387
388\ Stack data structure ----------------------------------------
389\ This is a general purpose stack utility used to implement necessary
390\ stacks for the compiler or the user. Not real fast.
391\ These stacks grow up which is different then normal.
392\ cell 0 - stack pointer, offset from pfa of word
393\ cell 1 - limit for range checking
394\ cell 2 - first data location
395
396: :STACK ( #cells -- )
397 CREATE 2 cells , ( offset of first data location )
398 dup , ( limit for range checking, not currently used )
399 cells cell+ allot ( allot an extra cell for safety )
400;
401
402: >STACK ( n stack -- , push onto stack, postincrement )
403 dup @ 2dup cell+ swap ! ( -- n stack offset )
404 + !
405;
406
407: STACK> ( stack -- n , pop , predecrement )
408 dup @ cell- 2dup swap !
409 + @
410;
411
412: STACK@ ( stack -- n , copy )
413 dup @ cell- + @
414;
415
416: STACK.PICK ( index stack -- n , grab Nth from top of stack )
417 dup @ cell- +
418 swap cells - \ offset for index
419 @
420;
421: STACKP ( stack -- ptr , to next empty location on stack )
422 dup @ +
423;
424
425: 0STACKP ( stack -- , clear stack)
426 8 swap !
427;
428
42932 :stack ustack
430ustack 0stackp
431
432\ Define JForth like words.
433: >US ustack >stack ;
434: US> ustack stack> ;
435: US@ ustack stack@ ;
436: 0USP ustack 0stackp ;
437
438
439\ DO LOOP ------------------------------------------------
440
4413 constant do_flag
4424 constant leave_flag
4435 constant ?do_flag
444
445: DO ( -- , loop-back do_flag jump-from ?do_flag )
446 ?comp
447 compile (do)
448 here >us do_flag >us ( for backward branch )
449; immediate
450
451: ?DO ( -- , loop-back do_flag jump-from ?do_flag , on user stack )
452 ?comp
453 ( leave address to set for forward branch )
454 compile (?do)
455 here 0 ,
456 here >us do_flag >us ( for backward branch )
457 >us ( for forward branch ) ?do_flag >us
458; immediate
459
460: LEAVE ( -- addr leave_flag )
461 compile (leave)
462 here 0 , >us
463 leave_flag >us
464; immediate
465
466: LOOP-FORWARD ( -us- jump-from ?do_flag -- )
467 BEGIN
468 us@ leave_flag =
469 us@ ?do_flag =
470 OR
471 WHILE
472 us> leave_flag =
473 IF
474 us> here over - cell+ swap !
475 ELSE
476 us> dup
477 here swap -
478 cell+ swap !
479 THEN
480 REPEAT
481;
482
483: LOOP-BACK ( loop-addr do_flag -us- )
484 us> do_flag ?pairs
485 us> here - here
486 !
487 cell allot
488;
489
490: LOOP ( -- , loop-back do_flag jump-from ?do_flag )
491 compile (loop)
492 loop-forward loop-back
493; immediate
494
495\ : DOTEST 5 0 do 333 . loop 888 . ;
496\ : ?DOTEST0 0 0 ?do 333 . loop 888 . ;
497\ : ?DOTEST1 5 0 ?do 333 . loop 888 . ;
498
499: +LOOP ( -- , loop-back do_flag jump-from ?do_flag )
500 compile (+loop)
501 loop-forward loop-back
502; immediate
503
504: UNLOOP ( loop-sys -r- )
505 r> \ save return pointer
506 rdrop rdrop
507 >r
508;
509
510: RECURSE ( ? -- ? , call the word currently being defined )
511 latest name> compile,
512; immediate
513
514
515
516: SPACE bl emit ;
517: SPACES 512 min 0 max 0 ?DO space LOOP ;
518: 0SP depth 0 ?do drop loop ;
519
520: >NEWLINE ( -- , CR if needed )
521 out @ 0>
522 IF cr
523 THEN
524;
525
526
527\ Support for DEFER --------------------
528: CHECK.DEFER ( xt -- , error if not a deferred word by comparing to type )
529 >code @
530 ['] emit >code @
531 - err_defer ?error
532;
533
534: >is ( xt -- address_of_vector )
535 >code
536 cell +
537;
538
539: (IS) ( xt_do xt_deferred -- )
540 >is !
541;
542
543: IS ( xt <name> -- , act like normal IS )
544 ' \ xt
545 dup check.defer
546 state @
547 IF [compile] literal compile (is)
548 ELSE (is)
549 THEN
550; immediate
551
552: (WHAT'S) ( xt -- xt_do )
553 >is @
554;
555: WHAT'S ( <name> -- xt , what will deferred word call? )
556 ' \ xt
557 dup check.defer
558 state @
559 IF [compile] literal compile (what's)
560 ELSE (what's)
561 THEN
562; immediate
563
564: /STRING ( addr len n -- addr' len' )
565 over min rot over + -rot -
566;
567: PLACE ( addr len to -- , move string )
568 3dup 1+ swap cmove c! drop
569;
570
571: PARSE-WORD ( char -- addr len )
572 >r source tuck >in @ /string r@ skip over swap r> scan
573 >r over - rot r> dup 0<> + - >in !
574;
575: PARSE ( char -- addr len )
576 >r source >in @ /string over swap r> scan
577 >r over - dup r> 0<> - >in +!
578;
579
580: LWORD ( char -- addr )
581 parse-word here place here \ 00002 , use PARSE-WORD
582;
583
584: ASCII ( <char> -- char , state smart )
585 bl parse drop c@
586 state @
587 IF [compile] literal
588 THEN
589; immediate
590
591: CHAR ( <char> -- char , interpret mode )
592 bl parse drop c@
593;
594
595: [CHAR] ( <char> -- char , for compile mode )
596 char [compile] literal
597; immediate
598
6cc29c22
HE
599: TOUPPER ( char -- char' )
600 dup [char] a >=
601 IF
602 dup [char] z <= IF [ char A char a - ] literal + THEN
603 THEN
604;
605
606: UPCASE ( c-addr u -- )
607 over + swap ?do
608 i c@ toupper i c!
609 loop
610;
611
612create WORD-SAVE-AREA 257 allot
613
614\ This version performs case-conversion for backward compatibility.
615: WORD ( char -- addr )
616 parse-word
617 word-save-area place
618 word-save-area count upcase
619 word-save-area
620;
621
8e9db35f
PB
622: $TYPE ( $string -- )
623 count type
624;
625
626: 'word ( -- addr ) here ;
627
628: EVEN ( addr -- addr' ) dup 1 and + ;
629
630: (C") ( -- $addr , some Forths return addr AND count, OBSOLETE?)
631 r> dup count + aligned >r
632;
633: (S") ( -- c-addr cnt )
634 r> count 2dup + aligned >r
635;
636
637: (.") ( -- , type following string )
638 r> count 2dup + aligned >r type
639;
640
641: ", ( adr len -- , place string into dictionary )
642 tuck 'word place 1+ allot align
643;
644: ," ( -- )
645 [char] " parse ",
646;
647
648: .( ( <string> -- , type string delimited by parentheses )
649 [CHAR] ) PARSE TYPE
650; IMMEDIATE
651
652: ." ( <string> -- , type string )
653 state @
654 IF compile (.") ,"
655 ELSE [char] " parse type
656 THEN
657; immediate
658
659
660: .' ( <string> -- , type string delimited by single quote )
661 state @
662 IF compile (.") [char] ' parse ",
663 ELSE [char] ' parse type
664 THEN
665; immediate
666
667: C" ( <string> -- addr , return string address, ANSI )
668 state @
669 IF compile (c") ,"
670 ELSE [char] " parse pad place pad
671 THEN
672; immediate
673
674: S" ( <string> -- , -- addr , return string address, ANSI )
675 state @
676 IF compile (s") ,"
677 ELSE [char] " parse pad place pad count
678 THEN
679; immediate
680
681: " ( <string> -- , -- addr , return string address )
682 [compile] C"
683; immediate
684: P" ( <string> -- , -- addr , return string address )
685 [compile] C"
686; immediate
687
688: "" ( <string> -- addr )
689 state @
690 IF
691 compile (C")
692 bl parse-word ",
693 ELSE
694 bl parse-word pad place pad
695 THEN
696; immediate
697
698: SLITERAL ( addr cnt -- , compile string )
699 compile (S")
700 ",
701; IMMEDIATE
702
703: $APPEND ( addr count $1 -- , append text to $1 )
704 over >r
705 dup >r
706 count + ( -- a2 c2 end1 )
707 swap cmove
708 r> dup c@ ( a1 c1 )
709 r> + ( -- a1 totalcount )
710 swap c!
711;
712
713
714\ ANSI word to replace [COMPILE] and COMPILE ----------------
715: POSTPONE ( <name> -- )
716 bl word find
717 dup 0=
718 IF
719 ." Postpone could not find " count type cr abort
720 ELSE
721 0>
722 IF compile, \ immediate
723 ELSE (compile) \ normal
724 THEN
725 THEN
726; immediate
727
728\ -----------------------------------------------------------------
729\ Auto Initialization
730: AUTO.INIT ( -- )
731\ Kernel finds AUTO.INIT and executes it after loading dictionary.
732\ ." Begin AUTO.INIT ------" cr
733;
734: AUTO.TERM ( -- )
735\ Kernel finds AUTO.TERM and executes it on bye.
736\ ." End AUTO.TERM ------" cr
737;
738
739\ -------------- INCLUDE ------------------------------------------
740variable TRACE-INCLUDE
741
742: INCLUDE.MARK.START ( $filename -- , mark start of include for FILE?)
743 " ::::" pad $MOVE
744 count pad $APPEND
745 pad ['] noop (:)
746;
747
748: INCLUDE.MARK.END ( -- , mark end of include )
749 " ;;;;" ['] noop (:)
750;
751
752: $INCLUDE ( $filename -- )
753\ Print messages.
754 trace-include @
755 IF
756 >newline ." Include " dup count type cr
757 THEN
758 here >r
759 dup
760 count r/o open-file
761 IF ( -- $filename bad-fid )
762 drop ." Could not find file " $type cr abort
763 ELSE ( -- $filename good-fid )
764 swap include.mark.start
765 depth >r
766 include-file \ will also close the file
767 depth 1+ r> -
768 IF
769 ." Warning: stack depth changed during include!" cr
770 .s cr
771 0sp
772 THEN
773 include.mark.end
774 THEN
775 trace-include @
776 IF
777 ." include added " here r@ - . ." bytes,"
778 codelimit here - . ." left." cr
779 THEN
780 rdrop
781;
782
783create INCLUDE-SAVE-NAME 128 allot
784: INCLUDE ( <fname> -- )
785 BL lword
786 dup include-save-name $move \ save for RI
787 $include
788;
789
790: RI ( -- , ReInclude previous file as a convenience )
791 include-save-name $include
792;
793
794: INCLUDE? ( <word> <file> -- , load file if word not defined )
795 bl word find
796 IF drop bl word drop ( eat word from source )
797 ELSE drop include
798 THEN
799;
800
801\ desired sizes for dictionary loaded after SAVE-FORTH
802variable HEADERS-SIZE
803variable CODE-SIZE
804
805: AUTO.INIT
806 auto.init
807 codelimit codebase - code-size !
808 namelimit namebase - headers-size !
809;
810auto.init
811
812: SAVE-FORTH ( $name -- )
813 0 \ Entry point
814 headers-ptr @ namebase - 65536 + \ NameSize
815 headers-size @ MAX
816 here codebase - 131072 + \ CodeSize
817 code-size @ MAX
818 (save-forth)
819 IF
820 ." SAVE-FORTH failed!" cr abort
821 THEN
822;
823
824: TURNKEY ( $name entry-token-- )
825 0 \ NameSize = 0, names not saved in turnkey dictionary
826 here codebase - 131072 + \ CodeSize, remember that base is HEX
827 (save-forth)
828 IF
829 ." TURNKEY failed!" cr abort
830 THEN
831;
832
833\ Now that we can load from files, load remainder of dictionary.
834
835trace-include on
836\ Turn this OFF if you do not want to see the contents of the stack after each entry.
837trace-stack off
838
839include loadp4th.fth
840
841decimal
842
843: ;;;; ; \ Mark end of this file so FILE? can find things in here.
844FREEZE \ prevent forgetting below this point
845
846.( Dictionary compiled, save in "pforth.dic".) cr
847c" pforth.dic" save-forth