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