Diff for /gforth/prims2x.fs between versions 1.120 and 1.143

version 1.120, 2002/10/12 19:06:37 version 1.143, 2003/08/27 12:13:49
Line 1 Line 1
 \ converts primitives to, e.g., C code   \ converts primitives to, e.g., C code 
   
 \ Copyright (C) 1995,1996,1997,1998,2000 Free Software Foundation, Inc.  \ Copyright (C) 1995,1996,1997,1998,2000,2003 Free Software Foundation, Inc.
   
 \ This file is part of Gforth.  \ This file is part of Gforth.
   
Line 51 Line 51
 \ (stack-in-index-xt and a test for stack==instruction-stream); there  \ (stack-in-index-xt and a test for stack==instruction-stream); there
 \ should be only one.  \ should be only one.
   
   \ for backwards compatibility, jaw
   require compat/strcomp.fs
   
 warnings off  warnings off
   
   \ redefinitions of kernel words not present in gforth-0.6.1
   : latestxt lastcfa @ ;
   : latest last @ ;
   
 [IFUNDEF] try  [IFUNDEF] try
 include startup.fs  include startup.fs
 [THEN]  [THEN]
Line 63  warnings off Line 70  warnings off
 \ warnings on  \ warnings on
   
 include ./gray.fs  include ./gray.fs
 32 constant max-effect \ number of things on one side of a stack effect  128 constant max-effect \ number of things on one side of a stack effect
 4 constant max-stacks  \ the max. number of stacks (including inst-stream).  4 constant max-stacks  \ the max. number of stacks (including inst-stream).
 255 constant maxchar  255 constant maxchar
 maxchar 1+ constant eof-char  maxchar 1+ constant eof-char
Line 95  variable include-skipped-insts Line 102  variable include-skipped-insts
 \ inline arguments (false)  \ inline arguments (false)
 include-skipped-insts off  include-skipped-insts off
   
   variable immarg \ values for immediate arguments (to be used in IMM_ARG macros)
   $12340000 immarg !
   
 : th ( addr1 n -- addr2 )  : th ( addr1 n -- addr2 )
     cells + ;      cells + ;
   
Line 159  struct% Line 169  struct%
     cell% 2* field stack-pointer \ stackpointer name      cell% 2* field stack-pointer \ stackpointer name
     cell%    field stack-type \ name for default type of stack items      cell%    field stack-type \ name for default type of stack items
     cell%    field stack-in-index-xt \ ( in-size item -- in-index )      cell%    field stack-in-index-xt \ ( in-size item -- in-index )
       cell%    field stack-access-transform \ ( nitem -- index )
 end-struct stack%  end-struct stack%
   
 struct%  struct%
