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