File:
[gforth] /
gforth /
Attic /
kernal.fs
Revision
1.54:
download - view:
text,
annotated -
select for diffs
Wed Apr 17 16:39:41 1996 UTC (26 years, 11 months ago) by
anton
Branches:
MAIN
CVS tags:
HEAD
changed image file format:
now every stack has its own size spec in the image
size changes through the command line are passed to the image (and
saved with savesystem)
added a checksum to protect against incompatible binary/image combinations
(e.g., direct threaded binary with indirect threaded image)
the preamble specifies an interpreter and is propagated by save-system
1: \ KERNAL.FS GForth kernal 17dec92py
2:
3: \ Copyright (C) 1995 Free Software Foundation, Inc.
4:
5: \ This file is part of Gforth.
6:
7: \ Gforth is free software; you can redistribute it and/or
8: \ modify it under the terms of the GNU General Public License
9: \ as published by the Free Software Foundation; either version 2
10: \ of the License, or (at your option) any later version.
11:
12: \ This program is distributed in the hope that it will be useful,
13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15: \ GNU General Public License for more details.
16:
17: \ You should have received a copy of the GNU General Public License
18: \ along with this program; if not, write to the Free Software
19: \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
20:
21: \ Idea and implementation: Bernd Paysan (py)
22:
23: \ Log: ', '- usw. durch [char] ... ersetzt
24: \ man sollte die unterschiedlichen zahlensysteme
25: \ mit $ und & zumindest im interpreter weglassen
26: \ schon erledigt!
27: \ 11may93jaw
28: \ name> 0= nicht vorhanden 17may93jaw
29: \ nfa can be lfa or nfa!
30: \ find splited into find and (find)
31: \ (find) for later use 17may93jaw
32: \ search replaced by lookup because
33: \ it is a word of the string wordset
34: \ 20may93jaw
35: \ postpone added immediate 21may93jaw
36: \ to added immediate 07jun93jaw
37: \ cfa, header put "here lastcfa !" in
38: \ cfa, this is more logical
39: \ and noname: works wothout
40: \ extra "here lastcfa !" 08jun93jaw
41: \ (parse-white) thrown out
42: \ refill added outer trick
43: \ to show there is something
44: \ going on 09jun93jaw
45: \ leave ?leave somebody forgot UNLOOP!!! 09jun93jaw
46: \ leave ?leave unloop thrown out
47: \ unloop after loop is used 10jun93jaw
48:
49: HEX
50:
51: \ labels for some code addresses
52:
53: : docon: ( -- addr ) \ gforth
54: \ the code address of a @code{CONSTANT}
55: ['] bl >code-address ;
56:
57: : docol: ( -- addr ) \ gforth
58: \ the code address of a colon definition
59: ['] docon: >code-address ;
60:
61: : dovar: ( -- addr ) \ gforth
62: \ the code address of a @code{CREATE}d word
63: ['] udp >code-address ;
64:
65: : douser: ( -- addr ) \ gforth
66: \ the code address of a @code{USER} variable
67: ['] s0 >code-address ;
68:
69: : dodefer: ( -- addr ) \ gforth
70: \ the code address of a @code{defer}ed word
71: ['] source >code-address ;
72:
73: : dofield: ( -- addr ) \ gforth
74: \ the code address of a @code{field}
75: ['] reveal-method >code-address ;
76:
77: \ Bit string manipulation 06oct92py
78:
79: \ Create bits 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
80: \ DOES> ( n -- ) + c@ ;
81:
82: \ : >bit ( addr n -- c-addr mask ) 8 /mod rot + swap bits ;
83: \ : +bit ( addr n -- ) >bit over c@ or swap c! ;
84:
85: \ : relinfo ( -- addr ) forthstart dup @ + !!bug!! ;
86: \ : >rel ( addr -- n ) forthstart - ;
87: \ : relon ( addr -- ) relinfo swap >rel cell / +bit ;
88:
89: \ here allot , c, A, 17dec92py
90:
91: : dp ( -- addr ) \ gforth
92: dpp @ ;
93: : here ( -- here ) \ core
94: dp @ ;
95: : allot ( n -- ) \ core
96: dp +! ;
97: : c, ( c -- ) \ core
98: here 1 chars allot c! ;
99: : , ( x -- ) \ core
100: here cell allot ! ;
101: : 2, ( w1 w2 -- ) \ gforth
102: here 2 cells allot 2! ;
103:
104: \ : aligned ( addr -- addr' ) \ core
105: \ [ cell 1- ] Literal + [ -1 cells ] Literal and ;
106: : align ( -- ) \ core
107: here dup aligned swap ?DO bl c, LOOP ;
108:
109: \ : faligned ( addr -- f-addr ) \ float
110: \ [ 1 floats 1- ] Literal + [ -1 floats ] Literal and ;
111:
112: : falign ( -- ) \ float
113: here dup faligned swap
114: ?DO
115: bl c,
116: LOOP ;
117:
118: \ !! this is machine-dependent, but works on all but the strangest machines
119: ' faligned Alias maxaligned ( addr1 -- addr2 ) \ gforth
120: ' falign Alias maxalign ( -- ) \ gforth
121:
122: \ !! machine-dependent and won't work if "0 >body" <> "0 >body maxaligned"
123: ' maxaligned Alias cfaligned ( addr1 -- addr2 ) \ gforth
124: \ the code field is aligned if its body is maxaligned
125: ' maxalign Alias cfalign ( -- ) \ gforth
126:
127: : chars ( n1 -- n2 ) \ core
128: ; immediate
129:
130:
131: \ : A! ( addr1 addr2 -- ) \ gforth
132: \ dup relon ! ;
133: \ : A, ( addr -- ) \ gforth
134: \ here cell allot A! ;
135: ' ! alias A! ( addr1 addr2 -- ) \ gforth
136: ' , alias A, ( addr -- ) \ gforth
137:
138:
139: \ on off 23feb93py
140:
141: : on ( addr -- ) \ gforth
142: true swap ! ;
143: : off ( addr -- ) \ gforth
144: false swap ! ;
145:
146: \ name> found 17dec92py
147:
148: : (name>) ( nfa+cell -- cfa )
149: 1 cells - name>string + cfaligned ;
150: : name> ( nfa -- cfa ) \ gforth
151: cell+
152: dup (name>) swap c@ $80 and 0= IF @ THEN ;
153:
154: : found ( nfa -- cfa n ) \ gforth
155: cell+
156: dup c@ >r (name>) r@ $80 and 0= IF @ THEN
157: -1 r@ $40 and IF 1- THEN
158: r> $20 and IF negate THEN ;
159:
160: \ (find) 17dec92py
161:
162: \ : (find) ( addr count nfa1 -- nfa2 / false )
163: \ BEGIN dup WHILE dup >r
164: \ name>string dup >r 2over r> =
165: \ IF -text 0= IF 2drop r> EXIT THEN
166: \ ELSE 2drop drop THEN r> @
167: \ REPEAT nip nip ;
168:
169: \ place bounds 13feb93py
170:
171: : place ( addr len to -- ) \ gforth
172: over >r rot over 1+ r> move c! ;
173: : bounds ( beg count -- end beg ) \ gforth
174: over + swap ;
175:
176: \ input stream primitives 23feb93py
177:
178: : tib ( -- c-addr ) \ core-ext
179: \ obsolescent
180: >tib @ ;
181: Defer source ( -- addr count ) \ core
182: \ used by dodefer:, must be defer
183: : (source) ( -- addr count )
184: tib #tib @ ;
185: ' (source) IS source
186:
187: \ (word) 22feb93py
188:
189: : scan ( addr1 n1 char -- addr2 n2 ) \ gforth
190: \ skip all characters not equal to char
191: >r
192: BEGIN
193: dup
194: WHILE
195: over c@ r@ <>
196: WHILE
197: 1 /string
198: REPEAT THEN
199: rdrop ;
200: : skip ( addr1 n1 char -- addr2 n2 ) \ gforth
201: \ skip all characters equal to char
202: >r
203: BEGIN
204: dup
205: WHILE
206: over c@ r@ =
207: WHILE
208: 1 /string
209: REPEAT THEN
210: rdrop ;
211:
212: : (word) ( addr1 n1 char -- addr2 n2 )
213: dup >r skip 2dup r> scan nip - ;
214:
215: \ (word) should fold white spaces
216: \ this is what (parse-white) does
217:
218: \ word parse 23feb93py
219:
220: : parse-word ( char -- addr len ) \ gforth
221: source 2dup >r >r >in @ over min /string
222: rot dup bl = IF drop (parse-white) ELSE (word) THEN
223: 2dup + r> - 1+ r> min >in ! ;
224: : word ( char -- addr ) \ core
225: parse-word here place bl here count + c! here ;
226:
227: : parse ( char -- addr len ) \ core-ext
228: >r source >in @ over min /string over swap r> scan >r
229: over - dup r> IF 1+ THEN >in +! ;
230:
231: \ name 13feb93py
232:
233: : capitalize ( addr len -- addr len ) \ gforth
234: 2dup chars chars bounds
235: ?DO I c@ toupper I c! 1 chars +LOOP ;
236: : (name) ( -- c-addr count )
237: source 2dup >r >r >in @ /string (parse-white)
238: 2dup + r> - 1+ r> min >in ! ;
239: \ name count ;
240:
241: : name-too-short? ( c-addr u -- c-addr u )
242: dup 0= -&16 and throw ;
243:
244: : name-too-long? ( c-addr u -- c-addr u )
245: dup $1F u> -&19 and throw ;
246:
247: \ Literal 17dec92py
248:
249: : Literal ( compilation n -- ; run-time -- n ) \ core
250: state @ IF postpone lit , THEN ; immediate
251: : ALiteral ( compilation addr -- ; run-time -- addr ) \ gforth
252: state @ IF postpone lit A, THEN ;
253: immediate
254:
255: : char ( 'char' -- n ) \ core
256: bl word char+ c@ ;
257: : [char] ( compilation 'char' -- ; run-time -- n )
258: char postpone Literal ; immediate
259: ' [char] Alias Ascii immediate
260:
261: : (compile) ( -- ) \ gforth
262: r> dup cell+ >r @ compile, ;
263: : postpone ( "name" -- ) \ core
264: name sfind dup 0= abort" Can't compile "
265: 0> IF compile, ELSE postpone (compile) A, THEN ;
266: immediate restrict
267:
268: \ Use (compile) for the old behavior of compile!
269:
270: \ digit? 17dec92py
271:
272: : digit? ( char -- digit true/ false ) \ gforth
273: base @ $100 =
274: IF
275: true EXIT
276: THEN
277: toupper [char] 0 - dup 9 u> IF
278: [ 'A '9 1 + - ] literal -
279: dup 9 u<= IF
280: drop false EXIT
281: THEN
282: THEN
283: dup base @ u>= IF
284: drop false EXIT
285: THEN
286: true ;
287:
288: : accumulate ( +d0 addr digit - +d1 addr )
289: swap >r swap base @ um* drop rot base @ um* d+ r> ;
290:
291: : >number ( d addr count -- d addr count ) \ core
292: 0
293: ?DO
294: count digit?
295: WHILE
296: accumulate
297: LOOP
298: 0
299: ELSE
300: 1- I' I -
301: UNLOOP
302: THEN ;
303:
304: \ number? number 23feb93py
305:
306: Create bases 10 , 2 , A , 100 ,
307: \ 16 2 10 Zeichen
308: \ !! this saving and restoring base is an abomination! - anton
309: : getbase ( addr u -- addr' u' )
310: over c@ [char] $ - dup 4 u<
311: IF
312: cells bases + @ base ! 1 /string
313: ELSE
314: drop
315: THEN ;
316: : s>number ( addr len -- d )
317: base @ >r dpl on
318: over c@ '- = dup >r
319: IF
320: 1 /string
321: THEN
322: getbase dpl on 0 0 2swap
323: BEGIN
324: dup >r >number dup
325: WHILE
326: dup r> -
327: WHILE
328: dup dpl ! over c@ [char] . =
329: WHILE
330: 1 /string
331: REPEAT THEN
332: 2drop rdrop dpl off
333: ELSE
334: 2drop rdrop r>
335: IF
336: dnegate
337: THEN
338: THEN
339: r> base ! ;
340:
341: : snumber? ( c-addr u -- 0 / n -1 / d 0> )
342: s>number dpl @ 0=
343: IF
344: 2drop false EXIT
345: THEN
346: dpl @ dup 0> 0= IF
347: nip
348: THEN ;
349: : number? ( string -- string 0 / n -1 / d 0> )
350: dup >r count snumber? dup if
351: rdrop
352: else
353: r> swap
354: then ;
355: : s>d ( n -- d ) \ core s-to-d
356: dup 0< ;
357: : number ( string -- d )
358: number? ?dup 0= abort" ?" 0<
359: IF
360: s>d
361: THEN ;
362:
363: \ space spaces ud/mod 21mar93py
364: decimal
365: Create spaces ( u -- ) \ core
366: bl 80 times \ times from target compiler! 11may93jaw
367: DOES> ( u -- )
368: swap
369: 0 max 0 ?DO I' I - &80 min 2dup type +LOOP drop ;
370: Create backspaces
371: 08 80 times \ times from target compiler! 11may93jaw
372: DOES> ( u -- )
373: swap
374: 0 max 0 ?DO I' I - &80 min 2dup type +LOOP drop ;
375: hex
376: : space ( -- ) \ core
377: 1 spaces ;
378:
379: : ud/mod ( ud1 u2 -- urem udquot ) \ gforth
380: >r 0 r@ um/mod r> swap >r
381: um/mod r> ;
382:
383: : pad ( -- addr ) \ core-ext
384: here [ $20 8 2* cells + 2 + cell+ ] Literal + aligned ;
385:
386: \ hold <# #> sign # #s 25jan92py
387:
388: : hold ( char -- ) \ core
389: pad cell - -1 chars over +! @ c! ;
390:
391: : <# ( -- ) \ core less-number-sign
392: pad cell - dup ! ;
393:
394: : #> ( xd -- addr u ) \ core number-sign-greater
395: 2drop pad cell - dup @ tuck - ;
396:
397: : sign ( n -- ) \ core
398: 0< IF [char] - hold THEN ;
399:
400: : # ( ud1 -- ud2 ) \ core number-sign
401: base @ 2 max ud/mod rot 9 over <
402: IF
403: [ char A char 9 - 1- ] Literal +
404: THEN
405: [char] 0 + hold ;
406:
407: : #s ( +d -- 0 0 ) \ core number-sign-s
408: BEGIN
409: # 2dup d0=
410: UNTIL ;
411:
412: \ print numbers 07jun92py
413:
414: : d.r ( d n -- ) \ double d-dot-r
415: >r tuck dabs <# #s rot sign #>
416: r> over - spaces type ;
417:
418: : ud.r ( ud n -- ) \ gforth u-d-dot-r
419: >r <# #s #> r> over - spaces type ;
420:
421: : .r ( n1 n2 -- ) \ core-ext dot-r
422: >r s>d r> d.r ;
423: : u.r ( u n -- ) \ core-ext u-dot-r
424: 0 swap ud.r ;
425:
426: : d. ( d -- ) \ double d-dot
427: 0 d.r space ;
428: : ud. ( ud -- ) \ gforth u-d-dot
429: 0 ud.r space ;
430:
431: : . ( n -- ) \ core dot
432: s>d d. ;
433: : u. ( u -- ) \ core u-dot
434: 0 ud. ;
435:
436: \ catch throw 23feb93py
437: \ bounce 08jun93jaw
438:
439: \ !! allow the user to add rollback actions anton
440: \ !! use a separate exception stack? anton
441:
442: : lp@ ( -- addr ) \ gforth l-p-fetch
443: laddr# [ 0 , ] ;
444:
445: : catch ( x1 .. xn xt -- y1 .. ym 0 / z1 .. zn error ) \ exception
446: >r sp@ r> swap >r \ don't count xt! jaw
447: fp@ >r
448: lp@ >r
449: handler @ >r
450: rp@ handler !
451: execute
452: r> handler ! rdrop rdrop rdrop 0 ;
453:
454: : throw ( y1 .. ym error/0 -- y1 .. ym / z1 .. zn error ) \ exception
455: ?DUP IF
456: [ here 9 cells ! ]
457: handler @ rp!
458: r> handler !
459: r> lp!
460: r> fp!
461: r> swap >r sp! r>
462: THEN ;
463:
464: \ Bouncing is very fine,
465: \ programming without wasting time... jaw
466: : bounce ( y1 .. ym error/0 -- y1 .. ym error / y1 .. ym ) \ gforth
467: \ a throw without data or fp stack restauration
468: ?DUP IF
469: handler @ rp!
470: r> handler !
471: r> lp!
472: rdrop
473: rdrop
474: THEN ;
475:
476: \ ?stack 23feb93py
477:
478: : ?stack ( ?? -- ?? ) \ gforth
479: sp@ s0 @ > IF -4 throw THEN
480: fp@ f0 @ > IF -&45 throw THEN ;
481: \ ?stack should be code -- it touches an empty stack!
482:
483: \ interpret 10mar92py
484:
485: Defer parser
486: Defer name ( -- c-addr count ) \ gforth
487: \ get the next word from the input buffer
488: ' (name) IS name
489: Defer notfound ( c-addr count -- )
490:
491: : no.extensions ( addr u -- )
492: 2drop -&13 bounce ;
493: ' no.extensions IS notfound
494:
495: : interpret ( ?? -- ?? ) \ gforth
496: \ interpret/compile the (rest of the) input buffer
497: BEGIN
498: ?stack name dup
499: WHILE
500: parser
501: REPEAT
502: 2drop ;
503:
504: \ interpreter compiler 30apr92py
505:
506: : interpreter ( c-addr u -- ) \ gforth
507: \ interpretation semantics for the name/number c-addr u
508: 2dup sfind dup
509: IF
510: 1 and
511: IF \ not restricted to compile state?
512: nip nip execute EXIT
513: THEN
514: -&14 throw
515: THEN
516: drop
517: 2dup 2>r snumber?
518: IF
519: 2rdrop
520: ELSE
521: 2r> notfound
522: THEN ;
523:
524: ' interpreter IS parser
525:
526: : compiler ( c-addr u -- ) \ gforth
527: \ compilation semantics for the name/number c-addr u
528: 2dup sfind dup
529: IF
530: 0>
531: IF
532: nip nip execute EXIT
533: THEN
534: compile, 2drop EXIT
535: THEN
536: drop
537: 2dup snumber? dup
538: IF
539: 0>
540: IF
541: swap postpone Literal
542: THEN
543: postpone Literal
544: 2drop
545: ELSE
546: drop notfound
547: THEN ;
548:
549: : [ ( -- ) \ core left-bracket
550: ['] interpreter IS parser state off ; immediate
551: : ] ( -- ) \ core right-bracket
552: ['] compiler IS parser state on ;
553:
554: \ locals stuff needed for control structures
555:
556: : compile-lp+! ( n -- ) \ gforth compile-l-p-plus-store
557: dup negate locals-size +!
558: 0 over = if
559: else -1 cells over = if postpone lp-
560: else 1 floats over = if postpone lp+
561: else 2 floats over = if postpone lp+2
562: else postpone lp+!# dup ,
563: then then then then drop ;
564:
565: : adjust-locals-size ( n -- ) \ gforth
566: \ sets locals-size to n and generates an appropriate lp+!
567: locals-size @ swap - compile-lp+! ;
568:
569:
570: here 0 , \ just a dummy, the real value of locals-list is patched into it in glocals.fs
571: AConstant locals-list \ acts like a variable that contains
572: \ a linear list of locals names
573:
574:
575: variable dead-code \ true if normal code at "here" would be dead
576: variable backedge-locals
577: \ contains the locals list that BEGIN will assume to be live on
578: \ the back edge if the BEGIN is unreachable from above. Set by
579: \ ASSUME-LIVE, reset by UNREACHABLE.
580:
581: : UNREACHABLE ( -- ) \ gforth
582: \ declares the current point of execution as unreachable
583: dead-code on
584: 0 backedge-locals ! ; immediate
585:
586: : ASSUME-LIVE ( orig -- orig ) \ gforth
587: \ used immediateliy before a BEGIN that is not reachable from
588: \ above. causes the BEGIN to assume that the same locals are live
589: \ as at the orig point
590: dup orig?
591: 2 pick backedge-locals ! ; immediate
592:
593: \ locals list operations
594:
595: : common-list ( list1 list2 -- list3 ) \ gforth-internal
596: \ list1 and list2 are lists, where the heads are at higher addresses than
597: \ the tail. list3 is the largest sublist of both lists.
598: begin
599: 2dup u<>
600: while
601: 2dup u>
602: if
603: swap
604: then
605: @
606: repeat
607: drop ;
608:
609: : sub-list? ( list1 list2 -- f ) \ gforth-internal
610: \ true iff list1 is a sublist of list2
611: begin
612: 2dup u<
613: while
614: @
615: repeat
616: = ;
617:
618: : list-size ( list -- u ) \ gforth-internal
619: \ size of the locals frame represented by list
620: 0 ( list n )
621: begin
622: over 0<>
623: while
624: over
625: name> >body @ max
626: swap @ swap ( get next )
627: repeat
628: faligned nip ;
629:
630: : set-locals-size-list ( list -- )
631: dup locals-list !
632: list-size locals-size ! ;
633:
634: : check-begin ( list -- )
635: \ warn if list is not a sublist of locals-list
636: locals-list @ sub-list? 0= if
637: \ !! print current position
638: ." compiler was overly optimistic about locals at a BEGIN" cr
639: \ !! print assumption and reality
640: then ;
641:
642: \ Control Flow Stack
643: \ orig, etc. have the following structure:
644: \ type ( defstart, live-orig, dead-orig, dest, do-dest, scopestart) ( TOS )
645: \ address (of the branch or the instruction to be branched to) (second)
646: \ locals-list (valid at address) (third)
647:
648: \ types
649: 0 constant defstart
650: 1 constant live-orig
651: 2 constant dead-orig
652: 3 constant dest \ the loopback branch is always assumed live
653: 4 constant do-dest
654: 5 constant scopestart
655:
656: : def? ( n -- )
657: defstart <> abort" unstructured " ;
658:
659: : orig? ( n -- )
660: dup live-orig <> swap dead-orig <> and abort" expected orig " ;
661:
662: : dest? ( n -- )
663: dest <> abort" expected dest " ;
664:
665: : do-dest? ( n -- )
666: do-dest <> abort" expected do-dest " ;
667:
668: : scope? ( n -- )
669: scopestart <> abort" expected scope " ;
670:
671: : non-orig? ( n -- )
672: dest scopestart 1+ within 0= abort" expected dest, do-dest or scope" ;
673:
674: : cs-item? ( n -- )
675: live-orig scopestart 1+ within 0= abort" expected control flow stack item" ;
676:
677: 3 constant cs-item-size
678:
679: : CS-PICK ( ... u -- ... destu ) \ tools-ext
680: 1+ cs-item-size * 1- >r
681: r@ pick r@ pick r@ pick
682: rdrop
683: dup non-orig? ;
684:
685: : CS-ROLL ( destu/origu .. dest0/orig0 u -- .. dest0/orig0 destu/origu ) \ tools-ext
686: 1+ cs-item-size * 1- >r
687: r@ roll r@ roll r@ roll
688: rdrop
689: dup cs-item? ;
690:
691: : cs-push-part ( -- list addr )
692: locals-list @ here ;
693:
694: : cs-push-orig ( -- orig )
695: cs-push-part dead-code @
696: if
697: dead-orig
698: else
699: live-orig
700: then ;
701:
702: \ Structural Conditionals 12dec92py
703:
704: : ?struc ( flag -- ) abort" unstructured " ;
705: : sys? ( sys -- ) dup 0= ?struc ;
706: : >mark ( -- orig )
707: cs-push-orig 0 , ;
708: : >resolve ( addr -- ) here over - swap ! ;
709: : <resolve ( addr -- ) here - , ;
710:
711: : BUT
712: 1 cs-roll ; immediate restrict
713: : YET
714: 0 cs-pick ; immediate restrict
715:
716: \ Structural Conditionals 12dec92py
717:
718: : AHEAD ( compilation -- orig ; run-time -- ) \ tools-ext
719: POSTPONE branch >mark POSTPONE unreachable ; immediate restrict
720:
721: : IF ( compilation -- orig ; run-time f -- ) \ core
722: POSTPONE ?branch >mark ; immediate restrict
723:
724: : ?DUP-IF ( compilation -- orig ; run-time n -- n| ) \ gforth question-dupe-if
725: \ This is the preferred alternative to the idiom "?DUP IF", since it can be
726: \ better handled by tools like stack checkers. Besides, it's faster.
727: POSTPONE ?dup-?branch >mark ; immediate restrict
728:
729: : ?DUP-0=-IF ( compilation -- orig ; run-time n -- n| ) \ gforth question-dupe-zero-equals-if
730: POSTPONE ?dup-0=-?branch >mark ; immediate restrict
731:
732: : THEN ( compilation orig -- ; run-time -- ) \ core
733: dup orig?
734: dead-orig =
735: if
736: >resolve drop
737: else
738: dead-code @
739: if
740: >resolve set-locals-size-list dead-code off
741: else \ both live
742: over list-size adjust-locals-size
743: >resolve
744: locals-list @ common-list dup list-size adjust-locals-size
745: locals-list !
746: then
747: then ; immediate restrict
748:
749: ' THEN alias ENDIF ( compilation orig -- ; run-time -- ) \ gforth
750: immediate restrict
751: \ Same as "THEN". This is what you use if your program will be seen by
752: \ people who have not been brought up with Forth (or who have been
753: \ brought up with fig-Forth).
754:
755: : ELSE ( compilation orig1 -- orig2 ; run-time f -- ) \ core
756: POSTPONE ahead
757: 1 cs-roll
758: POSTPONE then ; immediate restrict
759:
760:
761: : BEGIN ( compilation -- dest ; run-time -- ) \ core
762: dead-code @ if
763: \ set up an assumption of the locals visible here. if the
764: \ users want something to be visible, they have to declare
765: \ that using ASSUME-LIVE
766: backedge-locals @ set-locals-size-list
767: then
768: cs-push-part dest
769: dead-code off ; immediate restrict
770:
771: \ AGAIN (the current control flow joins another, earlier one):
772: \ If the dest-locals-list is not a subset of the current locals-list,
773: \ issue a warning (see below). The following code is generated:
774: \ lp+!# (current-local-size - dest-locals-size)
775: \ branch <begin>
776: : AGAIN ( compilation dest -- ; run-time -- ) \ core-ext
777: dest?
778: over list-size adjust-locals-size
779: POSTPONE branch
780: <resolve
781: check-begin
782: POSTPONE unreachable ; immediate restrict
783:
784: \ UNTIL (the current control flow may join an earlier one or continue):
785: \ Similar to AGAIN. The new locals-list and locals-size are the current
786: \ ones. The following code is generated:
787: \ ?branch-lp+!# <begin> (current-local-size - dest-locals-size)
788: : until-like ( list addr xt1 xt2 -- )
789: \ list and addr are a fragment of a cs-item
790: \ xt1 is the conditional branch without lp adjustment, xt2 is with
791: >r >r
792: locals-size @ 2 pick list-size - dup if ( list dest-addr adjustment )
793: r> drop r> compile,
794: swap <resolve ( list adjustment ) ,
795: else ( list dest-addr adjustment )
796: drop
797: r> compile, <resolve
798: r> drop
799: then ( list )
800: check-begin ;
801:
802: : UNTIL ( compilation dest -- ; run-time f -- ) \ core
803: dest? ['] ?branch ['] ?branch-lp+!# until-like ; immediate restrict
804:
805: : WHILE ( compilation dest -- orig dest ; run-time f -- ) \ core
806: POSTPONE if
807: 1 cs-roll ; immediate restrict
808:
809: : REPEAT ( compilation orig dest -- ; run-time -- ) \ core
810: POSTPONE again
811: POSTPONE then ; immediate restrict
812:
813:
814: \ counted loops
815:
816: \ leave poses a little problem here
817: \ we have to store more than just the address of the branch, so the
818: \ traditional linked list approach is no longer viable.
819: \ This is solved by storing the information about the leavings in a
820: \ special stack.
821:
822: \ !! remove the fixed size limit. 'Tis not hard.
823: 20 constant leave-stack-size
824: create leave-stack 60 cells allot
825: Avariable leave-sp leave-stack 3 cells + leave-sp !
826:
827: : clear-leave-stack ( -- )
828: leave-stack leave-sp ! ;
829:
830: \ : leave-empty? ( -- f )
831: \ leave-sp @ leave-stack = ;
832:
833: : >leave ( orig -- )
834: \ push on leave-stack
835: leave-sp @
836: dup [ leave-stack 60 cells + ] Aliteral
837: >= abort" leave-stack full"
838: tuck ! cell+
839: tuck ! cell+
840: tuck ! cell+
841: leave-sp ! ;
842:
843: : leave> ( -- orig )
844: \ pop from leave-stack
845: leave-sp @
846: dup leave-stack <= IF
847: drop 0 0 0 EXIT THEN
848: cell - dup @ swap
849: cell - dup @ swap
850: cell - dup @ swap
851: leave-sp ! ;
852:
853: : DONE ( compilation orig -- ; run-time -- ) \ gforth
854: \ !! the original done had ( addr -- )
855: drop >r drop
856: begin
857: leave>
858: over r@ u>=
859: while
860: POSTPONE then
861: repeat
862: >leave rdrop ; immediate restrict
863:
864: : LEAVE ( compilation -- ; run-time loop-sys -- ) \ core
865: POSTPONE ahead
866: >leave ; immediate restrict
867:
868: : ?LEAVE ( compilation -- ; run-time f | f loop-sys -- ) \ gforth question-leave
869: POSTPONE 0= POSTPONE if
870: >leave ; immediate restrict
871:
872: : DO ( compilation -- do-sys ; run-time w1 w2 -- loop-sys ) \ core
873: POSTPONE (do)
874: POSTPONE begin drop do-dest
875: ( 0 0 0 >leave ) ; immediate restrict
876:
877: : ?do-like ( -- do-sys )
878: ( 0 0 0 >leave )
879: >mark >leave
880: POSTPONE begin drop do-dest ;
881:
882: : ?DO ( compilation -- do-sys ; run-time w1 w2 -- | loop-sys ) \ core-ext question-do
883: POSTPONE (?do) ?do-like ; immediate restrict
884:
885: : +DO ( compilation -- do-sys ; run-time n1 n2 -- | loop-sys ) \ gforth plus-do
886: POSTPONE (+do) ?do-like ; immediate restrict
887:
888: : U+DO ( compilation -- do-sys ; run-time u1 u2 -- | loop-sys ) \ gforth u-plus-do
889: POSTPONE (u+do) ?do-like ; immediate restrict
890:
891: : -DO ( compilation -- do-sys ; run-time n1 n2 -- | loop-sys ) \ gforth minus-do
892: POSTPONE (-do) ?do-like ; immediate restrict
893:
894: : U-DO ( compilation -- do-sys ; run-time u1 u2 -- | loop-sys ) \ gforth u-minus-do
895: POSTPONE (u-do) ?do-like ; immediate restrict
896:
897: : FOR ( compilation -- do-sys ; run-time u -- loop-sys ) \ gforth
898: POSTPONE (for)
899: POSTPONE begin drop do-dest
900: ( 0 0 0 >leave ) ; immediate restrict
901:
902: \ LOOP etc. are just like UNTIL
903:
904: : loop-like ( do-sys xt1 xt2 -- )
905: >r >r 0 cs-pick swap cell - swap 1 cs-roll r> r> rot do-dest?
906: until-like POSTPONE done POSTPONE unloop ;
907:
908: : LOOP ( compilation do-sys -- ; run-time loop-sys1 -- | loop-sys2 ) \ core
909: ['] (loop) ['] (loop)-lp+!# loop-like ; immediate restrict
910:
911: : +LOOP ( compilation do-sys -- ; run-time loop-sys1 n -- | loop-sys2 ) \ core plus-loop
912: ['] (+loop) ['] (+loop)-lp+!# loop-like ; immediate restrict
913:
914: \ !! should the compiler warn about +DO..-LOOP?
915: : -LOOP ( compilation do-sys -- ; run-time loop-sys1 u -- | loop-sys2 ) \ gforth minus-loop
916: ['] (-loop) ['] (-loop)-lp+!# loop-like ; immediate restrict
917:
918: \ A symmetric version of "+LOOP". I.e., "-high -low ?DO -inc S+LOOP"
919: \ will iterate as often as "high low ?DO inc S+LOOP". For positive
920: \ increments it behaves like "+LOOP". Use S+LOOP instead of +LOOP for
921: \ negative increments.
922: : S+LOOP ( compilation do-sys -- ; run-time loop-sys1 n -- | loop-sys2 ) \ gforth s-plus-loop
923: ['] (s+loop) ['] (s+loop)-lp+!# loop-like ; immediate restrict
924:
925: : NEXT ( compilation do-sys -- ; run-time loop-sys1 -- | loop-sys2 ) \ gforth
926: ['] (next) ['] (next)-lp+!# loop-like ; immediate restrict
927:
928: \ Structural Conditionals 12dec92py
929:
930: : EXIT ( compilation -- ; run-time nest-sys -- ) \ core
931: 0 adjust-locals-size
932: POSTPONE ;s
933: POSTPONE unreachable ; immediate restrict
934:
935: : ?EXIT ( -- ) ( compilation -- ; run-time nest-sys f -- | nest-sys ) \ gforth
936: POSTPONE if POSTPONE exit POSTPONE then ; immediate restrict
937:
938: \ Strings 22feb93py
939:
940: : ," ( "string"<"> -- ) [char] " parse
941: here over char+ allot place align ;
942: : "lit ( -- addr )
943: r> r> dup count + aligned >r swap >r ; restrict
944: : (.") "lit count type ; restrict
945: : (S") "lit count ; restrict
946: : SLiteral ( Compilation c-addr1 u ; run-time -- c-addr2 u ) \ string
947: postpone (S") here over char+ allot place align ;
948: immediate restrict
949: create s"-buffer /line chars allot
950: : S" ( compilation 'ccc"' -- ; run-time -- c-addr u ) \ core,file s-quote
951: [char] " parse
952: state @
953: IF
954: postpone SLiteral
955: ELSE
956: /line min >r s"-buffer r@ cmove
957: s"-buffer r>
958: THEN ; immediate
959:
960: : ." ( compilation 'ccc"' -- ; run-time -- ) \ core dot-quote
961: state @ IF postpone (.") ," align
962: ELSE [char] " parse type THEN ; immediate
963: : ( ( compilation 'ccc<close-paren>' -- ; run-time -- ) \ core,file paren
964: BEGIN
965: >in @ [char] ) parse nip >in @ rot - =
966: WHILE
967: loadfile @ IF
968: refill 0= abort" missing ')' in paren comment"
969: THEN
970: REPEAT ; immediate
971: : \ ( -- ) \ core-ext backslash
972: blk @
973: IF
974: >in @ c/l / 1+ c/l * >in !
975: EXIT
976: THEN
977: source >in ! drop ; immediate
978:
979: : \G ( -- ) \ gforth backslash
980: POSTPONE \ ; immediate
981:
982: \ error handling 22feb93py
983: \ 'abort thrown out! 11may93jaw
984:
985: : (abort")
986: "lit >r
987: IF
988: r> "error ! -2 throw
989: THEN
990: rdrop ;
991: : abort" ( compilation 'ccc"' -- ; run-time f -- ) \ core,exception-ext abort-quote
992: postpone (abort") ," ; immediate restrict
993:
994: \ Header states 23feb93py
995:
996: : flag! ( 8b -- )
997: last @ dup 0= abort" last word was headerless"
998: cell+ tuck c@ xor swap c! ;
999: : immediate $20 flag! ;
1000: : restrict $40 flag! ;
1001: \ ' noop alias restrict
1002:
1003: \ Header 23feb93py
1004:
1005: \ input-stream, nextname and noname are quite ugly (passing
1006: \ information through global variables), but they are useful for dealing
1007: \ with existing/independent defining words
1008:
1009: defer (header)
1010: defer header ( -- ) \ gforth
1011: ' (header) IS header
1012:
1013: : string, ( c-addr u -- ) \ gforth
1014: \ puts down string as cstring
1015: dup c, here swap chars dup allot move ;
1016:
1017: : name, ( "name" -- ) \ gforth
1018: name name-too-short? name-too-long?
1019: string, cfalign ;
1020: : input-stream-header ( "name" -- )
1021: \ !! this is f83-implementation-dependent
1022: align here last ! -1 A,
1023: name, $80 flag! ;
1024:
1025: : input-stream ( -- ) \ general
1026: \ switches back to getting the name from the input stream ;
1027: ['] input-stream-header IS (header) ;
1028:
1029: ' input-stream-header IS (header)
1030:
1031: \ !! make that a 2variable
1032: create nextname-buffer 32 chars allot
1033:
1034: : nextname-header ( -- )
1035: \ !! f83-implementation-dependent
1036: nextname-buffer count
1037: align here last ! -1 A,
1038: string, cfalign
1039: $80 flag!
1040: input-stream ;
1041:
1042: \ the next name is given in the string
1043: : nextname ( c-addr u -- ) \ gforth
1044: name-too-long?
1045: nextname-buffer c! ( c-addr )
1046: nextname-buffer count move
1047: ['] nextname-header IS (header) ;
1048:
1049: : noname-header ( -- )
1050: 0 last ! cfalign
1051: input-stream ;
1052:
1053: : noname ( -- ) \ gforth
1054: \ the next defined word remains anonymous. The xt of that word is given by lastxt
1055: ['] noname-header IS (header) ;
1056:
1057: : lastxt ( -- xt ) \ gforth
1058: \ xt is the execution token of the last word defined. The main purpose of this word is to get the xt of words defined using noname
1059: lastcfa @ ;
1060:
1061: : Alias ( cfa "name" -- ) \ gforth
1062: Header reveal , $80 flag! ;
1063:
1064: : name>string ( nfa -- addr count ) \ gforth name-to-string
1065: cell+ count $1F and ;
1066:
1067: Create ??? 0 , 3 c, char ? c, char ? c, char ? c,
1068: : >name ( cfa -- nfa ) \ gforth to-name
1069: $21 cell do
1070: dup i - count $9F and + cfaligned over $80 + = if
1071: i - cell - unloop exit
1072: then
1073: cell +loop
1074: drop ??? ( wouldn't 0 be better? ) ;
1075:
1076: \ threading 17mar93py
1077:
1078: : cfa, ( code-address -- ) \ gforth cfa-comma
1079: here
1080: dup lastcfa !
1081: 0 A, 0 , code-address! ;
1082: : compile, ( xt -- ) \ core-ext compile-comma
1083: A, ;
1084: : !does ( addr -- ) \ gforth store-does
1085: lastxt does-code! ;
1086: : (does>) ( R: addr -- )
1087: r> /does-handler + !does ;
1088: : dodoes, ( -- )
1089: here /does-handler allot does-handler! ;
1090:
1091: : Create ( -- ) \ core
1092: Header reveal dovar: cfa, ;
1093:
1094: \ DOES> 17mar93py
1095:
1096: : DOES> ( compilation colon-sys1 -- colon-sys2 ; run-time nest-sys -- ) \ core does
1097: state @
1098: IF
1099: ;-hook postpone (does>) ?struc dodoes,
1100: ELSE
1101: align dodoes, here !does ]
1102: THEN
1103: defstart :-hook ; immediate
1104:
1105: \ Create Variable User Constant 17mar93py
1106:
1107: : Variable ( -- ) \ core
1108: Create 0 , ;
1109: : AVariable ( -- ) \ gforth
1110: Create 0 A, ;
1111: : 2VARIABLE ( "name" -- ) \ double
1112: create 0 , 0 , ;
1113:
1114: : User
1115: Variable ;
1116: : AUser
1117: AVariable ;
1118:
1119: : (Constant) Header reveal docon: cfa, ;
1120: : Constant ( w -- ) \ core
1121: (Constant) , ;
1122: : AConstant ( addr -- ) \ gforth
1123: (Constant) A, ;
1124:
1125: : 2Constant ( d -- ) \ double
1126: Create ( w1 w2 "name" -- )
1127: 2,
1128: DOES> ( -- w1 w2 )
1129: 2@ ;
1130:
1131: \ IS Defer What's Defers TO 24feb93py
1132:
1133: : Defer ( -- ) \ gforth
1134: \ !! shouldn't it be initialized with abort or something similar?
1135: Header Reveal dodefer: cfa,
1136: ['] noop A, ;
1137: \ Create ( -- )
1138: \ ['] noop A,
1139: \ DOES> ( ??? )
1140: \ @ execute ;
1141:
1142: : IS ( addr "name" -- ) \ gforth
1143: ' >body
1144: state @
1145: IF postpone ALiteral postpone !
1146: ELSE !
1147: THEN ; immediate
1148: ' IS Alias TO ( addr "name" -- ) \ core-ext
1149: immediate
1150:
1151: : What's ( "name" -- addr ) \ gforth
1152: ' >body
1153: state @
1154: IF
1155: postpone ALiteral postpone @
1156: ELSE
1157: @
1158: THEN ; immediate
1159: : Defers ( "name" -- ) \ gforth
1160: ' >body @ compile, ; immediate
1161:
1162: \ : ; 24feb93py
1163:
1164: defer :-hook ( sys1 -- sys2 )
1165: defer ;-hook ( sys2 -- sys1 )
1166:
1167: : : ( -- colon-sys ) \ core colon
1168: Header docol: cfa, defstart ] :-hook ;
1169: : ; ( compilation colon-sys -- ; run-time nest-sys ) \ core semicolon
1170: ;-hook ?struc postpone exit reveal postpone [ ; immediate restrict
1171:
1172: : :noname ( -- xt colon-sys ) \ core-ext colon-no-name
1173: 0 last !
1174: here docol: cfa, 0 ] :-hook ;
1175:
1176: \ Search list handling 23feb93py
1177:
1178: AVariable current ( -- addr ) \ gforth
1179:
1180: : last? ( -- false / nfa nfa )
1181: last @ ?dup ;
1182: : (reveal) ( -- )
1183: last?
1184: IF
1185: dup @ 0<
1186: IF
1187: current @ @ over ! current @ !
1188: ELSE
1189: drop
1190: THEN
1191: THEN ;
1192:
1193: \ object oriented search list 17mar93py
1194:
1195: \ word list structure:
1196:
1197: struct
1198: 1 cells: field find-method \ xt: ( c_addr u wid -- name-id )
1199: 1 cells: field reveal-method \ xt: ( -- ) \ used by dofield:, must be field
1200: 1 cells: field rehash-method \ xt: ( wid -- )
1201: \ \ !! what else
1202: end-struct wordlist-map-struct
1203:
1204: struct
1205: 1 cells: field wordlist-id \ not the same as wid; representation depends on implementation
1206: 1 cells: field wordlist-map \ pointer to a wordlist-map-struct
1207: 1 cells: field wordlist-link \ link field to other wordlists
1208: 1 cells: field wordlist-extend \ points to wordlist extensions (eg hash)
1209: end-struct wordlist-struct
1210:
1211: : f83find ( addr len wordlist -- nfa / false ) @ (f83find) ;
1212:
1213: \ Search list table: find reveal
1214: Create f83search ' f83find A, ' (reveal) A, ' drop A,
1215:
1216: Create forth-wordlist NIL A, G f83search T A, NIL A, NIL A,
1217: AVariable lookup G forth-wordlist lookup T !
1218: G forth-wordlist current T !
1219:
1220: : (search-wordlist) ( addr count wid -- nfa / false )
1221: dup wordlist-map @ find-method @ execute ;
1222:
1223: : search-wordlist ( addr count wid -- 0 / xt +-1 ) \ search
1224: (search-wordlist) dup IF found THEN ;
1225:
1226: Variable warnings ( -- addr ) \ gforth
1227: G -1 warnings T !
1228:
1229: : check-shadow ( addr count wid -- )
1230: \ prints a warning if the string is already present in the wordlist
1231: \ !! should be refined so the user can suppress the warnings
1232: >r 2dup 2dup r> (search-wordlist) warnings @ and ?dup if
1233: ." redefined " name>string 2dup type
1234: compare 0<> if
1235: ." with " type
1236: else
1237: 2drop
1238: then
1239: space space EXIT
1240: then
1241: 2drop 2drop ;
1242:
1243: : sfind ( c-addr u -- xt n / 0 ) \ gforth
1244: lookup @ search-wordlist ;
1245:
1246: : find ( addr -- cfa +-1 / string false ) \ core,search
1247: \ !! not ANS conformant: returns +-2 for restricted words
1248: dup count sfind dup if
1249: rot drop
1250: then ;
1251:
1252: : reveal ( -- ) \ gforth
1253: last? if
1254: name>string current @ check-shadow
1255: then
1256: current @ wordlist-map @ reveal-method @ execute ;
1257:
1258: : rehash ( wid -- )
1259: dup wordlist-map @ rehash-method @ execute ;
1260:
1261: : ' ( "name" -- addr ) \ core tick
1262: name sfind 0= if -&13 bounce then ;
1263: : ['] ( compilation "name" -- ; run-time --addr ) \ core bracket-tick
1264: ' postpone ALiteral ; immediate
1265: \ Input 13feb93py
1266:
1267: 07 constant #bell ( -- c ) \ gforth
1268: 08 constant #bs ( -- c ) \ gforth
1269: 09 constant #tab ( -- c ) \ gforth
1270: 7F constant #del ( -- c ) \ gforth
1271: 0D constant #cr ( -- c ) \ gforth
1272: \ the newline key code
1273: 0C constant #ff ( -- c ) \ gforth
1274: 0A constant #lf ( -- c ) \ gforth
1275:
1276: : bell #bell emit ;
1277: : cr ( -- ) \ core
1278: \ emit a newline
1279: #lf ( sic! ) emit ;
1280:
1281: \ : backspaces 0 ?DO #bs emit LOOP ;
1282: : >string ( span addr pos1 -- span addr pos1 addr2 len )
1283: over 3 pick 2 pick chars /string ;
1284: : type-rest ( span addr pos1 -- span addr pos1 back )
1285: >string tuck type ;
1286: : (del) ( max span addr pos1 -- max span addr pos2 )
1287: 1- >string over 1+ -rot move
1288: rot 1- -rot #bs emit type-rest bl emit 1+ backspaces ;
1289: : (ins) ( max span addr pos1 char -- max span addr pos2 )
1290: >r >string over 1+ swap move 2dup chars + r> swap c!
1291: rot 1+ -rot type-rest 1- backspaces 1+ ;
1292: : ?del ( max span addr pos1 -- max span addr pos2 0 )
1293: dup IF (del) THEN 0 ;
1294: : (ret) type-rest drop true space ;
1295: : back dup IF 1- #bs emit ELSE #bell emit THEN 0 ;
1296: : forw 2 pick over <> IF 2dup + c@ emit 1+ ELSE #bell emit THEN 0 ;
1297: : eof 2 pick 0= IF bye ELSE (ret) THEN ;
1298:
1299: Create ctrlkeys
1300: ] false false back false eof false forw false
1301: ?del false (ret) false false (ret) false false
1302: false false false false false false false false
1303: false false false false false false false false [
1304:
1305: defer everychar
1306: ' noop IS everychar
1307:
1308: : decode ( max span addr pos1 key -- max span addr pos2 flag )
1309: everychar
1310: dup #del = IF drop #bs THEN \ del is rubout
1311: dup bl < IF cells ctrlkeys + @ execute EXIT THEN
1312: >r 2over = IF rdrop bell 0 EXIT THEN
1313: r> (ins) 0 ;
1314:
1315: \ decode should better use a table for control key actions
1316: \ to define keyboard bindings later
1317:
1318: : accept ( addr len -- len ) \ core
1319: dup 0< IF abs over dup 1 chars - c@ tuck type
1320: \ this allows to edit given strings
1321: ELSE 0 THEN rot over
1322: BEGIN key decode UNTIL
1323: 2drop nip ;
1324:
1325: \ Output 13feb93py
1326:
1327: : (type) ( c-addr u -- ) \ gforth
1328: outfile-id write-file drop \ !! use ?DUP-IF THROW ENDIF instead of DROP ?
1329: ;
1330:
1331: Defer type ( c-addr u -- ) \ core
1332: \ defer type for a output buffer or fast
1333: \ screen write
1334:
1335: ' (type) IS Type
1336:
1337: : (emit) ( c -- ) \ gforth
1338: outfile-id emit-file drop \ !! use ?DUP-IF THROW ENDIF instead of DROP ?
1339: ;
1340:
1341: Defer emit ( c -- ) \ core
1342: ' (Emit) IS Emit
1343:
1344: Defer key ( -- c ) \ core
1345: ' (key) IS key
1346:
1347: \ Query 07apr93py
1348:
1349: : refill ( -- flag ) \ core-ext,block-ext,file-ext
1350: blk @ IF 1 blk +! true 0 >in ! EXIT THEN
1351: tib /line
1352: loadfile @ ?dup
1353: IF read-line throw
1354: ELSE sourceline# 0< IF 2drop false EXIT THEN
1355: accept true
1356: THEN
1357: 1 loadline +!
1358: swap #tib ! 0 >in ! ;
1359:
1360: : Query ( -- ) \ core-ext
1361: \ obsolescent
1362: loadfile off blk off refill drop ;
1363:
1364: \ File specifiers 11jun93jaw
1365:
1366:
1367: \ 1 c, here char r c, 0 c, 0 c, 0 c, char b c, 0 c,
1368: \ 2 c, here char r c, char + c, 0 c,
1369: \ 2 c, here char w c, char + c, 0 c, align
1370: 4 Constant w/o ( -- fam ) \ file w-o
1371: 2 Constant r/w ( -- fam ) \ file r-w
1372: 0 Constant r/o ( -- fam ) \ file r-o
1373:
1374: \ BIN WRITE-LINE 11jun93jaw
1375:
1376: \ : bin dup 1 chars - c@
1377: \ r/o 4 chars + over - dup >r swap move r> ;
1378:
1379: : bin ( fam1 -- fam2 ) \ file
1380: 1 or ;
1381:
1382: create nl$ 1 c, A c, 0 c, \ gnu includes usually a cr in dos
1383: \ or not unix environments if
1384: \ bin is not selected
1385:
1386: : write-line ( c-addr u fileid -- ior ) \ file
1387: dup >r write-file
1388: ?dup IF
1389: r> drop EXIT
1390: THEN
1391: nl$ count r> write-file ;
1392:
1393: \ include-file 07apr93py
1394:
1395: : push-file ( -- ) r>
1396: sourceline# >r loadfile @ >r
1397: blk @ >r tibstack @ >r >tib @ >r #tib @ >r
1398: >tib @ tibstack @ = IF r@ tibstack +! THEN
1399: tibstack @ >tib ! >in @ >r >r ;
1400:
1401: : pop-file ( throw-code -- throw-code )
1402: dup IF
1403: source >in @ sourceline# sourcefilename
1404: error-stack dup @ dup 1+
1405: max-errors 1- min error-stack !
1406: 6 * cells + cell+
1407: 5 cells bounds swap DO
1408: I !
1409: -1 cells +LOOP
1410: THEN
1411: r>
1412: r> >in ! r> #tib ! r> >tib ! r> tibstack ! r> blk !
1413: r> loadfile ! r> loadline ! >r ;
1414:
1415: : read-loop ( i*x -- j*x )
1416: BEGIN refill WHILE interpret REPEAT ;
1417:
1418: : include-file ( i*x fid -- j*x ) \ file
1419: push-file loadfile !
1420: 0 loadline ! blk off ['] read-loop catch
1421: loadfile @ close-file swap 2dup or
1422: pop-file drop throw throw ;
1423:
1424: create pathfilenamebuf 256 chars allot \ !! make this grow on demand
1425:
1426: \ : check-file-prefix ( addr len -- addr' len' flag )
1427: \ dup 0= IF true EXIT THEN
1428: \ over c@ '/ = IF true EXIT THEN
1429: \ over 2 S" ./" compare 0= IF true EXIT THEN
1430: \ over 3 S" ../" compare 0= IF true EXIT THEN
1431: \ over 2 S" ~/" compare 0=
1432: \ IF 1 /string
1433: \ S" HOME" getenv tuck pathfilenamebuf swap move
1434: \ 2dup + >r pathfilenamebuf + swap move
1435: \ pathfilenamebuf r> true
1436: \ ELSE false
1437: \ THEN ;
1438:
1439: : open-path-file ( c-addr1 u1 -- file-id c-addr2 u2 ) \ gforth
1440: \ opens a file for reading, searching in the path for it (unless
1441: \ the filename contains a slash); c-addr2 u2 is the full filename
1442: \ (valid until the next call); if the file is not found (or in
1443: \ case of other errors for each try), -38 (non-existant file) is
1444: \ thrown. Opening for other access modes makes little sense, as
1445: \ the path will usually contain dirs that are only readable for
1446: \ the user
1447: \ !! use file-status to determine access mode?
1448: 2dup [char] / scan nip ( 0<> )
1449: if \ the filename contains a slash
1450: 2dup r/o open-file throw ( c-addr1 u1 file-id )
1451: -rot >r pathfilenamebuf r@ cmove ( file-id R: u1 )
1452: pathfilenamebuf r> EXIT
1453: then
1454: pathdirs 2@ 0
1455: \ check-file-prefix 0=
1456: \ IF pathdirs 2@ 0
1457: ?DO ( c-addr1 u1 dirnamep )
1458: dup >r 2@ dup >r pathfilenamebuf swap cmove ( addr u )
1459: 2dup pathfilenamebuf r@ chars + swap cmove ( addr u )
1460: pathfilenamebuf over r> + dup >r r/o open-file 0=
1461: IF ( addr u file-id )
1462: nip nip r> rdrop 0 LEAVE
1463: THEN
1464: rdrop drop r> cell+ cell+
1465: LOOP
1466: \ ELSE 2dup open-file throw -rot THEN
1467: 0<> -&38 and throw ( file-id u2 )
1468: pathfilenamebuf swap ;
1469:
1470: create included-files 0 , 0 , ( pointer to and count of included files )
1471: here ," the terminal" dup c@ swap 1 + swap , A, here 2 cells -
1472: create image-included-files 1 , A, ( pointer to and count of included files )
1473: \ included-files points to ALLOCATEd space, while image-included-files
1474: \ points to ALLOTed objects, so it survives a save-system
1475:
1476: : loadfilename ( -- a-addr )
1477: \ a-addr 2@ produces the current file name ( c-addr u )
1478: included-files 2@ drop loadfilename# @ 2* cells + ;
1479:
1480: : sourcefilename ( -- c-addr u ) \ gforth
1481: \ the name of the source file which is currently the input
1482: \ source. The result is valid only while the file is being
1483: \ loaded. If the current input source is no (stream) file, the
1484: \ result is undefined.
1485: loadfilename 2@ ;
1486:
1487: : sourceline# ( -- u ) \ gforth sourceline-number
1488: \ the line number of the line that is currently being interpreted
1489: \ from a (stream) file. The first line has the number 1. If the
1490: \ current input source is no (stream) file, the result is
1491: \ undefined.
1492: loadline @ ;
1493:
1494: : init-included-files ( -- )
1495: image-included-files 2@ 2* cells save-string drop ( addr )
1496: image-included-files 2@ nip included-files 2! ;
1497:
1498: : included? ( c-addr u -- f ) \ gforth
1499: \ true, iff filename c-addr u is in included-files
1500: included-files 2@ 0
1501: ?do ( c-addr u addr )
1502: dup >r 2@ 2over compare 0=
1503: if
1504: 2drop rdrop unloop
1505: true EXIT
1506: then
1507: r> cell+ cell+
1508: loop
1509: 2drop drop false ;
1510:
1511: : add-included-file ( c-addr u -- ) \ gforth
1512: \ add name c-addr u to included-files
1513: included-files 2@ tuck 1+ 2* cells resize throw
1514: swap 2dup 1+ included-files 2!
1515: 2* cells + 2! ;
1516:
1517: : save-string ( addr1 u -- addr2 u ) \ gforth
1518: \ !! not a string, but a memblock word
1519: swap >r
1520: dup allocate throw
1521: swap 2dup r> -rot move ;
1522:
1523: : included1 ( i*x file-id c-addr u -- j*x ) \ gforth
1524: \ include the file file-id with the name given by c-addr u
1525: loadfilename# @ >r
1526: save-string add-included-file ( file-id )
1527: included-files 2@ nip 1- loadfilename# !
1528: ['] include-file catch
1529: r> loadfilename# !
1530: throw ;
1531:
1532: : included ( i*x addr u -- j*x ) \ file
1533: open-path-file included1 ;
1534:
1535: : required ( i*x addr u -- j*x ) \ gforth
1536: \ include the file with the name given by addr u, if it is not
1537: \ included already. Currently this works by comparing the name of
1538: \ the file (with path) against the names of earlier included
1539: \ files; however, it would probably be better to fstat the file,
1540: \ and compare the device and inode. The advantages would be: no
1541: \ problems with several paths to the same file (e.g., due to
1542: \ links) and we would catch files included with include-file and
1543: \ write a require-file.
1544: open-path-file 2dup included?
1545: if
1546: 2drop close-file throw
1547: else
1548: included1
1549: then ;
1550:
1551: \ HEX DECIMAL 2may93jaw
1552:
1553: : decimal ( -- ) \ core
1554: a base ! ;
1555: : hex ( -- ) \ core-ext
1556: 10 base ! ;
1557:
1558: \ DEPTH 9may93jaw
1559:
1560: : depth ( -- +n ) \ core
1561: sp@ s0 @ swap - cell / ;
1562: : clearstack ( ... -- )
1563: s0 @ sp! ;
1564:
1565: \ INCLUDE 9may93jaw
1566:
1567: : include ( "file" -- ) \ gforth
1568: name included ;
1569:
1570: : require ( "file" -- ) \ gforth
1571: name required ;
1572:
1573: \ RECURSE 17may93jaw
1574:
1575: : recurse ( compilation -- ; run-time ?? -- ?? ) \ core
1576: lastxt compile, ; immediate restrict
1577: : recursive ( -- ) \ gforth
1578: reveal last off ; immediate
1579:
1580: \ */MOD */ 17may93jaw
1581:
1582: \ !! I think */mod should have the same rounding behaviour as / - anton
1583: : */mod ( n1 n2 n3 -- n4 n5 ) \ core star-slash-mod
1584: >r m* r> sm/rem ;
1585:
1586: : */ ( n1 n2 n3 -- n4 ) \ core star-slash
1587: */mod nip ;
1588:
1589: \ EVALUATE 17may93jaw
1590:
1591: : evaluate ( c-addr len -- ) \ core,block
1592: push-file #tib ! >tib !
1593: >in off blk off loadfile off -1 loadline !
1594: ['] interpret catch
1595: pop-file throw ;
1596:
1597: : abort ( ?? -- ?? ) \ core,exception-ext
1598: -1 throw ;
1599:
1600: \+ environment? true ENV" CORE"
1601: \ core wordset is now complete!
1602:
1603: \ Quit 13feb93py
1604:
1605: Defer 'quit
1606: Defer .status
1607: : prompt state @ IF ." compiled" EXIT THEN ." ok" ;
1608: : (quit) BEGIN .status cr query interpret prompt AGAIN ;
1609: ' (quit) IS 'quit
1610:
1611: \ DOERROR (DOERROR) 13jun93jaw
1612:
1613: 8 Constant max-errors
1614: Variable error-stack 0 error-stack !
1615: max-errors 6 * cells allot
1616: \ format of one cell:
1617: \ source ( addr u )
1618: \ >in
1619: \ line-number
1620: \ Loadfilename ( addr u )
1621:
1622: : dec. ( n -- ) \ gforth
1623: \ print value in decimal representation
1624: base @ decimal swap . base ! ;
1625:
1626: : typewhite ( addr u -- ) \ gforth
1627: \ like type, but white space is printed instead of the characters
1628: bounds ?do
1629: i c@ 9 = if \ check for tab
1630: 9
1631: else
1632: bl
1633: then
1634: emit
1635: loop ;
1636:
1637: DEFER DOERROR
1638:
1639: : .error-frame ( addr1 u1 n1 n2 addr2 u2 -- )
1640: cr error-stack @
1641: IF
1642: ." in file included from "
1643: type ." :" dec. drop 2drop
1644: ELSE
1645: type ." :" dec.
1646: cr dup 2over type cr drop
1647: nip -trailing 1- ( line-start index2 )
1648: 0 >r BEGIN
1649: 2dup + c@ bl > WHILE
1650: r> 1+ >r 1- dup 0< UNTIL THEN 1+
1651: ( line-start index1 )
1652: typewhite
1653: r> 1 max 0 ?do \ we want at least one "^", even if the length is 0
1654: [char] ^ emit
1655: loop
1656: THEN
1657: ;
1658:
1659: : (DoError) ( throw-code -- )
1660: sourceline# IF
1661: source >in @ sourceline# 0 0 .error-frame
1662: THEN
1663: error-stack @ 0 ?DO
1664: -1 error-stack +!
1665: error-stack dup @ 6 * cells + cell+
1666: 6 cells bounds DO
1667: I @
1668: cell +LOOP
1669: .error-frame
1670: LOOP
1671: dup -2 =
1672: IF
1673: "error @ ?dup
1674: IF
1675: cr count type
1676: THEN
1677: drop
1678: ELSE
1679: .error
1680: THEN
1681: normal-dp dpp ! ;
1682:
1683: ' (DoError) IS DoError
1684:
1685: : quit ( ?? -- ?? ) \ core
1686: r0 @ rp! handler off >tib @ >r
1687: BEGIN
1688: postpone [
1689: ['] 'quit CATCH dup
1690: WHILE
1691: DoError r@ >tib ! r@ tibstack !
1692: REPEAT
1693: drop r> >tib ! ;
1694:
1695: \ Cold 13feb93py
1696:
1697: \ : .name ( name -- ) name>string type space ;
1698: \ : words listwords @
1699: \ BEGIN @ dup WHILE dup .name REPEAT drop ;
1700:
1701: : cstring>sstring ( cstring -- addr n ) \ gforth cstring-to-sstring
1702: -1 0 scan 0 swap 1+ /string ;
1703: : arg ( n -- addr count ) \ gforth
1704: cells argv @ + @ cstring>sstring ;
1705: : #! postpone \ ; immediate
1706:
1707: Create pathstring 2 cells allot \ string
1708: Create pathdirs 2 cells allot \ dir string array, pointer and count
1709: Variable argv
1710: Variable argc
1711:
1712: 0 Value script? ( -- flag )
1713:
1714: : process-path ( addr1 u1 -- addr2 u2 )
1715: \ addr1 u1 is a path string, addr2 u2 is an array of dir strings
1716: align here >r
1717: BEGIN
1718: over >r [char] : scan
1719: over r> tuck - ( rest-str this-str )
1720: dup
1721: IF
1722: 2dup 1- chars + c@ [char] / <>
1723: IF
1724: 2dup chars + [char] / swap c!
1725: 1+
1726: THEN
1727: 2,
1728: ELSE
1729: 2drop
1730: THEN
1731: dup
1732: WHILE
1733: 1 /string
1734: REPEAT
1735: 2drop
1736: here r> tuck - 2 cells / ;
1737:
1738: : do-option ( addr1 len1 addr2 len2 -- n )
1739: 2swap
1740: 2dup s" -e" compare 0= >r
1741: 2dup s" --evaluate" compare 0= r> or
1742: IF 2drop dup >r ['] evaluate catch
1743: ?dup IF dup >r DoError r> negate (bye) THEN
1744: r> >tib +! 2 EXIT THEN
1745: ." Unknown option: " type cr 2drop 1 ;
1746:
1747: : process-args ( -- )
1748: >tib @ >r
1749: argc @ 1
1750: ?DO
1751: I arg over c@ [char] - <>
1752: IF
1753: required 1
1754: ELSE
1755: I 1+ argc @ = IF s" " ELSE I 1+ arg THEN
1756: do-option
1757: THEN
1758: +LOOP
1759: r> >tib ! ;
1760:
1761: Defer 'cold ' noop IS 'cold
1762:
1763: : cold ( -- ) \ gforth
1764: stdout TO outfile-id
1765: pathstring 2@ process-path pathdirs 2!
1766: init-included-files
1767: 'cold
1768: argc @ 1 >
1769: IF
1770: true to script?
1771: ['] process-args catch ?dup
1772: IF
1773: dup >r DoError cr r> negate (bye)
1774: THEN
1775: cr
1776: THEN
1777: false to script?
1778: ." GForth " version-string type ." , Copyright (C) 1994-1996 Free Software Foundation, Inc." cr
1779: ." GForth comes with ABSOLUTELY NO WARRANTY; for details type `license'" cr
1780: ." Type `bye' to exit"
1781: loadline off quit ;
1782:
1783: : license ( -- ) \ gforth
1784: cr
1785: ." This program is free software; you can redistribute it and/or modify" cr
1786: ." it under the terms of the GNU General Public License as published by" cr
1787: ." the Free Software Foundation; either version 2 of the License, or" cr
1788: ." (at your option) any later version." cr cr
1789:
1790: ." This program is distributed in the hope that it will be useful," cr
1791: ." but WITHOUT ANY WARRANTY; without even the implied warranty of" cr
1792: ." MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the" cr
1793: ." GNU General Public License for more details." cr cr
1794:
1795: ." You should have received a copy of the GNU General Public License" cr
1796: ." along with this program; if not, write to the Free Software" cr
1797: ." Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA." cr ;
1798:
1799: : boot ( path **argv argc -- )
1800: argc ! argv ! cstring>sstring pathstring 2! main-task up!
1801: sp@ dup s0 ! $10 + dup >tib ! tibstack ! #tib off >in off
1802: rp@ r0 ! fp@ f0 ! ['] cold catch DoError bye ;
1803:
1804: : bye ( -- ) \ tools-ext
1805: script? 0= IF cr THEN 0 (bye) ;
1806:
1807: \ **argv may be scanned by the C starter to get some important
1808: \ information, as -display and -geometry for an X client FORTH
1809: \ or space and stackspace overrides
1810:
1811: \ 0 arg contains, however, the name of the program.
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>