Diff for /gforth/prims2x.fs between versions 1.5 and 1.47

version 1.5, 1994/07/21 10:52:49 version 1.47, 2000/09/23 15:06:02
Line 1 Line 1
   \ converts primitives to, e.g., C code 
   
   \ Copyright (C) 1995,1996,1997,1998,2000 Free Software Foundation, Inc.
   
   \ This file is part of Gforth.
   
   \ Gforth is free software; you can redistribute it and/or
   \ modify it under the terms of the GNU General Public License
   \ as published by the Free Software Foundation; either version 2
   \ of the License, or (at your option) any later version.
   
   \ This program is distributed in the hope that it will be useful,
   \ but WITHOUT ANY WARRANTY; without even the implied warranty of
   \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   \ GNU General Public License for more details.
   
   \ You should have received a copy of the GNU General Public License
   \ along with this program; if not, write to the Free Software
   \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
   
   
 \ This is not very nice (hard limits, no checking, assumes 1 chars = 1)  \ This is not very nice (hard limits, no checking, assumes 1 chars = 1)
   
 \ Optimizations:  \ Optimizations:
Line 21 Line 42
   
 warnings off  warnings off
   
 [IFUNDEF] vocabulary  include search-order.fs [THEN]  [IFUNDEF] vocabulary    \ we are executed just with kernel image
 include gray.fs                          \ load the rest that is needed
                           \ (require fails because this file is needed from a
                           \ different directory with the wordlibraries)
   include ./search.fs                     
   include ./extend.fs
   [THEN]
   
   [IFUNDEF] environment?
   include ./environ.fs
   [THEN]
   
   include ./gray.fs
   
 100 constant max-effect \ number of things on one side of a stack effect  100 constant max-effect \ number of things on one side of a stack effect
 4096 constant batch-size \ no meaning, just make sure it's >0  
 255 constant maxchar  255 constant maxchar
 maxchar 1+ constant eof-char  maxchar 1+ constant eof-char
 9 constant tab-char  #tab constant tab-char
 10 constant nl-char  #lf constant nl-char
   
 : read-whole-file ( c-addr1 file-id -- c-addr2 )  variable rawinput \ pointer to next character to be scanned
 \ reads the contents of the file file-id puts it into memory at c-addr1  variable endrawinput \ pointer to the end of the input (the char after the last)
 \ c-addr2 is the first address after the file block  variable cookedinput \ pointer to the next char to be parsed
   begin ( c-addr file-id )  variable line \ line number of char pointed to by input
     2dup batch-size swap read-file   1 line !
     if  2variable filename \ filename of original input file
       abort" I/O error"  0 0 filename 2!
     endif  2variable f-comment
     ( c-addr file-id actual-size ) rot over + -rot  0 0 f-comment 2!
     batch-size <>  variable skipsynclines \ are sync lines ("#line ...") invisible to the parser?
   until  skipsynclines on 
   drop ;  
   
 variable input \ pointer to next character to be parsed  
 variable endinput \ pointer to the end of the input (the char after the last)  
   
 : start ( -- addr )  : start ( -- addr )
  input @ ;   cookedinput @ ;
   
 : end ( addr -- addr u )  : end ( addr -- addr u )
  input @ over - ;   cookedinput @ over - ;
   
 variable output \ xt ( -- ) of output word  variable output \ xt ( -- ) of output word
   
Line 88  variable effect-in-end ( pointer ) Line 115  variable effect-in-end ( pointer )
 variable effect-out-end ( pointer )  variable effect-out-end ( pointer )
 2variable effect-in-size  2variable effect-in-size
 2variable effect-out-size  2variable effect-out-size
   variable c-line
   2variable c-filename
   variable name-line
   2variable name-filename
   2variable last-name-filename
   
 variable primitive-number -8 primitive-number !  variable primitive-number -10 primitive-number !
   Variable function-number 0 function-number !
   
 \ for several reasons stack items of a word are stored in a wordlist  \ for several reasons stack items of a word are stored in a wordlist
 \ since neither forget nor marker are implemented yet, we make a new  \ since neither forget nor marker are implemented yet, we make a new
Line 109  variable items Line 142  variable items
 eof-char max-member \ the whole character set + EOF  eof-char max-member \ the whole character set + EOF
   
 : getinput ( -- n )  : getinput ( -- n )
  input @   rawinput @ endrawinput @ =
  dup endinput @ =  
  if   if
    drop eof-char     eof-char
  else   else
    c@     cookedinput @ c@
  endif ;   endif ;
   
 :noname ( n -- )  :noname ( n -- )