Line 194  create stacks max-stacks cells allot \ a Line 205  create stacks max-stacks cells allot \ a
     1 next-stack-number +!      1 next-stack-number +!
     r@ stack-type !      r@ stack-type !
     save-mem r@ stack-pointer 2!       save-mem r@ stack-pointer 2! 
     ['] stack-in-index r> stack-in-index-xt ! ;      ['] stack-in-index r@ stack-in-index-xt !
       ['] noop r@ stack-access-transform !
       rdrop ;
   
 : map-stacks { xt -- }  : map-stacks { xt -- }
     \ perform xt for all stacks      \ perform xt for all stacks
Line 316  variable name-line Line 329  variable name-line
 2variable name-filename  2variable name-filename
 2variable last-name-filename  2variable last-name-filename
 Variable function-number 0 function-number !  Variable function-number 0 function-number !
   Variable function-old 0 function-old !
   : function-diff ( n -- )
       ." GROUPADD(" function-number @ function-old @ - 0 .r ." )" cr
       function-number @ function-old ! ;
   : forth-fdiff ( -- )
       function-number @ function-old @ - 0 .r ."  groupadd" cr
       function-number @ function-old ! ;
   
 \ a few more set ops  \ a few more set ops
   
Line 325  Variable function-number 0 function-numb Line 345  Variable function-number 0 function-numb
 : complement ( set1 -- set2 )  : complement ( set1 -- set2 )
  empty ['] bit-equivalent binary-set-operation ;   empty ['] bit-equivalent binary-set-operation ;
   
   \ forward declaration for inst-stream (breaks cycle in definitions)
   defer inst-stream-f ( -- stack )
   
 \ stack access stuff  \ stack access stuff
   
 : normal-stack-access ( n stack -- )  : normal-stack-access0 { n stack -- }
     stack-pointer 2@ type      n stack stack-access-transform @ execute ." [" 0 .r ." ]" ;
     dup      
     if  : normal-stack-access1 { n stack -- }
         ." [" 0 .r ." ]"      stack stack-pointer 2@ type
       n if
           n stack normal-stack-access0
     else      else
         drop ." TOS"          ." TOS"
     endif ;      endif ;
   
 \ forward declaration for inst-stream (breaks cycle in definitions)  : normal-stack-access ( n stack -- )
 defer inst-stream-f ( -- stack )      dup inst-stream-f = if
           ." IMM_ARG(" normal-stack-access1 ." ," immarg ? ." )"
           1 immarg +!
       else
           normal-stack-access1
       endif ;
   
 : stack-depth { stack -- n }  : stack-depth { stack -- n }
     current-depth stack stack-number @ th @ ;      current-depth stack stack-number @ th @ ;
Line 592  wordlist constant type-names \ this is h Line 622  wordlist constant type-names \ this is h
     get-current type-names set-current      get-current type-names set-current
     stack-type 2dup nextname stack-type-name      stack-type 2dup nextname stack-type-name
     set-current      set-current
     stack-pointer lastxt >body stack-name nextname make-stack ;      stack-pointer latestxt >body stack-name nextname make-stack ;
   
 stack inst-stream IP Cell  stack inst-stream IP Cell
 ' inst-in-index inst-stream stack-in-index-xt !  ' inst-in-index inst-stream stack-in-index-xt !
Line 615  stack inst-stream IP Cell Line 645  stack inst-stream IP Cell
 : compute-offset-out ( addr1 addr2 -- )  : compute-offset-out ( addr1 addr2 -- )
     ['] stack-out compute-offset ;      ['] stack-out compute-offset ;
   
 : clear-stack ( stack -- )  
     dup stack-in off stack-out off ;  
   
 : compute-offsets ( -- )  : compute-offsets ( -- )
     ['] clear-stack map-stacks      prim prim-stacks-in  max-stacks cells erase
       prim prim-stacks-out max-stacks cells erase
     prim prim-effect-in  prim prim-effect-in-end  @ ['] compute-offset-in  map-items      prim prim-effect-in  prim prim-effect-in-end  @ ['] compute-offset-in  map-items
     prim prim-effect-out prim prim-effect-out-end @ ['] compute-offset-out map-items      prim prim-effect-out prim prim-effect-out-end @ ['] compute-offset-out map-items
     inst-stream stack-out @ 0= s" # can only be on the input side" ?print-error ;      inst-stream stack-out @ 0= s" # can only be on the input side" ?print-error ;
Line 634  stack inst-stream IP Cell Line 662  stack inst-stream IP Cell
     stack stack-out @ 0<> stack stack-in @ 0= and      stack stack-out @ 0<> stack stack-in @ 0= and
     if      if
         ." IF_" stack stack-pointer 2@ 2dup type ." TOS("          ." IF_" stack stack-pointer 2@ 2dup type ." TOS("
         2dup type ." [0] = " type ." TOS);" cr          2dup type 0 stack normal-stack-access0 ."  = " type ." TOS);" cr
     endif ;      endif ;
   
 : flush-tos ( -- )  : flush-tos ( -- )
Line 644  stack inst-stream IP Cell Line 672  stack inst-stream IP Cell
     stack stack-out @ 0= stack stack-in @ 0<> and      stack stack-out @ 0= stack stack-in @ 0<> and
     if      if
         ." IF_" stack stack-pointer 2@ 2dup type ." TOS("          ." IF_" stack stack-pointer 2@ 2dup type ." TOS("
         2dup type ." TOS = " type ." [0]);" cr          2dup type ." TOS = " type 0 stack normal-stack-access0 ." );" cr
     endif ;      endif ;
   
 : fill-tos ( -- )  : fill-tos ( -- )
Line 657  stack inst-stream IP Cell Line 685  stack inst-stream IP Cell
 : fetches ( -- )  : fetches ( -- )
     prim prim-effect-in prim prim-effect-in-end @ ['] fetch map-items ;      prim prim-effect-in prim prim-effect-in-end @ ['] fetch map-items ;
   
   : stack-update-transform ( n1 stack -- n2 )
       \ n2 is the number by which the stack pointer should be
       \ incremented to pop n1 items
       stack-access-transform @ dup >r execute
       0 r> execute - ;
   
 : stack-pointer-update { stack -- }  : stack-pointer-update { stack -- }
     \ stack grow downwards      \ stacks grow downwards
     stack stack-diff      stack stack-diff
     ?dup-if \ this check is not necessary, gcc would do this for us      ?dup-if \ this check is not necessary, gcc would do this for us
         stack inst-stream = if          stack inst-stream = if
             ." INC_IP(" 0 .r ." );" cr              ." INC_IP(" 0 .r ." );" cr
         else          else
             stack stack-pointer 2@ type ."  += " 0 .r ." ;" cr              stack stack-pointer 2@ type ."  += "
               stack stack-update-transform 0 .r ." ;" cr
         endif          endif
     endif ;      endif ;
   
Line 713  stack inst-stream IP Cell Line 748  stack inst-stream IP Cell
     endif      endif
     2drop ;      2drop ;
   
   : output-nextp2 ( -- )
       ." NEXT_P2;" cr ;
   
   variable tail-nextp2 \ xt to execute for printing NEXT_P2 in INST_TAIL
   ' output-nextp2 tail-nextp2 !
   
 : output-label2 ( -- )  : output-label2 ( -- )
     ." LABEL2(" prim prim-c-name 2@ type ." )" cr ;      ." LABEL2(" prim prim-c-name 2@ type ." )" cr
       ." NEXT_P2;" cr ;
   
 : output-c-tail1 { xt -- }  : output-c-tail1 { xt -- }
     \ the final part of the generated C code, with xt printing LABEL2 or not.      \ the final part of the generated C code, with xt printing LABEL2 or not.
Line 723  stack inst-stream IP Cell Line 765  stack inst-stream IP Cell
     ." NEXT_P1;" cr      ." NEXT_P1;" cr
     stores      stores
     fill-tos       fill-tos 
     xt execute      xt execute ;
     ." NEXT_P2;" cr ;  
   
 : output-c-tail1-no-stores { xt -- }  : output-c-tail1-no-stores { xt -- }
     \ the final part of the generated C code for combinations      \ the final part of the generated C code for combinations
     output-super-end      output-super-end
     ." NEXT_P1;" cr      ." NEXT_P1;" cr
     fill-tos       fill-tos 
     xt execute      xt execute ;
     ." NEXT_P2;" cr ;  
   
 : output-c-tail ( -- )  : output-c-tail ( -- )
     ['] noop output-c-tail1 ;      tail-nextp2 @ output-c-tail1 ;
   
 : output-c-tail2 ( -- )  : output-c-tail2 ( -- )
     ['] output-label2 output-c-tail1 ;      ['] output-label2 output-c-tail1 ;
   
 : output-c-tail-no-stores ( -- )  : output-c-tail-no-stores ( -- )
     ['] noop output-c-tail1-no-stores ;      tail-nextp2 @ output-c-tail1-no-stores ;
   
 : output-c-tail2-no-stores ( -- )  : output-c-tail2-no-stores ( -- )
     ['] output-label2 output-c-tail1-no-stores ;      ['] output-label2 output-c-tail1-no-stores ;
Line 836  stack inst-stream IP Cell Line 876  stack inst-stream IP Cell
     endif      endif
     ." }" cr ;      ." }" cr ;
   
   : prim-branch? { prim -- f }
       \ true if prim is a branch or super-end
       prim prim-c-code 2@  s" SET_IP" search nip nip 0<> ;
   
 : output-superend ( -- )  : output-superend ( -- )
     \ output flag specifying whether the current word ends a dynamic superinst      \ output flag specifying whether the current word ends a dynamic superinst
     prim prim-c-code 2@  s" SET_IP"    search nip nip      prim prim-branch?
     prim prim-c-code 2@  s" SUPER_END" search nip nip or 0<>      prim prim-c-code 2@  s" SUPER_END" search nip nip 0<> or
     prim prim-c-code 2@  s" SUPER_CONTINUE" search nip nip 0= and      prim prim-c-code 2@  s" SUPER_CONTINUE" search nip nip 0= and
     negate 0 .r ." , /* " prim prim-name 2@ type ."  */" cr ;      negate 0 .r ." , /* " prim prim-name 2@ type ."  */" cr ;
   
Line 912  stack inst-stream IP Cell Line 956  stack inst-stream IP Cell
 : output-alias ( -- )   : output-alias ( -- ) 
     ( primitive-number @ . ." alias " ) ." Primitive " prim prim-name 2@ type cr ;      ( primitive-number @ . ." alias " ) ." Primitive " prim prim-name 2@ type cr ;
   
 : output-prim-num ( -- )  : output-c-prim-num ( -- )
     prim prim-num @ 8 + 4 .r space prim prim-name 2@ type cr ;      ." N_" prim prim-c-name 2@ type ." ," cr ;
   
 : output-forth ( -- )    : output-forth ( -- )  
     prim prim-forth-code @ 0=      prim prim-forth-code @ 0=
Line 1133  stack inst-stream IP Cell Line 1177  stack inst-stream IP Cell
 : print-item { n stack -- }  : print-item { n stack -- }
     \ print nth stack item name      \ print nth stack item name
     stack stack-type @ type-c-name 2@ type space      stack stack-type @ type-c-name 2@ type space
     ." _" stack stack-pointer 2@ type n 0 .r ;      ." MAYBE_UNUSED _" stack stack-pointer 2@ type n 0 .r ;
   
 : print-declarations-combined ( -- )  : print-declarations-combined ( -- )
     max-stacks 0 ?do      max-stacks 0 ?do
Line 1156  stack inst-stream IP Cell Line 1200  stack inst-stream IP Cell
     r> in-part ! ;      r> in-part ! ;
   
 : part-stack-pointer-updates ( -- )  : part-stack-pointer-updates ( -- )
     max-stacks 0 +do      next-stack-number @ 0 +do
         i part-num @ 1+ s-c-max-depth @ dup          i part-num @ 1+ s-c-max-depth @ dup
         i num-combined @ s-c-max-depth @ =    \ final depth          i num-combined @ s-c-max-depth @ =    \ final depth
         swap i part-num @ s-c-max-depth @ <> \ just reached now          swap i part-num @ s-c-max-depth @ <> \ just reached now
Line 1238  stack inst-stream IP Cell Line 1282  stack inst-stream IP Cell
 \    int loads;       /* number of stack loads */  \    int loads;       /* number of stack loads */
 \    int stores;      /* number of stack stores */  \    int stores;      /* number of stack stores */
 \    int updates;     /* number of stack pointer updates */  \    int updates;     /* number of stack pointer updates */
   \    int offset;      /* offset into super2 table */
 \    int length;      /* number of components */  \    int length;      /* number of components */
 \    int *components; /* array of vm_prim indexes of components */  
 \  };  \  };
   
 \ How do you know which primitive or combined instruction this  \ How do you know which primitive or combined instruction this
 \ structure refers to?  By the order of cost structures, as in most  \ structure refers to?  By the order of cost structures, as in most
 \ other cases.  \ other cases.
   
   : super2-length ( -- n )
       combined if
           num-combined @
       else
           1
       endif ;
   
 : compute-costs { p -- nloads nstores nupdates }  : compute-costs { p -- nloads nstores nupdates }
     \ compute the number of loads, stores, and stack pointer updates      \ compute the number of loads, stores, and stack pointer updates
     \ of a primitive or combined instruction; does not take TOS      \ of a primitive or combined instruction; does not take TOS
     \ caching into account, nor that IP updates are combined with      \ caching into account
     \ other stuff  
     0 max-stacks 0 +do      0 max-stacks 0 +do
         p prim-stacks-in i th @ +          p prim-stacks-in i th @ +
     loop      loop
       super2-length 1- - \ don't count instruction fetches of subsumed insts
     0 max-stacks 0 +do      0 max-stacks 0 +do
         p prim-stacks-out i th @ +          p prim-stacks-out i th @ +
     loop      loop
     0 max-stacks 0 +do      0 max-stacks 1 +do \ don't count ip updates, therefore "1 +do"
         p prim-stacks-in i th @ p prim-stacks-out i th @ <> -          p prim-stacks-in i th @ p prim-stacks-out i th @ <> -
     loop ;      loop ;
   
 : output-num-part ( p -- )  : output-num-part ( p -- )
     prim-num @ 4 .r ." ," ;      ." N_" prim-c-name 2@ type ." ," ;
       \ prim-num @ 4 .r ." ," ;
   
   : output-name-comment ( -- )
       ."  /* " prim prim-name 2@ type ."  */" ;
   
   variable offset-super2  0 offset-super2 ! \ offset into the super2 table
   
   : output-costs-prefix ( -- )
       ." {" prim compute-costs
       rot 2 .r ." ," swap 2 .r ." ," 2 .r ." , "
       prim prim-branch? negate . ." ," ;
   
   : output-costs-gforth-simple ( -- )
       output-costs-prefix
       prim output-num-part
       1 2 .r ." },"
       output-name-comment
       cr ;
   
   : output-costs-gforth-combined ( -- )
       output-costs-prefix
       ." N_START_SUPER+" offset-super2 @ 5 .r ." ,"
       super2-length dup 2 .r ." }," offset-super2 +!
       output-name-comment
       cr ;
   
 : output-costs ( -- )  : output-costs ( -- )
       \ description of superinstructions and simple instructions
     ." {" prim compute-costs      ." {" prim compute-costs
     rot 2 .r ." ," swap 2 .r ." ," 2 .r ." ,"      rot 2 .r ." ," swap 2 .r ." ," 2 .r ." ,"
       offset-super2 @ 5 .r ." ,"
       super2-length dup 2 .r ." }," offset-super2 +!
       output-name-comment
       cr ;
   
   : output-super2 ( -- )
       \ table of superinstructions without requirement for existing prefixes
     combined if      combined if
         num-combined @ 2 .r          ['] output-num-part map-combined 
         ." , ((int []){" ['] output-num-part map-combined ." })}, /* "  
     else      else
         ."  1, ((int []){" prim prim-num @ 4 .r ." })}, /* "          prim output-num-part
     endif      endif
     prim prim-name 2@ type ."  */"      output-name-comment
     cr ;      cr ;   
   
 \ the parser  \ the parser
   
Line 1300  print-token ! Line 1383  print-token !
  getinput member? ;   getinput member? ;
 ' testchar? test-vector !  ' testchar? test-vector !
   
 : checksyncline ( -- )  : checksynclines ( -- )
     \ when input points to a newline, check if the next line is a      \ when input points to a newline, check if the next line is a
     \ sync line.  If it is, perform the appropriate actions.      \ sync line.  If it is, perform the appropriate actions.
     rawinput @ >r      rawinput @ begin >r
     s" #line " r@ over compare if          s" #line " r@ over compare if
         rdrop 1 line +! EXIT              rdrop 1 line +! EXIT
     endif          endif
     0. r> 6 chars + 20 >number drop >r drop line ! r> ( c-addr )          0. r> 6 chars + 20 >number drop >r drop line ! r> ( c-addr )
     dup c@ bl = if          dup c@ bl = if
         char+ dup c@ [char] " <> 0= s" sync line syntax" ?print-error              char+ dup c@ [char] " <> 0= s" sync line syntax" ?print-error
         char+ dup 100 [char] " scan drop swap 2dup - save-mem filename 2!              char+ dup 100 [char] " scan drop swap 2dup - save-mem filename 2!
         char+              char+
     endif          endif
     dup c@ nl-char <> 0= s" sync line syntax" ?print-error          dup c@ nl-char <> 0= s" sync line syntax" ?print-error
     skipsynclines @ if          skipsynclines @ if
         dup char+ rawinput !              char+ dup rawinput !
         rawinput @ c@ cookedinput @ c!              rawinput @ c@ cookedinput @ c!
     endif          endif
     drop ;      again ;
   
 : ?nextchar ( f -- )  : ?nextchar ( f -- )
     s" syntax error, wrong char" ?print-error      s" syntax error, wrong char" ?print-error
Line 1327  print-token ! Line 1410  print-token !
         1 chars rawinput +!          1 chars rawinput +!
         1 chars cookedinput +!          1 chars cookedinput +!
         nl-char = if          nl-char = if
             checksyncline              checksynclines
             rawinput @ line-start !              rawinput @ line-start !
         endif          endif
         rawinput @ c@ cookedinput @ c!          rawinput @ c@
           cookedinput @ c!
     endif ;      endif ;
   
 : charclass ( set "name" -- )  : charclass ( set "name" -- )
Line 1388  Variable c-flag Line 1472  Variable c-flag
 )) <- c-comment ( -- )  )) <- c-comment ( -- )
   
 (( ` - nonl ** {{   (( ` - nonl ** {{ 
         forth-flag @ IF ." [ELSE]" cr THEN          forth-flag @ IF forth-fdiff ." [ELSE]" cr THEN
         c-flag @ IF ." #else" cr THEN }}          c-flag @ IF
               function-diff
               ." #else /* " function-number @ 0 .r ."  */" cr THEN }}
 )) <- else-comment  )) <- else-comment
   
 (( ` + {{ start }} nonl ** {{ end  (( ` + {{ start }} nonl ** {{ end
         dup          dup
         IF      c-flag @          IF      c-flag @
                 IF    ." #ifdef HAS_" bounds ?DO  I c@ toupper emit  LOOP cr              IF
                   function-diff
                   ." #ifdef HAS_" bounds ?DO  I c@ toupper emit  LOOP cr
                 THEN                  THEN
                 forth-flag @                  forth-flag @
                 IF  ." has? " type ."  [IF]"  cr THEN                  IF  forth-fdiff  ." has? " type ."  [IF]"  cr THEN
         ELSE    2drop          ELSE    2drop
             c-flag @      IF  ." #endif"  cr THEN              c-flag @      IF
             forth-flag @  IF  ." [THEN]"  cr THEN                  function-diff  ." #endif" cr THEN
               forth-flag @  IF  forth-fdiff  ." [THEN]"  cr THEN
         THEN }}          THEN }}
 )) <- if-comment  )) <- if-comment
   
 (( (( ` g || ` G )) {{ start }} nonl **  (( (( ` g || ` G )) {{ start }} nonl **
    {{ end     {{ end
       forth-flag @ IF  ." group " type cr  THEN        forth-flag @ IF  forth-fdiff  ." group " type cr  THEN
       c-flag @     IF  ." GROUP(" type ." )" cr  THEN }}        c-flag @     IF  function-diff
             ." GROUP(" type ." , " function-number @ 0 .r ." )" cr  THEN }}
 )) <- group-comment  )) <- group-comment
   
 (( (( eval-comment || forth-comment || c-comment || else-comment || if-comment || group-comment )) ?? nonl ** )) <- comment-body  (( (( eval-comment || forth-comment || c-comment || else-comment || if-comment || group-comment )) ?? nonl ** )) <- comment-body
