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