Line 129  print-token ! Line 161  print-token !
  getinput member? ;   getinput member? ;
 ' testchar? test-vector !  ' testchar? test-vector !
   
   : checksyncline ( -- )
       \ when input points to a newline, check if the next line is a
       \ sync line.  If it is, perform the appropriate actions.
       rawinput @ >r
       s" #line " r@ over compare 0<> if
           rdrop 1 line +! EXIT
       endif
       0. r> 6 chars + 20 >number drop >r drop line ! r> ( c-addr )
       dup c@ bl = if
           char+ dup c@ [char] " <> abort" sync line syntax"
           char+ dup 100 [char] " scan drop swap 2dup - save-mem filename 2!
           char+
       endif
       dup c@ nl-char <> abort" sync line syntax"
       skipsynclines @ if
           dup char+ rawinput !
           rawinput @ c@ cookedinput @ c!
       endif
       drop ;
   
 : ?nextchar ( f -- )  : ?nextchar ( f -- )
  ?not? if      ?not? if
    ." syntax error" cr          filename 2@ type ." :" line @ 0 .r ." : syntax error, wrong char:"
    getinput . cr          getinput . cr
    input @ endinput @ over - 100 min type cr          rawinput @ endrawinput @ over - 100 min type cr
    abort          abort
  endif      endif
  input @ endinput @ <> if      rawinput @ endrawinput @ <> if
    1 input +!          rawinput @ c@
  endif ;          1 chars rawinput +!
           1 chars cookedinput +!
           nl-char = if
               checksyncline
           endif
           rawinput @ c@ cookedinput @ c!
       endif ;
   
 : charclass ( set "name" -- )  : charclass ( set "name" -- )
  ['] ?nextchar terminal ;   ['] ?nextchar terminal ;
Line 152  print-token ! Line 210  print-token !
   
 : ` ( -- terminal ) ( use: ` c )  : ` ( -- terminal ) ( use: ` c )
  ( creates anonymous terminal for the character c )   ( creates anonymous terminal for the character c )
  [compile] ascii singleton ['] ?nextchar make-terminal ;   char singleton ['] ?nextchar make-terminal ;
   
 char a char z ..  char A char Z ..  union char _ singleton union  charclass letter  char a char z ..  char A char Z ..  union char _ singleton union  charclass letter
 char 0 char 9 ..                                        charclass digit  char 0 char 9 ..                                        charclass digit
 bl singleton                                            charclass blank  bl singleton tab-char over add-member                   charclass white
 tab-char singleton                                      charclass tab  
 nl-char singleton eof-char over add-member complement   charclass nonl  nl-char singleton eof-char over add-member complement   charclass nonl
 nl-char singleton eof-char over add-member char : over add-member complement  charclass nocolonnl  nl-char singleton eof-char over add-member
 bl 1+ maxchar ..                                        charclass nowhite      char : over add-member complement                   charclass nocolonnl
   bl 1+ maxchar .. char \ singleton complement intersection
                                                           charclass nowhitebq
   bl 1+ maxchar ..                                        charclass nowhite
 char " singleton eof-char over add-member complement    charclass noquote  char " singleton eof-char over add-member complement    charclass noquote
 nl-char singleton                                       charclass nl  nl-char singleton                                       charclass nl
 eof-char singleton                                      charclass eof  eof-char singleton                                      charclass eof
