Diff for /gforth/Attic/kernal.fs between versions 1.52 and 1.60

version 1.52, 1996/02/09 17:34:11 version 1.60, 1996/07/16 20:57:11
Line 74  HEX Line 74  HEX
     \ the code address of a @code{field}      \ the code address of a @code{field}
     ['] reveal-method >code-address ;      ['] reveal-method >code-address ;
   
   NIL AConstant NIL \ gforth
   
 \ Bit string manipulation                              06oct92py  \ Bit string manipulation                              06oct92py
   
 \ Create bits  80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,  \ Create bits  80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
Line 143  HEX Line 145  HEX
 : off ( addr -- ) \ gforth  : off ( addr -- ) \ gforth
     false swap ! ;      false swap ! ;
   
   \ dabs roll                                           17may93jaw
   
   : dabs ( d1 -- d2 ) \ double
       dup 0< IF dnegate THEN ;
   
   : roll  ( x0 x1 .. xn n -- x1 .. xn x0 ) \ core-ext
     dup 1+ pick >r
     cells sp@ cell+ dup cell+ rot move drop r> ;
   
 \ name> found                                          17dec92py  \ name> found                                          17dec92py
   
   $80 constant alias-mask \ set when the word is not an alias!
   $40 constant immediate-mask
   $20 constant restrict-mask
   
 : (name>)  ( nfa+cell -- cfa )  : (name>)  ( nfa+cell -- cfa )
     1 cells - name>string +  cfaligned ;      1 cells - name>string +  cfaligned ;
 : name>    ( nfa -- cfa ) \ gforth  : name>    ( nfa -- cfa ) \ gforth
     cell+      cell+
     dup  (name>) swap  c@ $80 and 0= IF  @ THEN ;      dup  (name>) swap  c@ alias-mask and 0= IF  @ THEN ;
   
 : found ( nfa -- cfa n ) \ gforth  
     cell+  
     dup c@ >r  (name>) r@ $80 and  0= IF  @       THEN  
                     -1 r@ $40 and     IF  1-      THEN  
                        r> $20 and     IF  negate  THEN  ;  
   
 \ (find)                                               17dec92py  \ (find)                                               17dec92py
   
Line 247  Defer source ( -- addr count ) \ core Line 256  Defer source ( -- addr count ) \ core
 \ Literal                                              17dec92py  \ Literal                                              17dec92py
   
 : Literal  ( compilation n -- ; run-time -- n ) \ core  : Literal  ( compilation n -- ; run-time -- n ) \ core
     state @ IF postpone lit  , THEN ; immediate      postpone lit  , ; immediate restrict
 : ALiteral ( compilation addr -- ; run-time -- addr ) \ gforth  : ALiteral ( compilation addr -- ; run-time -- addr ) \ gforth
     state @ IF postpone lit A, THEN ;      postpone lit A, ; immediate restrict
                                                       immediate  
   
 : char   ( 'char' -- n ) \ core  : char   ( 'char' -- n ) \ core
     bl word char+ c@ ;      bl word char+ c@ ;
 : [char] ( compilation 'char' -- ; run-time -- n )  : [char] ( compilation 'char' -- ; run-time -- n )
     char postpone Literal ; immediate      char postpone Literal ; immediate restrict
 ' [char] Alias Ascii immediate  
   
 : (compile) ( -- ) \ gforth  : (compile) ( -- ) \ gforth
     r> dup cell+ >r @ compile, ;      r> dup cell+ >r @ compile, ;
 : postpone ( "name" -- ) \ core  : postpone ( "name" -- ) \ core
   name sfind dup 0= abort" Can't compile "    name sfind dup 0= abort" Can't compile "
   0> IF  compile,  ELSE  postpone (compile) A,  THEN ;    0> IF  compile,  ELSE  postpone (compile) A,  THEN ; immediate restrict
                                              immediate restrict  
   : special: ( interp comp "name" -- )
       Create immediate swap A, A,
       DOES>  state @ IF  cell+  THEN  perform ;
   
 \ Use (compile) for the old behavior of compile!  \ Use (compile) for the old behavior of compile!
   