Line 1450  Variable c-flag Line 1540  Variable c-flag
       start }} [ifdef] vmgen c-ident [else] forth-ident [then] {{ end        start }} [ifdef] vmgen c-ident [else] forth-ident [then] {{ end
       2dup prim prim-name 2! prim prim-c-name 2! }}  white **        2dup prim prim-name 2! prim prim-c-name 2! }}  white **
    (( ` / white ** {{ start }} c-ident {{ end prim prim-c-name 2! }} white ** )) ??     (( ` / white ** {{ start }} c-ident {{ end prim prim-c-name 2! }} white ** )) ??
    (( simple-primitive || combined-primitive )) {{ 1 function-number +! }}     (( simple-primitive || combined-primitive ))
      {{ 1 function-number +! }}
 )) <- primitive ( -- )  )) <- primitive ( -- )
   
 (( (( comment || primitive || nl white ** )) ** eof ))  (( (( comment || primitive || nl white ** )) ** eof ))
Line 1475  warnings @ [IF] Line 1566  warnings @ [IF]
     \ process the string at addr u      \ process the string at addr u
     over dup rawinput ! dup line-start ! cookedinput !      over dup rawinput ! dup line-start ! cookedinput !
     + endrawinput !      + endrawinput !
     checksyncline      checksynclines
     primitives2something ;          primitives2something ;    
   
   : unixify ( c-addr u1 -- c-addr u2 )
       \ delete crs from the string
       bounds tuck tuck ?do ( c-addr1 )
           i c@ dup #cr <> if
               over c! char+
           else
               drop
           endif
       loop
       over - ;
   
 : process-file ( addr u xt-simple x-combined -- )  : process-file ( addr u xt-simple x-combined -- )
     output-combined ! output !      output-combined ! output !
     save-mem 2dup filename 2!      save-mem 2dup filename 2!
     slurp-file      slurp-file unixify
     warnings @ if      warnings @ if
         ." ------------ CUT HERE -------------" cr  endif          ." ------------ CUT HERE -------------" cr  endif
     primfilter ;      primfilter ;

Removed from v.1.120  
changed lines
  Added in v.1.143


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