Line 169  eof-char singleton     charclass eof Line 229  eof-char singleton     charclass eof
 (( letter (( letter || digit )) **  (( letter (( letter || digit )) **
 )) <- c-name ( -- )  )) <- c-name ( -- )
   
 nowhite ++  (( nowhitebq nowhite ** ))
 <- name ( -- )  <- name ( -- )
   
 (( ` \ nonl ** nl  Variable forth-flag
 )) <- comment ( -- )  Variable c-flag
   
 (( {{ effect-in }} (( {{ start }} c-name {{ end 2 pick item-name 2! item-descr + }} blank ** )) ** {{ effect-in-end ! }}  (( (( ` f || ` F )) {{ start }} nonl ** 
    ` - ` - blank **     {{ end forth-flag @ IF type cr ELSE 2drop THEN }}
    {{ effect-out }} (( {{ start }} c-name {{ end 2 pick item-name 2! item-descr + }} blank ** )) ** {{ effect-out-end ! }}  )) <- forth-comment ( -- )
   
   (( (( ` c || ` C )) {{ start }} nonl ** 
      {{ end c-flag @ IF type cr ELSE 2drop THEN }}
   )) <- c-comment ( -- )
   
   (( ` - nonl ** {{ 
           forth-flag @ IF ." [ELSE]" cr THEN
           c-flag @ IF ." #else" cr THEN }}
   )) <- else-comment
   
   (( ` + {{ start }} nonl ** {{ end
           dup
           IF      c-flag @
                   IF    ." #ifdef HAS_" bounds ?DO  I c@ toupper emit  LOOP cr
                   THEN
                   forth-flag @
                   IF  ." has? " type ."  [IF]"  cr THEN
           ELSE    2drop
               c-flag @      IF  ." #endif"  cr THEN
               forth-flag @  IF  ." [THEN]"  cr THEN
           THEN }}
   )) <- if-comment
   
   (( (( forth-comment || c-comment || else-comment || if-comment )) ?? nonl ** )) <- comment-body
   
   (( ` \ comment-body nl )) <- comment ( -- )
   
   (( {{ effect-in }} (( {{ start }} c-name {{ end 2 pick item-name 2! item-descr + }} white ** )) ** {{ effect-in-end ! }}
      ` - ` - white **
      {{ effect-out }} (( {{ start }} c-name {{ end 2 pick item-name 2! item-descr + }} white ** )) ** {{ effect-out-end ! }}
 )) <- stack-effect ( -- )  )) <- stack-effect ( -- )
   
 (( {{ s" " doc 2! s" " forth-code 2! }}  (( {{ s" " doc 2! s" " forth-code 2! }}
    (( comment || nl )) **     (( {{ line @ name-line ! filename 2@ name-filename 2! }}
    (( {{ start }} name {{ end 2dup forth-name 2! c-name 2! }}  tab ++        {{ start }} name {{ end 2dup forth-name 2! c-name 2! }}  white ++
       {{ start }} stack-effect {{ end stack-string 2! }} tab ++        ` ( white ** {{ start }} stack-effect {{ end stack-string 2! }} ` ) white **
         {{ start }} name {{ end wordset 2! }} tab **          {{ start }} name {{ end wordset 2! }} white **
         (( {{ start }}  c-name {{ end c-name 2! }} )) ??  nl          (( {{ start }}  c-name {{ end c-name 2! }} )) ??  nl
    ))     ))
    (( ` " ` "  {{ start }} (( noquote ++ ` " )) ++ {{ end 1- doc 2! }} ` " nl )) ??     (( ` " ` "  {{ start }} (( noquote ++ ` " )) ++ {{ end 1- doc 2! }} ` " nl )) ??
    {{ start }} (( nocolonnl nonl **  nl )) ** {{ end c-code 2! }}     {{ skipsynclines off line @ c-line ! filename 2@ c-filename 2! start }} (( nocolonnl nonl **  nl )) ** {{ end c-code 2! skipsynclines on }}
    (( ` :  nl     (( ` :  nl
       {{ start }} (( nonl ++  nl )) ++ {{ end forth-code 2! }}        {{ start }} (( nonl ++  nl )) ++ {{ end forth-code 2! }}
    )) ??     )) ?? {{ printprim }}
    (( nl || eof ))     (( nl || eof ))
 )) <- primitive ( -- )  )) <- primitive ( -- )
   
 (( (( primitive {{ printprim }} )) **  eof ))  (( (( comment || primitive || nl )) ** eof ))
 parser primitives2something  parser primitives2something
 warnings @ [IF]  warnings @ [IF]
 .( parser generated ok ) cr  .( parser generated ok ) cr
Line 204  warnings @ [IF] Line 294  warnings @ [IF]
 : primfilter ( file-id xt -- )  : primfilter ( file-id xt -- )
 \ fileid is for the input file, xt ( -- ) is for the output word  \ fileid is for the input file, xt ( -- ) is for the output word
  output !   output !
  here input !   here dup rawinput ! cookedinput !
  here swap read-whole-file   here unused rot read-file throw
  dup endinput !   dup here + endrawinput !
  here - allot   allot
  align   align
    checksyncline
   \ begin
   \     getinput dup eof-char = ?EXIT emit true ?nextchar
   \ again ;
  primitives2something ;   primitives2something ;
   
 \ types  \ types
