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