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