Line 241  constant type-description Line 335  constant type-description
   
 : fetch-single ( item -- )  : fetch-single ( item -- )
  >r   >r
  r@ item-name 2@ type ."  = ("    r@ item-name 2@ type
    ."  = (" 
  r@ item-type @ type-c-name 2@ type ." ) "   r@ item-type @ type-c-name 2@ type ." ) "
  r@ item-d-offset @ effect-in-size 2@ data-stack-access ." ;" cr   r@ item-d-offset @ effect-in-size 2@ data-stack-access ." ;" cr
  rdrop ;    rdrop ; 
   
 : fetch-double ( item -- )  : fetch-double ( item -- )
  >r   >r
  ." {Double_Store _d; _d.cells.low = "   ." FETCH_DCELL("
    r@ item-name 2@ type ." , "
  r@ item-d-offset @ dup    effect-in-size 2@ data-stack-access   r@ item-d-offset @ dup    effect-in-size 2@ data-stack-access
  ." ; _d.cells.high = " 1+ effect-in-size 2@ data-stack-access ." ; "   ." , "                 1+ effect-in-size 2@ data-stack-access
  r@ item-name 2@ type ."  = _d.dcell;}" cr   ." );" cr
  rdrop ;   rdrop ;
   
 : fetch-float ( item -- )  : fetch-float ( item -- )
  >r   >r
  r@ item-name 2@ type ."  = "   r@ item-name 2@ type
    ."  = "
  \ ." (" r@ item-type @ type-c-name 2@ type ." ) "   \ ." (" r@ item-type @ type-c-name 2@ type ." ) "
  r@ item-f-offset @ effect-in-size 2@ fp-stack-access ." ;" cr   r@ item-f-offset @ effect-in-size 2@ fp-stack-access ." ;" cr
  rdrop ;   rdrop ;
Line 265  constant type-description Line 362  constant type-description
 \ f is true iff the offset of item is the same as on input  \ f is true iff the offset of item is the same as on input
  >r   >r
  r@ item-name 2@ items @ search-wordlist 0=   r@ item-name 2@ items @ search-wordlist 0=
  if   abort" bug"
    ." bug" cr abort  
  endif  
  execute @   execute @
  dup r@ =   dup r@ =
  if \ item first appeared in output   if \ item first appeared in output
Line 281  constant type-description Line 376  constant type-description
 \ true if item has the same offset as the input TOS  \ true if item has the same offset as the input TOS
  item-d-offset @ 1+ effect-in-size 2@ drop = ;   item-d-offset @ 1+ effect-in-size 2@ drop = ;
   
   : is-out-tos? ( item -- f )
   \ true if item has the same offset as the input TOS
    item-d-offset @ 1+ effect-out-size 2@ drop = ;
   
 : really-store-single ( item -- )  : really-store-single ( item -- )
  >r   >r
  r@ item-d-offset @ effect-out-size 2@ data-stack-access ."  = (Cell)"   r@ item-d-offset @ effect-out-size 2@ data-stack-access ."  = (Cell)"
Line 291  constant type-description Line 390  constant type-description
  >r   >r
  r@ d-same-as-in?   r@ d-same-as-in?
  if   if
    r@ is-in-tos?     r@ is-in-tos? r@ is-out-tos? xor
    if     if
      ." IF_TOS(" r@ really-store-single ." );" cr       ." IF_TOS(" r@ really-store-single ." );" cr
    endif     endif
Line 303  constant type-description Line 402  constant type-description
 : store-double ( item -- )  : store-double ( item -- )
 \ !! store optimization is not performed, because it is not yet needed  \ !! store optimization is not performed, because it is not yet needed
  >r   >r
  ." {Double_Store _d; _d.dcell = " r@ item-name 2@ type ." ; "   ." STORE_DCELL(" r@ item-name 2@ type ." , "
  r@ item-d-offset @ dup    effect-out-size 2@ data-stack-access    r@ item-d-offset @ dup    effect-out-size 2@ data-stack-access
  ."  = _d.cells.low; " 1+ effect-out-size 2@ data-stack-access   ." , "                 1+ effect-out-size 2@ data-stack-access
  ." = _d.cells.high;}" cr   ." );" cr
  rdrop ;   rdrop ;
   
 : f-same-as-in? ( item -- f )  : f-same-as-in? ( item -- f )
 \ f is true iff the offset of item is the same as on input  \ f is true iff the offset of item is the same as on input
  >r   >r
  r@ item-name 2@ items @ search-wordlist 0=   r@ item-name 2@ items @ search-wordlist 0=
  if   abort" bug"
    ." bug" cr abort  
  endif  
  execute @   execute @
  dup r@ =   dup r@ =
  if \ item first appeared in output   if \ item first appeared in output