Line 453  hex Line 463  hex
   
 : throw ( y1 .. ym error/0 -- y1 .. ym / z1 .. zn error ) \ exception  : throw ( y1 .. ym error/0 -- y1 .. ym / z1 .. zn error ) \ exception
     ?DUP IF      ?DUP IF
         [ here 4 cells ! ]          [ here 9 cells ! ]
         handler @ rp!          handler @ rp!
         r> handler !          r> handler !
         r> lp!          r> lp!
Line 486  Defer parser Line 496  Defer parser
 Defer name ( -- c-addr count ) \ gforth  Defer name ( -- c-addr count ) \ gforth
 \ get the next word from the input buffer  \ get the next word from the input buffer
 ' (name) IS name  ' (name) IS name
 Defer notfound ( c-addr count -- )  Defer compiler-notfound ( c-addr count -- )
   Defer interpreter-notfound ( c-addr count -- )
   
 : no.extensions  ( addr u -- )  : no.extensions  ( addr u -- )
     2drop -&13 bounce ;      2drop -&13 bounce ;
 ' no.extensions IS notfound  ' no.extensions IS compiler-notfound
   ' no.extensions IS interpreter-notfound
   
   : compile-only ( ... -- )
       -&14 throw ;
   Defer interpret-special ( c-addr u xt -- ) \ !! use nfa instead of xt?
   ' compile-only IS interpret-special
   
 : interpret ( ?? -- ?? ) \ gforth  : interpret ( ?? -- ?? ) \ gforth
     \ interpret/compile the (rest of the) input buffer      \ interpret/compile the (rest of the) input buffer
Line 505  Defer notfound ( c-addr count -- ) Line 522  Defer notfound ( c-addr count -- )
   
 : interpreter  ( c-addr u -- ) \ gforth  : interpreter  ( c-addr u -- ) \ gforth
     \ interpretation semantics for the name/number c-addr u      \ interpretation semantics for the name/number c-addr u
     2dup sfind dup      2dup (sfind) dup
     IF      IF
         1 and          1 and
         IF \ not restricted to compile state?          IF \ not restricted to compile state?
             nip nip execute EXIT              nip nip execute EXIT
         THEN          THEN
         -&14 throw          interpret-special exit
     THEN      THEN
     drop      drop
     2dup 2>r snumber?      2dup 2>r snumber?
     IF      IF
         2rdrop          2rdrop
     ELSE      ELSE
         2r> notfound          2r> interpreter-notfound
     THEN ;      THEN ;
   
 ' interpreter  IS  parser  ' interpreter  IS  parser
   
 : compiler     ( c-addr u -- ) \ gforth  : compiler     ( c-addr u -- ) \ gforth
     \ compilation semantics for the name/number c-addr u      \ compilation semantics for the name/number c-addr u
     2dup sfind dup      2dup (sfind) dup
     IF      IF
         0>          0>
         IF          IF
