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