Line 348  constant type-description Line 445  constant type-description
  endif   endif
  rdrop ;   rdrop ;
     
 : single-type ( -- xt n1 n2 )  : single-type ( -- xt1 xt2 n1 n2 )
  ['] fetch-single ['] store-single 1 0 ;   ['] fetch-single ['] store-single 1 0 ;
   
 : double-type ( -- xt n1 n2 )  : double-type ( -- xt1 xt2 n1 n2 )
  ['] fetch-double ['] store-double 2 0 ;   ['] fetch-double ['] store-double 2 0 ;
   
 : float-type ( -- xt n1 n2 )  : float-type ( -- xt1 xt2 n1 n2 )
  ['] fetch-float ['] store-float 0 1 ;   ['] fetch-float ['] store-float 0 1 ;
   
 : s, ( addr u -- )  : s, ( addr u -- )
Line 392  s" DFloat *" single-type starts-with df_ Line 489  s" DFloat *" single-type starts-with df_
 s" SFloat *"    single-type starts-with sf_  s" SFloat *"    single-type starts-with sf_
 s" Xt"          single-type starts-with xt  s" Xt"          single-type starts-with xt
 s" WID"         single-type starts-with wid  s" WID"         single-type starts-with wid
 s" F83Name *"   single-type starts-with f83name  s" struct F83Name *"    single-type starts-with f83name
   
 set-current  set-current
   
Line 407  set-current Line 504  set-current
    endif     endif
  -1 s+loop   -1 s+loop
  \ we did not find a type, abort   \ we did not find a type, abort
  ." unknown type prefix" cr ABORT ;   true abort" unknown type prefix" ;
   
 : declare ( addr "name" -- )  : declare ( addr "name" -- )
 \ remember that there is a stack item at addr called name  \ remember that there is a stack item at addr called name
Line 429  set-current Line 526  set-current
   i declaration    i declaration
  item-descr +loop ;   item-descr +loop ;
   
   : fetch ( addr -- )
    dup item-type @ type-fetch-handler execute ;
   
 : declarations ( -- )  : declarations ( -- )
  wordlist dup items ! set-current   wordlist dup items ! set-current
  effect-in effect-in-end @ declaration-list   effect-in effect-in-end @ declaration-list
Line 480  set-current Line 580  set-current
    ." IF_TOS(TOS = sp[0]);" cr     ." IF_TOS(TOS = sp[0]);" cr
  endif ;   endif ;
   
 : fetch ( addr -- )  
  dup item-type @ type-fetch-handler execute ;  
   
 : fetches ( -- )  : fetches ( -- )
  effect-in-end @ effect-in ?do   effect-in-end @ effect-in ?do
    i fetch     i fetch
  item-descr +loop ;    item-descr +loop ; 
   
 : stack-pointer-updates ( -- )  : stack-pointer-updates ( -- )
 \ we do not check if an update is a noop; gcc does this for us  \ we need not check if an update is a noop; gcc does this for us
  effect-in-size 2@   effect-in-size 2@
  effect-out-size 2@   effect-out-size 2@
  rot swap - ( d-in d-out f-diff )   rot swap - ( d-in d-out f-diff )