Line 543  Defer notfound ( c-addr count -- ) Line 560  Defer notfound ( c-addr count -- )
         postpone Literal          postpone Literal
         2drop          2drop
     ELSE      ELSE
         drop notfound          drop compiler-notfound
     THEN ;      THEN ;
   
 : [ ( -- ) \ core       left-bracket  : [ ( -- ) \ core       left-bracket
Line 729  variable backedge-locals Line 746  variable backedge-locals
 : ?DUP-0=-IF ( compilation -- orig ; run-time n -- n| ) \ gforth        question-dupe-zero-equals-if  : ?DUP-0=-IF ( compilation -- orig ; run-time n -- n| ) \ gforth        question-dupe-zero-equals-if
     POSTPONE ?dup-0=-?branch >mark ;       immediate restrict      POSTPONE ?dup-0=-?branch >mark ;       immediate restrict
   
 : THEN ( compilation orig -- ; run-time -- ) \ core  : then-like ( orig -- addr )
     dup orig?      swap -rot dead-orig =
     dead-orig =  
     if      if
         >resolve drop          drop
     else      else
         dead-code @          dead-code @
         if          if
             >resolve set-locals-size-list dead-code off              set-locals-size-list dead-code off
         else \ both live          else \ both live
             over list-size adjust-locals-size              dup list-size adjust-locals-size
             >resolve  
             locals-list @ common-list dup list-size adjust-locals-size              locals-list @ common-list dup list-size adjust-locals-size
             locals-list !              locals-list !
         then          then
     then ; immediate restrict      then ;
   
   : THEN ( compilation orig -- ; run-time -- ) \ core
       dup orig?  then-like  >resolve ; immediate restrict
   
 ' THEN alias ENDIF ( compilation orig -- ; run-time -- ) \ gforth  ' THEN alias ENDIF ( compilation orig -- ; run-time -- ) \ gforth
 immediate restrict  immediate restrict
Line 773  immediate restrict Line 791  immediate restrict
 \ issue a warning (see below). The following code is generated:  \ issue a warning (see below). The following code is generated:
 \ lp+!# (current-local-size - dest-locals-size)  \ lp+!# (current-local-size - dest-locals-size)
 \ branch <begin>  \ branch <begin>
 : AGAIN ( compilation dest -- ; run-time -- ) \ core-ext  
     dest?  : again-like ( dest -- addr )
     over list-size adjust-locals-size      over list-size adjust-locals-size
     POSTPONE branch      swap check-begin  POSTPONE unreachable ;
     <resolve  
     check-begin  : AGAIN ( compilation dest -- ; run-time -- ) \ core-ext
     POSTPONE unreachable ; immediate restrict      dest? again-like  POSTPONE branch  <resolve ; immediate restrict
   
 \ UNTIL (the current control flow may join an earlier one or continue):  \ UNTIL (the current control flow may join an earlier one or continue):
 \ Similar to AGAIN. The new locals-list and locals-size are the current  \ Similar to AGAIN. The new locals-list and locals-size are the current
Line 946  Avariable leave-sp  leave-stack 3 cells Line 964  Avariable leave-sp  leave-stack 3 cells
 : SLiteral ( Compilation c-addr1 u ; run-time -- c-addr2 u ) \ string  : SLiteral ( Compilation c-addr1 u ; run-time -- c-addr2 u ) \ string
     postpone (S") here over char+ allot  place align ;      postpone (S") here over char+ allot  place align ;
                                              immediate restrict                                               immediate restrict
 create s"-buffer /line chars allot  
 : S" ( compilation 'ccc"' -- ; run-time -- c-addr u )   \ core,file     s-quote  
     [char] " parse  
     state @  
     IF  
         postpone SLiteral  
     ELSE  
         /line min >r s"-buffer r@ cmove  
         s"-buffer r>  
     THEN ; immediate  
   
 : ." ( compilation 'ccc"' -- ; run-time -- )  \ core    dot-quote  
     state @  IF    postpone (.") ,"  align  
                     ELSE  [char] " parse type  THEN  ;  immediate  
 : ( ( compilation 'ccc<close-paren>' -- ; run-time -- ) \ core,file     paren  : ( ( compilation 'ccc<close-paren>' -- ; run-time -- ) \ core,file     paren
     [char] ) parse 2drop ;                       immediate      BEGIN
           >in @ [char] ) parse nip >in @ rot - =
       WHILE
           loadfile @ IF
               refill 0= abort" missing ')' in paren comment"
           THEN
       REPEAT ;                       immediate
 : \ ( -- ) \ core-ext backslash  : \ ( -- ) \ core-ext backslash
     blk @      blk @
     IF      IF
Line 987  create s"-buffer /line chars allot Line 997  create s"-buffer /line chars allot
   
 \ Header states                                        23feb93py  \ Header states                                        23feb93py
   
 : flag! ( 8b -- )  : cset ( bmask c-addr -- )
     last @ dup 0= abort" last word was headerless"      tuck c@ or swap c! ; 
     cell+ tuck c@ xor swap c! ;  : creset ( bmask c-addr -- )
 : immediate     $20 flag! ;      tuck c@ swap invert and swap c! ; 
 : restrict      $40 flag! ;  : ctoggle ( bmask c-addr -- )
 \ ' noop alias restrict      tuck c@ xor swap c! ; 
   
   : lastflags ( -- c-addr )
       \ the address of the flags byte in the last header
       \ aborts if the last defined word was headerless
       last @ dup 0= abort" last word was headerless" cell+ ;
   
   : immediate     immediate-mask lastflags cset ;
   : restrict      restrict-mask lastflags cset ;
   
 \ Header                                               23feb93py  \ Header                                               23feb93py
   
Line 1008  defer header ( -- ) \ gforth Line 1026  defer header ( -- ) \ gforth
     \ puts down string as cstring      \ puts down string as cstring
     dup c, here swap chars dup allot move ;      dup c, here swap chars dup allot move ;
   
 : name,  ( "name" -- ) \ gforth  : header, ( c-addr u -- ) \ gforth
     name name-too-short? name-too-long?      name-too-long?
     string, cfalign ;      align here last !
 : input-stream-header ( "name" -- )      current @ 1 or A,   \ link field; before revealing, it contains the
     \ !! this is f83-implementation-dependent                          \ tagged reveal-into wordlist
     align here last !  -1 A,      string, cfalign
     name, $80 flag! ;      alias-mask lastflags cset ;
   
   : input-stream-header ( "name" -- )
       name name-too-short? header, ;
 : input-stream ( -- )  \ general  : input-stream ( -- )  \ general
 \ switches back to getting the name from the input stream ;  \ switches back to getting the name from the input stream ;
     ['] input-stream-header IS (header) ;      ['] input-stream-header IS (header) ;
Line 1026  defer header ( -- ) \ gforth Line 1046  defer header ( -- ) \ gforth
 create nextname-buffer 32 chars allot  create nextname-buffer 32 chars allot
   
 : nextname-header ( -- )  : nextname-header ( -- )
     \ !! f83-implementation-dependent      nextname-buffer count header,
     nextname-buffer count  
     align here last ! -1 A,  
     string, cfalign  
     $80 flag!  
     input-stream ;      input-stream ;
   
 \ the next name is given in the string  \ the next name is given in the string
Line 1053  create nextname-buffer 32 chars allot Line 1069  create nextname-buffer 32 chars allot
     lastcfa @ ;      lastcfa @ ;
   
 : Alias    ( cfa "name" -- ) \ gforth  : Alias    ( cfa "name" -- ) \ gforth
   Header reveal , $80 flag! ;      Header reveal
       alias-mask lastflags creset
       dup A, lastcfa ! ;
   
 : name>string ( nfa -- addr count ) \ gforth    name-to-string  : name>string ( nfa -- addr count ) \ gforth    name-to-string
  cell+ count $1F and ;   cell+ count $1F and ;
Line 1061  create nextname-buffer 32 chars allot Line 1079  create nextname-buffer 32 chars allot
 Create ???  0 , 3 c, char ? c, char ? c, char ? c,  Create ???  0 , 3 c, char ? c, char ? c, char ? c,
 : >name ( cfa -- nfa ) \ gforth to-name  : >name ( cfa -- nfa ) \ gforth to-name
  $21 cell do   $21 cell do
    dup i - count $9F and + cfaligned over $80 + = if     dup i - count $9F and + cfaligned over alias-mask + = if
      i - cell - unloop exit       i - cell - unloop exit
    then     then
  cell +loop   cell +loop
Line 1085  Create ???  0 , 3 c, char ? c, char ? c, Line 1103  Create ???  0 , 3 c, char ? c, char ? c,
 : Create ( -- ) \ core  : Create ( -- ) \ core
     Header reveal dovar: cfa, ;      Header reveal dovar: cfa, ;
   
 \ DOES>                                                17mar93py  
   
 : DOES>  ( compilation colon-sys1 -- colon-sys2 ; run-time nest-sys -- ) \ core does  
     state @  
     IF  
         ;-hook postpone (does>) ?struc dodoes,  
     ELSE  
         align dodoes, here !does ]  
     THEN   
     defstart :-hook ; immediate  
   
 \ Create Variable User Constant                        17mar93py  \ Create Variable User Constant                        17mar93py
   
 : Variable ( -- ) \ core  : Variable ( -- ) \ core
Line 1131  Create ???  0 , 3 c, char ? c, char ? c, Line 1138  Create ???  0 , 3 c, char ? c, char ? c,
 \     Create ( -- )   \     Create ( -- ) 
 \       ['] noop A,  \       ['] noop A,
 \     DOES> ( ??? )  \     DOES> ( ??? )
 \       @ execute ;  \       perform ;
   
 : IS ( addr "name" -- ) \ gforth  
     ' >body  
     state @  
     IF    postpone ALiteral postpone !    
     ELSE  !  
     THEN ;  immediate  
 ' IS Alias TO ( addr "name" -- ) \ core-ext  
 immediate  
   
 : What's ( "name" -- addr ) \ gforth  
     ' >body  
     state @  
     IF  
         postpone ALiteral postpone @  
     ELSE  
         @  
     THEN ; immediate  
 : Defers ( "name" -- ) \ gforth  : Defers ( "name" -- ) \ gforth
     ' >body @ compile, ; immediate      ' >body @ compile, ; immediate
   
Line 1173  AVariable current ( -- addr ) \ gforth Line 1163  AVariable current ( -- addr ) \ gforth
   
 : last?   ( -- false / nfa nfa )  : last?   ( -- false / nfa nfa )
     last @ ?dup ;      last @ ?dup ;
 : (reveal) ( -- )  : (reveal) ( nfa wid -- )
     last?      ( wid>wordlist-id ) dup >r
     IF      @ over ( name>link ) ! 
         dup @ 0<      r> ! ;
         IF  
             current @ @ over ! current @ !  
         ELSE  
             drop  
         THEN  
     THEN ;  
   
 \ object oriented search list                          17mar93py  \ object oriented search list                          17mar93py
   
Line 1190  AVariable current ( -- addr ) \ gforth Line 1174  AVariable current ( -- addr ) \ gforth
   
 struct  struct
   1 cells: field find-method   \ xt: ( c_addr u wid -- name-id )    1 cells: field find-method   \ xt: ( c_addr u wid -- name-id )
   1 cells: field reveal-method \ xt: ( -- ) \ used by dofield:, must be field    1 cells: field reveal-method \ xt: ( nfa wid -- ) \ used by dofield:, must be field
   1 cells: field rehash-method \ xt: ( wid -- )    1 cells: field rehash-method \ xt: ( wid -- )
 \   \ !! what else  \   \ !! what else
 end-struct wordlist-map-struct  end-struct wordlist-map-struct
Line 1202  struct Line 1186  struct
   1 cells: field wordlist-extend \ points to wordlist extensions (eg hash)    1 cells: field wordlist-extend \ points to wordlist extensions (eg hash)
 end-struct wordlist-struct  end-struct wordlist-struct
   
 : f83find      ( addr len wordlist -- nfa / false )  @ (f83find) ;  : f83find      ( addr len wordlist -- nfa / false )
       ( wid>wordlist-id ) @ (f83find) ;
   
 \ Search list table: find reveal  \ Search list table: find reveal
 Create f83search       ' f83find A,  ' (reveal) A,  ' drop A,  Create f83search ( -- wordlist-map )
       ' f83find A,  ' (reveal) A,  ' drop A,
   
 Create forth-wordlist  NIL A, G f83search T A, NIL A, NIL A,  Create forth-wordlist  NIL A, G f83search T A, NIL A, NIL A,
 AVariable lookup       G forth-wordlist lookup T !  AVariable lookup       G forth-wordlist lookup T !
 G forth-wordlist current T !  G forth-wordlist current T !
   
   \ higher level parts of find
   
   : special? ( xt -- flag )
       >does-code ['] S" >does-code = ;
   
   : xt>i ( xt -- xt )
       dup special?  IF  >body  @  THEN ;
   
   : xt>c ( xt -- xt )
       dup special?  IF  >body  cell+  @  THEN ;
   
   : xt>s ( xt -- xt )
       dup special?  IF  >body  state @ IF  cell+  THEN  @  THEN ;
   
   : found ( nfa -- cfa n ) \ gforth
       cell+  dup c@ >r  (name>)
       r@ alias-mask     and  0= IF  @       THEN  -1
       r@ restrict-mask  and     IF  1-      THEN
       r> immediate-mask and     IF  negate  THEN  ;
   
 : (search-wordlist)  ( addr count wid -- nfa / false )  : (search-wordlist)  ( addr count wid -- nfa / false )
   dup wordlist-map @ find-method @ execute ;      dup wordlist-map @ find-method perform ;
   
 : search-wordlist  ( addr count wid -- 0 / xt +-1 ) \ search  : search-wordlist  ( addr count wid -- 0 / xt +-1 ) \ search
     (search-wordlist) dup  IF  found  THEN ;      (search-wordlist) dup  IF  found  swap xt>s swap  THEN ;
   
   : (sfind) ( c-addr u -- xt n / 0 )
       lookup @ (search-wordlist) dup IF  found  THEN ;
   
   : sfind ( c-addr u -- xt n / 0 ) \ gforth
       lookup @ search-wordlist ;
   
   : find   ( addr -- cfa +-1 / string false ) \ core,search
       dup count sfind dup IF
           rot drop
       THEN
       dup 1 and 0=  IF  2/  THEN ;
   
   : (')    ( "name" -- xt ) \ gforth      paren-tick
       name (sfind) 0= IF  -&13 bounce THEN  ;
   : [(')]  ( compilation "name" -- ; run-time -- addr ) \ gforth  bracket-paren-tick
       (') postpone ALiteral ; immediate restrict
   
   : '    ( "name" -- xt ) \ core  tick
       (') xt>i ;
   : [']  ( compilation "name" -- ; run-time -- addr ) \ core      bracket-tick
       ' postpone ALiteral ; immediate restrict
   
   : C'    ( "name" -- xt ) \ gforth       c-tick
       (') xt>c ;
   : [C']  ( compilation "name" -- ; run-time -- addr ) \ gforth   bracket-c-tick
       C' postpone ALiteral ; immediate restrict
   
   : S'    ( "name" -- xt ) \ gforth       s-tick
       (') xt>s ;
   : [S']  ( compilation "name" -- ; run-time -- addr ) \ gforth   bracket-s-tick
       S' postpone ALiteral ; immediate restrict
   
   \ reveal words
   
 Variable warnings ( -- addr ) \ gforth  Variable warnings ( -- addr ) \ gforth
 G -1 warnings T !  G -1 warnings T !
   
 : check-shadow  ( addr count wid -- )  : check-shadow  ( addr count wid -- )
 \ prints a warning if the string is already present in the wordlist  \ prints a warning if the string is already present in the wordlist
 \ !! should be refined so the user can suppress the warnings  
  >r 2dup 2dup r> (search-wordlist) warnings @ and ?dup if   >r 2dup 2dup r> (search-wordlist) warnings @ and ?dup if
    ." redefined " name>string 2dup type     ." redefined " name>string 2dup type
    compare 0<> if     compare 0<> if
Line 1234  G -1 warnings T ! Line 1273  G -1 warnings T !
  then   then
  2drop 2drop ;   2drop 2drop ;
   
 : sfind ( c-addr u -- xt n / 0 ) \ gforth  
     lookup @ search-wordlist ;  
   
 : find   ( addr -- cfa +-1 / string false ) \ core,search  
     \ !! not ANS conformant: returns +-2 for restricted words  
     dup count sfind dup if  
         rot drop  
     then ;  
   
 : reveal ( -- ) \ gforth  : reveal ( -- ) \ gforth
  last? if      last?
    name>string current @ check-shadow      if \ the last word has a header
  then          dup ( name>link ) @ 1 and
  current @ wordlist-map @ reveal-method @ execute ;          if \ it is still hidden
               dup ( name>link ) @ 1 xor           ( nfa wid )
               2dup >r name>string r> check-shadow ( nfa wid )
               dup wordlist-map @ reveal-method perform
           then
       then ;
   
 : rehash  ( wid -- )  : rehash  ( wid -- )
     dup wordlist-map @ rehash-method @ execute ;      dup wordlist-map @ rehash-method perform ;
   
 : '    ( "name" -- addr ) \ core        tick  
     name sfind 0= if -&13 bounce then ;  
 : [']  ( compilation "name" -- ; run-time --addr ) \ core       bracket-tick  
     ' postpone ALiteral ; immediate  
 \ Input                                                13feb93py  \ Input                                                13feb93py
   
 07 constant #bell ( -- c ) \ gforth  07 constant #bell ( -- c ) \ gforth
Line 1273  G -1 warnings T ! Line 1304  G -1 warnings T !
     #lf ( sic! ) emit ;      #lf ( sic! ) emit ;
   
 \ : backspaces  0 ?DO  #bs emit  LOOP ;  \ : backspaces  0 ?DO  #bs emit  LOOP ;
 : >string  ( span addr pos1 -- span addr pos1 addr2 len )  
   over 3 pick 2 pick chars /string ;  : (ins) ( max span addr pos1 key -- max span addr pos2 )
 : type-rest ( span addr pos1 -- span addr pos1 back )      >r 2dup + r@ swap c! r> emit 1+ rot 1+ -rot ;
   >string tuck type ;  : (bs) ( max span addr pos1 -- max span addr pos2 flag )
 : (del)  ( max span addr pos1 -- max span addr pos2 )      dup IF
   1- >string over 1+ -rot move          #bs emit bl emit #bs emit 1- rot 1- -rot
   rot 1- -rot  #bs emit  type-rest bl emit 1+ backspaces ;      THEN false ;
 : (ins)  ( max span addr pos1 char -- max span addr pos2 )  : (ret)  true space ;
   >r >string over 1+ swap move 2dup chars + r> swap c!  
   rot 1+ -rot type-rest 1- backspaces 1+ ;  
 : ?del ( max span addr pos1 -- max span addr pos2 0 )  
   dup  IF  (del)  THEN  0 ;  
 : (ret)  type-rest drop true space ;  
 : back  dup  IF  1- #bs emit  ELSE  #bell emit  THEN 0 ;  
 : forw 2 pick over <> IF  2dup + c@ emit 1+  ELSE  #bell emit  THEN 0 ;  
 : eof  2 pick 0=  IF  bye  ELSE  (ret)  THEN ;  
   
 Create ctrlkeys  Create ctrlkeys
   ] false false back  false  eof   false forw  false    ] false false false false  false false false false
     ?del  false (ret) false  false (ret) false false      (bs)  false (ret) false  false (ret) false false
     false false false false  false false false false      false false false false  false false false false
     false false false false  false false false false [      false false false false  false false false false [
   
   defer insert-char
   ' (ins) IS insert-char
 defer everychar  defer everychar
 ' noop IS everychar  ' noop IS everychar
   
 : decode ( max span addr pos1 key -- max span addr pos2 flag )  : decode ( max span addr pos1 key -- max span addr pos2 flag )
   everychar    everychar
   dup #del = IF  drop #bs  THEN  \ del is rubout    dup #del = IF  drop #bs  THEN  \ del is rubout
   dup bl <   IF  cells ctrlkeys + @ execute  EXIT  THEN    dup bl <   IF  cells ctrlkeys + perform  EXIT  THEN
   >r 2over = IF  rdrop bell 0 EXIT  THEN    >r 2over = IF  rdrop bell 0 EXIT  THEN
   r> (ins) 0 ;    r> insert-char 0 ;
   
 \ decode should better use a table for control key actions  
 \ to define keyboard bindings later  
   
 : accept   ( addr len -- len ) \ core  : accept   ( addr len -- len ) \ core
   dup 0< IF    abs over dup 1 chars - c@ tuck type     dup 0< IF    abs over dup 1 chars - c@ tuck type 
Line 1430  create pathfilenamebuf 256 chars allot \ Line 1452  create pathfilenamebuf 256 chars allot \
 \   ELSE   false  \   ELSE   false
 \   THEN ;  \   THEN ;
   
   : absolut-path? ( addr u -- flag ) \ gforth
       \ a path is absolute, if it starts with a / or a ~ (~ expansion),
       \ or if it is in the form ./* or ../*, extended regexp: [/~]|./|../
       \ Pathes simply containing a / are not absolute!
       over c@ '/ = >r
       over c@ '~ = >r
       2dup 2 min S" ./" compare 0= >r
            3 min S" ../" compare 0=
       r> r> r> or or or ;
   \   [char] / scan nip 0<> ;    
   
 : open-path-file ( c-addr1 u1 -- file-id c-addr2 u2 ) \ gforth  : open-path-file ( c-addr1 u1 -- file-id c-addr2 u2 ) \ gforth
     \ opens a file for reading, searching in the path for it (unless      \ opens a file for reading, searching in the path for it (unless
     \ the filename contains a slash); c-addr2 u2 is the full filename      \ the filename contains a slash); c-addr2 u2 is the full filename
Line 1439  create pathfilenamebuf 256 chars allot \ Line 1472  create pathfilenamebuf 256 chars allot \
     \ the path will usually contain dirs that are only readable for      \ the path will usually contain dirs that are only readable for
     \ the user      \ the user
     \ !! use file-status to determine access mode?      \ !! use file-status to determine access mode?
     2dup [char] / scan nip ( 0<> )      2dup absolut-path?
     if \ the filename contains a slash      if \ the filename contains a slash
         2dup r/o open-file throw ( c-addr1 u1 file-id )          2dup r/o open-file throw ( c-addr1 u1 file-id )
         -rot >r pathfilenamebuf r@ cmove ( file-id R: u1 )          -rot >r pathfilenamebuf r@ cmove ( file-id R: u1 )
Line 1568  create image-included-files  1 , A, ( po Line 1601  create image-included-files  1 , A, ( po
   
 : recurse ( compilation -- ; run-time ?? -- ?? ) \ core  : recurse ( compilation -- ; run-time ?? -- ?? ) \ core
     lastxt compile, ; immediate restrict      lastxt compile, ; immediate restrict
 : recursive ( -- ) \ gforth  ' reveal alias recursive ( -- ) \ gforth
     reveal last off ; immediate          immediate
   
 \ */MOD */                                              17may93jaw  \ */MOD */                                              17may93jaw
   
Line 1803  Defer 'cold ' noop IS 'cold Line 1836  Defer 'cold ' noop IS 'cold
 \ or space and stackspace overrides  \ or space and stackspace overrides
   
 \ 0 arg contains, however, the name of the program.  \ 0 arg contains, however, the name of the program.
   
   

Removed from v.1.52  
changed lines
  Added in v.1.60


FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>