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