Line 507  set-current Line 604  set-current
    i store     i store
  item-descr +loop ;    item-descr +loop ; 
   
 : output-c ( -- )  : .stack-list ( start end -- )
  ." I_" c-name 2@ type ." :     /* " forth-name 2@ type ."  ( " stack-string 2@ type ."  ) */" cr   swap ?do
      i item-name 2@ type space
    item-descr +loop ; 
   
   : output-c ( -- ) 
    ." I_" c-name 2@ type ." :     /* " forth-name 2@ type ."  ( " stack-string 2@ type ." ) */" cr
  ." /* " doc 2@ type ."  */" cr   ." /* " doc 2@ type ."  */" cr
    ." NAME(" [char] " emit forth-name 2@ type [char] " emit ." )" cr \ debugging
  ." {" cr   ." {" cr
  ." DEF_CA" cr   ." DEF_CA" cr
  declarations   declarations
  compute-offsets \ for everything else   compute-offsets \ for everything else
    ." NEXT_P0;" cr
  flush-tos   flush-tos
  fetches   fetches
  stack-pointer-updates cr   stack-pointer-updates
  ." NAME(" [char] " emit forth-name 2@ type [char] " emit ." )" cr \ debugging  
  ." {" cr   ." {" cr
    ." #line " c-line @ . [char] " emit c-filename 2@ type [char] " emit cr
  c-code 2@ type   c-code 2@ type
  ." }" cr   ." }" cr
  ." NEXT_P1;" cr   ." NEXT_P1;" cr
  stores   stores
  fill-tos   fill-tos
  ." NEXT1_P2;" cr   ." NEXT_P2;" cr
  ." }" cr   ." }" cr
  cr   cr
 ;  ;
   
 : output-label ( -- )  : dstack-used?
  ." &&I_" c-name 2@ type ." ," cr ;    effect-in-size 2@ drop
     effect-out-size 2@ drop max 0<> ;
 : output-alias ( -- )  
  primitive-number @ . ." alias " forth-name 2@ type cr  : fstack-used?
  -1 primitive-number +! ;    effect-in-size 2@ nip
     effect-out-size 2@ nip max 0<> ;
   
   : output-funclabel ( -- )
     1 function-number +!
     ." &I_" c-name 2@ type ." ," cr ;
   
   : output-forthname ( -- )
     1 function-number +!
     '" emit forth-name 2@ type '" emit ." ," cr ;
   
   : output-c-func ( -- )
   \ used for word libraries
       1 function-number +!
       ." Cell * I_" c-name 2@ type ." (Cell *SP, Cell **FP)      /* " forth-name 2@ type
       ."  ( " stack-string 2@ type ."  ) */" cr
       ." /* " doc 2@ type ."  */" cr
       ." NAME(" [char] " emit forth-name 2@ type [char] " emit ." )" cr
       \ debugging
       ." {" cr
       declarations
       compute-offsets \ for everything else
       dstack-used? IF ." Cell *sp=SP;" cr THEN
       fstack-used? IF ." Cell *fp=*FP;" cr THEN
       flush-tos
       fetches
       stack-pointer-updates
       fstack-used? IF ." *FP=fp;" cr THEN
       ." {" cr
       ." #line " c-line @ . [char] " emit c-filename 2@ type [char] " emit cr
       c-code 2@ type
       ." }" cr
       stores
       fill-tos
       ." return (sp);" cr
       ." }" cr
       cr ;
   
   : output-label ( -- )  
       ." (Label)&&I_" c-name 2@ type ." ," cr
       -1 primitive-number +! ;
   
   : output-alias ( -- ) 
       ( primitive-number @ . ." alias " ) ." Primitive " forth-name 2@ type cr
       -1 primitive-number +! ;
   
   : output-forth ( -- )  
       forth-code @ 0=
       IF          \ output-alias
           \ this is bad for ec: an alias is compiled if tho word does not exist!
           \ JAW
       ELSE  ." : " forth-name 2@ type ."   ( "
           effect-in effect-in-end @ .stack-list ." -- "
           effect-out effect-out-end @ .stack-list ." )" cr
           forth-code 2@ type cr
           -1 primitive-number +!
       THEN ;
   
   : output-tag-file ( -- )
       name-filename 2@ last-name-filename 2@ compare if
           name-filename 2@ last-name-filename 2!
           #ff emit cr
           name-filename 2@ type
           ." ,0" cr
       endif ;
   
   : output-tag ( -- )
       output-tag-file
       forth-name 2@ 1+ type
       127 emit
       space forth-name 2@ type space
       1 emit
       name-line @ 0 .r
       ." ,0" cr ;
   
   [IFDEF] documentation
   : register-doc ( -- )
       get-current documentation set-current
       forth-name 2@ nextname create
       forth-name 2@ 2,
       stack-string 2@ condition-stack-effect 2,
       wordset 2@ 2,
       c-name 2@ condition-pronounciation 2,
       doc 2@ 2,
       set-current ;
   [THEN]
   
 : process-file ( addr u xt -- )  : process-file ( addr u xt -- )
  >r r/o open-file      >r
  if      2dup filename 2!
    ." cannot open file" cr abort      0 function-number !
  endif      r/o open-file abort" cannot open file"
  warnings @ if      warnings @ if
  ." ------------ CUT HERE -------------" cr  endif          ." ------------ CUT HERE -------------" cr  endif
  r> primfilter ;      r> primfilter ;
   
   : process      ( xt -- )
       bl word count rot
       process-file ;

Removed from v.1.5  
changed lines
  Added in v.1.47


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