Diff for /gforth/cross.fs between versions 1.82 and 1.151

version 1.82, 1999/12/30 20:43:25 version 1.151, 2006/01/29 18:34:33
Line 1 Line 1
 \ CROSS.FS     The Cross-Compiler                      06oct92py  \ CROSS.FS     The Cross-Compiler                      06oct92py
 \ Idea and implementation: Bernd Paysan (py)  \ Idea and implementation: Bernd Paysan (py)
   
 \ Copyright (C) 1995,1996,1997,1998,1999 Free Software Foundation, Inc.  \ Copyright (C) 1995,1996,1997,1998,1999,2000,2003,2004,2005 Free Software Foundation, Inc.
   
 \ This file is part of Gforth.  \ This file is part of Gforth.
   
Line 17 Line 17
   
 \ You should have received a copy of the GNU General Public License  \ You should have received a copy of the GNU General Public License
 \ along with this program; if not, write to the Free Software  \ along with this program; if not, write to the Free Software
 \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
   
 0   0 
 [IF]  [IF]
   
 ToDo:  ToDo:
 Crossdoc destination ./doc/crossdoc.fd makes no sense when  - Crossdoc destination ./doc/crossdoc.fd makes no sense when
 cross.fs is uses seperately. jaw    cross.fs is used seperately. jaw
 Do we need this char translation with >address and in branchoffset?   - Do we need this char translation with >address and in branchoffset? 
 (>body also affected) jaw    (>body also affected) jaw
 Clean up mark> and >resolve stuff jaw  
   
 [THEN]  [THEN]
   
   s" compat/strcomp.fs" included
   
 hex  hex
   
 \ debugging for compiling  \ debugging for compiling
Line 62  forth definitions Line 63  forth definitions
 : T  previous Ghosts also Target ; immediate  : T  previous Ghosts also Target ; immediate
 : G  Ghosts ; immediate  : G  Ghosts ; immediate
   
   
 : >cross  also Cross definitions previous ;  : >cross  also Cross definitions previous ;
 : >target also Target definitions previous ;  : >target also Target definitions previous ;
 : >minimal also Minimal definitions previous ;  : >minimal also Minimal definitions previous ;
Line 70  H Line 72  H
   
 >CROSS  >CROSS
   
   \ Test against this definitions to find out whether we are cross-compiling
   \ may be usefull for assemblers
   0 Constant gforth-cross-indicator
   
 \ find out whether we are compiling with gforth  \ find out whether we are compiling with gforth
   
 : defined? bl word find nip ;  : defined? bl word find nip ;
Line 201  Create bases   10 ,   2 ,   A , 100 , Line 207  Create bases   10 ,   2 ,   A , 100 ,
   
 [THEN]  [THEN]
   
   \ this provides assert( and struct stuff
   \GFORTH [IFUNDEF] assert1(
   \GFORTH also forth definitions require assert.fs previous
   \GFORTH [THEN]
   
   >CROSS
   
 hex     \ the defualt base for the cross-compiler is hex !!  hex     \ the defualt base for the cross-compiler is hex !!
 \ Warnings off  \ Warnings off
   
Line 241  hex     \ the defualt base for the cross Line 254  hex     \ the defualt base for the cross
   
 hex  hex
   
   \ FIXME delete`
 \ 1 Constant Cross-Flag \ to check whether assembler compiler plug-ins are  \ 1 Constant Cross-Flag \ to check whether assembler compiler plug-ins are
                         \ for cross-compiling                          \ for cross-compiling
 \ No! we use "[IFUNDEF]" there to find out whether we are target compiling!!!  \ No! we use "[IFUNDEF]" there to find out whether we are target compiling!!!
   
   \ FIXME move down
 : comment? ( c-addr u -- c-addr u )  : comment? ( c-addr u -- c-addr u )
         2dup s" (" compare 0=          2dup s" (" str=
         IF    postpone (          IF    postpone (
         ELSE  2dup s" \" compare 0= IF postpone \ THEN          ELSE  2dup s" \" str= IF postpone \ THEN
         THEN ;          THEN ;
   
   : X ( -- <name> )
   \G The next word in the input is a target word.
   \G Equivalent to T <name> but without permanent
   \G switch to target dictionary. Used as prefix e.g. for @, !, here etc.
     bl word count [ ' target >wordlist ] Literal search-wordlist
     IF state @ IF compile, ELSE execute THEN
     ELSE  -1 ABORT" Cross: access method not supported!"
     THEN ; immediate
   
 \ Begin CROSS COMPILER:  \ Begin CROSS COMPILER:
   
 \ debugging  \ debugging
Line 296  set-order previous Line 320  set-order previous
         \ POSTPONE false           \ POSTPONE false 
   THEN ; immediate    THEN ; immediate
   
   : symentry ( adr len taddr -- )
   \G Produce a symbol table (an optional symbol address
   \G map) if wanted
       [ [IFDEF] fd-symbol-table ]
         base @ swap hex s>d <# 8 0 DO # LOOP #> fd-symbol-table write-file throw base !
         s" :" fd-symbol-table write-file throw
         fd-symbol-table write-line throw
       [ [ELSE] ]
         2drop drop
       [ [THEN] ] ;
   
   
 \ \ --------------------        source file  \ \ --------------------        source file
   
 decimal  decimal
Line 411  sourcepath value fpath Line 447  sourcepath value fpath
     \G Make a complete new Forth search path; the path separator is |.      \G Make a complete new Forth search path; the path separator is |.
     fpath path= ;      fpath path= ;
   
 : path>counted  cell+ dup cell+ swap @ ;  : path>string  cell+ dup cell+ swap @ ;
   
 : next-path ( adr len -- adr2 len2 )  : next-path ( adr len -- adr2 len2 )
   2dup 0 scan    2dup 0 scan
Line 420  sourcepath value fpath Line 456  sourcepath value fpath
   r> - ;    r> - ;
   
 : previous-path ( path^ -- )  : previous-path ( path^ -- )
   dup path>counted    dup path>string
   BEGIN tuck dup WHILE repeat ;    BEGIN tuck dup WHILE repeat ;
   
 : .path ( path-addr -- ) \ gforth  : .path ( path-addr -- ) \ gforth
     \G Display the contents of the search path @var{path-addr}.      \G Display the contents of the search path @var{path-addr}.
     path>counted      path>string
     BEGIN next-path dup WHILE type space REPEAT 2drop 2drop ;      BEGIN next-path dup WHILE type space REPEAT 2drop 2drop ;
   
 : .fpath ( -- ) \ gforth  : .fpath ( -- ) \ gforth
Line 440  sourcepath value fpath Line 476  sourcepath value fpath
     2dup 2 u> swap 1+ c@ [char] : = and >r \ dos absoulte: c:/....      2dup 2 u> swap 1+ c@ [char] : = and >r \ dos absoulte: c:/....
     over c@ [char] / = >r      over c@ [char] / = >r
     over c@ [char] ~ = >r      over c@ [char] ~ = >r
     \ 2dup 3 min S" ../" compare 0= r> or >r \ not catered for in expandtopic      \ 2dup S" ../" string-prefix? r> or >r \ not catered for in expandtopic
     2 min S" ./" compare 0=      S" ./" string-prefix?
     r> r> r> or or or ;      r> r> r> or or or ;
   
 Create ofile 0 c, 255 chars allot  Create ofile 0 c, 255 chars allot
Line 457  Create tfile 0 c, 255 chars allot Line 493  Create tfile 0 c, 255 chars allot
   REPEAT ;    REPEAT ;
   
 : remove~+ ( -- )  : remove~+ ( -- )
     ofile count 3 min s" ~+/" compare 0=      ofile count s" ~+/" string-prefix?
     IF      IF
         ofile count 3 /string ofile place          ofile count 3 /string ofile place
     THEN ;      THEN ;
   
 : expandtopic ( -- ) \ stack effect correct? - anton  : expandtopic ( -- ) \ stack effect correct? - anton
     \ expands "./" into an absolute name      \ expands "./" into an absolute name
     ofile count 2 min s" ./" compare 0=      ofile count s" ./" string-prefix?
     IF      IF
         ofile count 1 /string tfile place          ofile count 1 /string tfile place
         0 ofile c! sourcefilename extractpath ofile place          0 ofile c! sourcefilename extractpath ofile place
Line 474  Create tfile 0 c, 255 chars allot Line 510  Create tfile 0 c, 255 chars allot
     THEN ;      THEN ;
   
 : compact.. ( adr len -- adr2 len2 )  : compact.. ( adr len -- adr2 len2 )
 \ deletes phrases like "xy/.." out of our directory name 2dec97jaw      \ deletes phrases like "xy/.." out of our directory name 2dec97jaw
   over >r -1 >r      over swap
   BEGIN dup WHILE      BEGIN  dup  WHILE
         over c@ pathsep?           dup >r '/ scan 2dup s" /../" string-prefix?
         IF      r@ -1 =          IF
                 IF      r> drop dup >r              dup r> - >r 4 /string over r> + 4 -
                 ELSE    2dup 1 /string               swap 2dup + >r move dup r> over -
                         3 min s" ../" compare          ELSE
                         0=              rdrop dup 1 min /string
                         IF      r@ over - ( diff )          THEN
                                 2 pick swap - ( dest-adr )      REPEAT  drop over - ;
                                 >r 3 /string r> swap 2dup >r >r  
                                 move r> r>  
                         ELSE    r> drop dup >r  
                         THEN  
                 THEN  
         THEN  
         1 /string  
   REPEAT   
   r> drop   
   drop r> tuck - ;  
   
 : reworkdir ( -- )  : reworkdir ( -- )
   remove~+    remove~+
Line 520  Create tfile 0 c, 255 chars allot Line 546  Create tfile 0 c, 255 chars allot
   IF    rdrop    IF    rdrop
         ofile place open-ofile          ofile place open-ofile
         dup 0= IF >r ofile count r> THEN EXIT          dup 0= IF >r ofile count r> THEN EXIT
   ELSE  r> path>counted    ELSE  r> path>string
         BEGIN  next-path dup          BEGIN  next-path dup
         WHILE  5 pick 5 pick check-path          WHILE  5 pick 5 pick check-path
         0= IF >r 2drop 2drop r> ofile count 0 EXIT ELSE drop THEN          0= IF >r 2drop 2drop r> ofile count 0 EXIT ELSE drop THEN
Line 550  fpath= ~+ Line 576  fpath= ~+
 : included? ( c-addr u -- f )  : included? ( c-addr u -- f )
   file-list    file-list
   BEGIN @ dup    BEGIN @ dup
   WHILE >r 2dup r@ >fl-name count compare 0=    WHILE >r 2dup r@ >fl-name count str=
         IF rdrop 2drop true EXIT THEN          IF rdrop 2drop true EXIT THEN
         r>          r>
   REPEAT    REPEAT
Line 636  stack-warn [IF] Line 662  stack-warn [IF]
 : defempty? empty? ;  : defempty? empty? ;
 [ELSE]  [ELSE]
 : defempty? ; immediate  : defempty? ; immediate
   \ : defempty? .sourcepos ; 
 [THEN]  [THEN]
   
 \ \ GhostNames Ghosts                                  9may93jaw  \ \ --------------------        Compiler Plug Ins               01aug97jaw
   
 \ second name source to search trough list  >CROSS
   
 VARIABLE GhostNames  \ Compiler States
 0 GhostNames !  
   
 : GhostName ( -- addr )  Variable comp-state
     align here GhostNames @ , GhostNames ! here 0 ,  0 Constant interpreting
     bl word count  1 Constant compiling
     \ 2dup type space  2 Constant resolving
     string, \ !! cfalign ?  3 Constant assembling
     align ;  
   
 \ Ghost Builder                                        06oct92py  : compiling? comp-state @ compiling = ;
   
   : pi-undefined -1 ABORT" Plugin undefined" ;
   
   : Plugin ( -- : pluginname )
     Create 
     \ for normal cross-compiling only one action
     \ exists, this fields are identical. For the instant
     \ simulation environment we need, two actions for each plugin
     \ the target one and the one that generates the simulation code
     ['] pi-undefined , \ action
     ['] pi-undefined , \ target plugin action
     8765 ,     \ plugin magic
     DOES> perform ;
   
   Plugin DummyPlugin
   
   : 'PI ( -- addr : pluginname )
     ' >body dup 2 cells + @ 8765 <> ABORT" not a plugin" ;
   
   : plugin-of ( xt -- : pluginname )
     dup 'PI 2! ;
   
   : action-of ( xt -- : plunginname )
     'PI cell+ ! ;
   
   : TPA ( -- : plugin )
   \ target plugin action
   \ executes current target action of plugin
     'PI cell+ POSTPONE literal POSTPONE perform ; immediate
   
   Variable ppi-temp 0 ppi-temp !
   
   : pa:
   \g define plugin action
     ppi-temp @ ABORT" pa: definition not closed"
     'PI ppi-temp ! :noname ;
   
   : ;pa
   \g end a definition for plugin action
     POSTPONE ; ppi-temp @ ! 0 ppi-temp ! ; immediate
   
   
   Plugin dlit, ( d -- )                   \ compile numerical value the target
   Plugin lit, ( n -- )
   Plugin alit, ( n -- )
   
   Plugin branch, ( target-addr -- )       \ compiles a branch
   Plugin ?branch, ( target-addr -- )      \ compiles a ?branch
   Plugin branchmark, ( -- branch-addr )   \ reserves room for a branch
   Plugin ?branchmark, ( -- branch-addr )  \ reserves room for a ?branch
   Plugin ?domark, ( -- branch-addr )      \ reserves room for a ?do branch
   Plugin branchto, ( -- )                 \ actual program position is target of a branch (do e.g. alignment)
   ' NOOP plugin-of branchto, 
   Plugin branchtoresolve, ( branch-addr -- ) \ resolves a forward reference from branchmark
   Plugin branchtomark, ( -- target-addr ) \ marks a branch destination
   
   Plugin colon, ( tcfa -- )               \ compiles call to tcfa at current position
   Plugin prim, ( tcfa -- )                \ compiles primitive invocation
   Plugin colonmark, ( -- addr )           \ marks a colon call
   Plugin colon-resolve ( tcfa addr -- )
   
   Plugin addr-resolve ( target-addr addr -- )
   Plugin doer-resolve ( ghost res-pnt target-addr addr -- ghost res-pnt )
   
   Plugin ncontrols? ( [ xn ... x1 ] n -- ) \ checks wheter n control structures are open
   Plugin if,      ( -- if-token )
   Plugin else,    ( if-token -- if-token )
   Plugin then,    ( if-token -- )
   Plugin ahead,
   Plugin begin,
   Plugin while,
   Plugin until,
   Plugin again,
   Plugin repeat,
   Plugin cs-swap  ( x1 x2 -- x2 x1 )
   
   Plugin case,    ( -- n )
   Plugin of,      ( n -- x1 n )
   Plugin endof,   ( x1 n -- x2 n )
   Plugin endcase, ( x1 .. xn n -- )
   
   Plugin do,      ( -- do-token )
   Plugin ?do,     ( -- ?do-token )
   Plugin for,     ( -- for-token )
   Plugin loop,    ( do-token / ?do-token -- )
   Plugin +loop,   ( do-token / ?do-token -- )
   Plugin next,    ( for-token )
   Plugin leave,   ( -- )
   Plugin ?leave,  ( -- )
   
   Plugin ca>native  \ Convert a code address to the processors
                     \ native address. This is used in doprim, and
                     \ code/code: primitive definitions word to
                     \ convert the addresses.
                     \ The only target where we need this is the misc
                     \ which is a 16 Bit processor with word addresses
                     \ but the forth system we build has a normal byte
                     \ addressed memory model    
   
   Plugin doprim,  \ compiles start of a primitive
   Plugin docol,           \ compiles start of a colon definition
   Plugin doer,            
   Plugin fini,      \ compiles end of definition ;s
   Plugin doeshandler,
   Plugin dodoes,
   
   Plugin colon-start
   ' noop plugin-of colon-start
   Plugin colon-end
   ' noop plugin-of colon-end
   
   Plugin ]comp     \ starts compilation
   ' noop plugin-of ]comp
   Plugin comp[     \ ends compilation
   ' noop plugin-of comp[
   
   Plugin t>body             \ we need the system >body
                           \ and the target >body
   
 \ <T T> new version with temp variable                 10may93jaw  >TARGET
   : >body t>body ;
   
 VARIABLE VocTemp  
   
 : <T  get-current VocTemp ! also Ghosts definitions ;  \ Ghost Builder                                        06oct92py
 : T>  previous VocTemp @ set-current ;  
   
   >CROSS
 hex  hex
   \ Values for ghost magic
 4711 Constant <fwd>             4712 Constant <res>  4711 Constant <fwd>             4712 Constant <res>
 4713 Constant <imm>             4714 Constant <do:>  4713 Constant <imm>             4714 Constant <do:>
 4715 Constant <skip>  4715 Constant <skip>
   
 \ iForth makes only immediate directly after create  \ Bitmask for ghost flags
 \ make atonce trick! ?  1 Constant <unique>
   2 Constant <primitive>
   
   \ FXIME: move this to general stuff?
   : set-flag ( addr flag -- )
     over @ or swap ! ;
   
   : reset-flag ( addr flag -- )
     invert over @ and swap ! ;
   
   : get-flag ( addr flag -- f )
     swap @ and 0<> ;
     
   
 Variable atonce atonce off  Struct
   
 : NoExec true ABORT" CROSS: Don't execute ghost, or immediate target word" ;    \ link to next ghost (always the first element)
     cell% field >next-ghost
   
 : GhostHeader <fwd> , 0 , ['] NoExec , ;    \ type of ghost
     cell% field >magic
                   
     \ pointer where ghost is in target, or if unresolved
     \ points to the where we have to resolve (linked-list)
     cell% field >link
   
     \ execution semantics (while target compiling) of ghost
     cell% field >exec
   
     \ compilation action of this ghost; this is what is
     \ done to compile a call (or whatever) to this definition.
     \ E.g. >comp contains the semantic of postpone s"
     \ whereas >exec-compile contains the semantic of s"
     cell% field >comp
   
     \ Compilation sematics (while parsing) of this ghost. E.g. 
     \ "\" will skip the rest of line.
     \ These semantics are defined by Cond: and
     \ if a word is made immediate in instant, then the >exec2 field
     \ gets copied to here
     cell% field >exec-compile
   
     \ Additional execution semantics of this ghost. This is used
     \ for code generated by instant and for the doer-xt of created
     \ words
     cell% field >exec2
   
     cell% field >created
   
     \ the xt of the created ghost word itself
     cell% field >ghost-xt
   
     \ pointer to the counted string of the assiciated
     \ assembler label
     cell% field >asm-name
   
     \ mapped primitives have a special address, so
     \ we are able to detect them
     cell% field >asm-dummyaddr
                           
     \ for builder (create, variable...) words
     \ the execution symantics of words built are placed here
     \ this is a doer ghost or a dummy ghost
     cell% field >do:ghost
   
 : >magic ;              \ type of ghost    cell% field >ghost-flags
 : >link cell+ ;         \ pointer where ghost is in target, or if unresolved  
                         \ points to the where we have to resolve (linked-list)    cell% field >ghost-name
 : >exec cell+ cell+ ;   \ execution symantics (while target compiling) of ghost  
 : >end 3 cells + ;      \ room for additional tags  End-Struct ghost-struct
                         \ for builder (create, variable...) words the  
                         \ execution symantics of words built are placed here  Variable ghost-list
   0 ghost-list !
   
 Variable executed-ghost \ last executed ghost, needed in tcreate and gdoes>  Variable executed-ghost \ last executed ghost, needed in tcreate and gdoes>
 Variable last-ghost     \ last ghost that is created  \ Variable last-ghost   \ last ghost that is created
 Variable last-header-ghost \ last ghost definitions with header  Variable last-header-ghost \ last ghost definitions with header
   
   \ space for ghosts resolve structure
   \ we create ghosts in a sepearte space
   \ and not to the current host dp, because this
   \ gives trouble with instant while compiling and creating
   \ a ghost for a forward reference
   \ BTW: we cannot allocate another memory region
   \ because allot will check the overflow!!
   Variable cross-space-dp
   Create cross-space 250000 allot here 100 allot align 
   Constant cross-space-end
   cross-space cross-space-dp !
   Variable cross-space-dp-orig
   
   : cross-space-used cross-space-dp @ cross-space - ;
   
   : >space ( -- )
     dp @ cross-space-dp-orig !
     cross-space-dp @ dp ! ;
   
   : space> ( -- )
     dp @ dup cross-space-dp !
     cross-space-end u> ABORT" CROSS: cross-space overflow"
     cross-space-dp-orig @ dp ! ;
   
   \ this is just for debugging, to see this in the backtrace
   : execute-exec execute ;
   : execute-exec2 execute ;
   : execute-exec-compile execute ;
   
   : NoExec
     executed-ghost @ >exec2 @
     ?dup 
     IF   execute-exec2
     ELSE true ABORT" CROSS: Don't execute ghost, or immediate target word"
     THEN ;
   
   Defer is-forward
   
   : (ghostheader) ( -- )
       ghost-list linked <fwd> , 0 , ['] NoExec , ['] is-forward ,
       0 , 0 , 0 , 0 , 0 , 0 , 0 , 0 , ;
   
   : ghostheader ( -- ) (ghostheader) 0 , ;
   
   ' Ghosts >wordlist Constant ghosts-wordlist
   
   \ the current wordlist for ghost definitions in the host
   ghosts-wordlist Value current-ghosts
   
 : Make-Ghost ( "name" -- ghost )  : Make-Ghost ( "name" -- ghost )
   >in @ GhostName swap >in !    >space
   <T Create atonce @ IF immediate atonce off THEN    \ save current and create in ghost vocabulary
   here tuck swap ! ghostheader T>    get-current >r current-ghosts set-current
   dup last-ghost !    >in @ Create >in !
   DOES> dup executed-ghost ! >exec @ execute ;    \ some forth systems like iForth need the immediate directly
     \ after the word is created
     \ restore current
     r> set-current
     here (ghostheader)
     bl word count string, align
     space>
     \ set ghost-xt field by doing a search
     dup >ghost-name count 
     current-ghosts search-wordlist
     0= ABORT" CROSS: Just created, must be there!"
     over >ghost-xt !
     DOES> 
         dup executed-ghost !
         >exec @ execute-exec ;
   
 \ ghost words                                          14oct92py  \ ghost words                                          14oct92py
 \                                          changed:    10may93py/jaw  \                                          changed:    10may93py/jaw
   
 : gfind   ( string -- ghost true/1 / string false )  Defer search-ghosts
   
   : (search-ghosts) ( adr len -- cfa true | 0 )
     current-ghosts search-wordlist ; 
   
     ' (search-ghosts) IS search-ghosts
   
   : gsearch ( addr len -- ghost true | 0 )
     search-ghosts
     dup IF swap >body swap THEN ;
   
   : gfind   ( string -- ghost true / string false )
 \ searches for string in word-list ghosts  \ searches for string in word-list ghosts
   dup count [ ' ghosts >wordlist ] Literal search-wordlist    \ dup count type space
   dup IF >r >body nip r>  THEN ;    dup >r count gsearch
     dup IF rdrop ELSE r> swap THEN ;
   
 : gdiscover ( xt -- ghost true | xt false )  : gdiscover ( xt -- ghost true | xt false )
   GhostNames    >r ghost-list
   BEGIN @ dup    BEGIN @ dup
   WHILE 2dup    WHILE dup >magic @ <fwd> <>
         cell+ @ dup >magic @ <fwd> <>          IF dup >link @ r@ =
         >r >link @ = r> and             IF rdrop true EXIT THEN
         IF cell+ @ nip true EXIT THEN          THEN
   REPEAT    REPEAT
   drop false ;    drop r> false ;
   
 VARIABLE Already  : xt>ghost ( xt -- ghost )
     gdiscover 0= ABORT" CROSS: ghost not found for this xt" ;
   
 : ghost   ( "name" -- ghost )  : Ghost   ( "name" -- ghost )
   Already off    >in @ bl word gfind IF  nip EXIT  THEN
   >in @  bl word gfind   IF  atonce off Already on nip EXIT  THEN  
   drop  >in !  Make-Ghost ;    drop  >in !  Make-Ghost ;
   
 : >ghostname ( ghost -- adr len )  : >ghostname ( ghost -- adr len )
   GhostNames    >ghost-name count ;
   BEGIN @ dup  
   WHILE 2dup cell+ @ =  
   UNTIL nip 2 cells + count  
   ELSE  2drop   
         \ true abort" CROSS: Ghostnames inconsistent"  
         s" ?!?!?!"  
   THEN ;  
   
 : .ghost ( ghost -- ) >ghostname type ;  
   
 \ ' >ghostname ALIAS @name  
   
 : forward? ( ghost -- flag )  : forward? ( ghost -- flag )
   >magic @ <fwd> = ;    >magic @ <fwd> = ;
Line 739  VARIABLE Already Line 1005  VARIABLE Already
 : undefined? ( ghost -- flag )  : undefined? ( ghost -- flag )
   >magic @ dup <fwd> = swap <skip> = or ;    >magic @ dup <fwd> = swap <skip> = or ;
   
   : immediate? ( ghost -- flag )
     >magic @ <imm> = ;
   
   Variable TWarnings
   TWarnings on
   Variable Exists-Warnings
   Exists-Warnings on
   
   : exists-warning ( ghost -- ghost )
     TWarnings @ Exists-Warnings @ and
     IF dup >ghostname warnhead type ."  exists " THEN ;
   
   \ : HeaderGhost Ghost ;
   
   Variable reuse-ghosts reuse-ghosts off
   
   : HeaderGhost ( "name" -- ghost )
     >in @ 
     bl word count 
   \  2dup type space
     current-ghosts search-wordlist
     IF  >body dup undefined? reuse-ghosts @ or
         IF   nip EXIT
         ELSE exists-warning 
         THEN
         drop >in ! 
     ELSE >in ! 
     THEN 
     \ we keep the execution semantics of the prviously
     \ defined words, this is a workaround
     \ for the redefined \ until vocs work
     Make-Ghost ;
    
   : .ghost ( ghost -- ) >ghostname type ;
   
   \ ' >ghostname ALIAS @name
   
   : findghost ( "ghostname" -- ghost ) 
     bl word gfind 0= ABORT" CROSS: Ghost don't exists" ;
   
   : [G'] ( -- ghost : name )
   \G ticks a ghost and returns its address
     findghost
     state @ IF postpone literal THEN ; immediate
   
   : g>xt ( ghost -- xt )
   \G Returns the xt (cfa) of a ghost. Issues a warning if undefined.
     dup undefined? ABORT" CROSS: forward " >link @ ;
      
   : g>body ( ghost -- body )
   \G Returns the body-address (pfa) of a ghost. 
   \G Issues a warning if undefined (a forward-reference).
     g>xt X >body ;
   
   1 Constant <label>
   
   Struct
     \ bitmask of address type (not used for now)
     cell% field addr-type
     \ if this address is an xt, this field points to the ghost
     cell% field addr-xt-ghost
     \ a bit mask that tells as what part of the cell
     \ is refenced from an address pointer, used for assembler generation
     cell% field addr-refs
   End-Struct addr-struct
   
   : %allocerase ( align size -- addr )
     dup >r %alloc dup r> erase ;
   
   \ returns the addr struct, define it if 0 reference
   : define-addr-struct ( addr -- struct-addr )
     dup @ ?dup IF nip EXIT THEN
     addr-struct %allocerase tuck swap ! ;
   
   >cross
   
 \ Predefined ghosts                                    12dec92py  \ Predefined ghosts                                    12dec92py
   
 ghost 0=                                        drop  Ghost - drop \ need a ghost otherwise "-" would be treated as a number
 ghost branch    ghost ?branch                   2drop  
 ghost (do)      ghost (?do)                     2drop  Ghost 0=                                        drop
 ghost (for)                                     drop  Ghost branch    Ghost ?branch                   2drop
 ghost (loop)    ghost (+loop)                   2drop  Ghost unloop    Ghost ;S                        2drop
 ghost (next)                                    drop  Ghost lit       Ghost !                         2drop
 ghost unloop    ghost ;S                        2drop  Ghost noop                                      drop
 ghost lit       ghost (compile) ghost !         2drop drop  Ghost over      Ghost =         Ghost drop      2drop drop
 ghost (does>)   ghost noop                      2drop  Ghost 2drop drop
 ghost (.")      ghost (S")      ghost (ABORT")  2drop drop  Ghost 2dup drop
 ghost '                                         drop  Ghost call drop
 ghost :docol    ghost :doesjump ghost :dodoes   2drop drop  Ghost @ drop
 ghost :dovar                                    drop  Ghost useraddr drop
 ghost over      ghost =         ghost drop      2drop drop  Ghost execute drop
 ghost - drop  Ghost + drop
 ghost 2drop drop  Ghost decimal drop
 ghost 2dup drop  Ghost hex drop
   Ghost lit@ drop
   Ghost lit-perform drop
   Ghost lit+ drop
   Ghost does-exec drop
   
   Ghost :docol    Ghost :doesjump Ghost :dodoes   2drop drop
   Ghost :dovar                                    drop
   
 \ \ Parameter for target systems                         06oct92py  \ \ Parameter for target systems                         06oct92py
   
   
 \ we define it ans like...  \ we define it ans like...
 wordlist Constant target-environment  wordlist Constant target-environment
   
 VARIABLE env-current \ save information of current dictionary to restore with environ>  \ save information of current dictionary to restore with environ>
   Variable env-current 
   
 : >ENVIRON get-current env-current ! target-environment set-current ;  : >ENVIRON get-current env-current ! target-environment set-current ;
 : ENVIRON> env-current @ set-current ;   : ENVIRON> env-current @ set-current ; 
   
 >TARGET  >TARGET
   
 : environment? ( adr len -- [ x ] true | false )  : environment? ( addr len -- [ x ] true | false )
   target-environment search-wordlist   \G returns the content of environment variable and true or
   IF execute true ELSE false THEN ;  \G false if not present
      target-environment search-wordlist 
 : e? bl word count T environment? H 0= ABORT" environment variable not defined!" ;     IF EXECUTE true ELSE false THEN ;
   
 : has?  bl word count T environment? H   : $has? ( addr len -- x | false )
         IF      \ environment variable is present, return its value  \G returns the content of environment variable 
         ELSE    \ environment variable is not present, return false  \G or false if not present
                 false \ debug true ABORT" arg"      T environment? H dup IF drop THEN ;
         THEN ;  
   : e? ( "name" -- x )
   \G returns the content of environment variable. 
   \G The variable is expected to exist. If not, issue an error.
      bl word count T environment? H 
      0= ABORT" environment variable not defined!" ;
   
   : has? ( "name" --- x | false )
   \G returns the content of environment variable 
   \G or false if not present
      bl word count T $has? H ;
   
 : $has? T environment? H IF ELSE false THEN ;  
   
 >ENVIRON get-order get-current swap 1+ set-order  >ENVIRON get-order get-current swap 1+ set-order
 true SetValue compiler  true SetValue compiler
 true  SetValue cross  true SetValue cross
 true SetValue standard-threading  true SetValue standard-threading
 >TARGET previous  >TARGET previous
   
 0  0
 [IFDEF] mach-file mach-file count 1 [THEN]  [IFDEF] mach-file drop mach-file count 1 [THEN]
 [IFDEF] machine-file machine-file 1 [THEN]  [IFDEF] machine-file drop machine-file 1 [THEN]
 [IF]    included hex drop  [IF]    included hex
 [ELSE]  cr ." No machine description!" ABORT   [ELSE]  cr ." No machine description!" ABORT 
 [THEN]  [THEN]
   
Line 812  false DefaultValue dcomps Line 1172  false DefaultValue dcomps
 false DefaultValue hash  false DefaultValue hash
 false DefaultValue xconds  false DefaultValue xconds
 false DefaultValue header  false DefaultValue header
   false DefaultValue backtrace
   false DefaultValue new-input
   false DefaultValue peephole
   false DefaultValue abranch
   true DefaultValue f83headerstring
   true DefaultValue control-rack
 [THEN]  [THEN]
   
   true DefaultValue gforthcross
 true DefaultValue interpreter  true DefaultValue interpreter
 true DefaultValue ITC  true DefaultValue ITC
 false DefaultValue rom  false DefaultValue rom
 true DefaultValue standardthreading  true DefaultValue standardthreading
   
   \ ANSForth environment  stuff
   8 DefaultValue ADDRESS-UNIT-BITS
   255 DefaultValue MAX-CHAR
   255 DefaultValue /COUNTED-STRING
   
 >TARGET  >TARGET
 s" relocate" T environment? H   s" relocate" T environment? H 
 [IF]    SetValue NIL  \ JAW why set NIL to this?!
 [ELSE]  >ENVIRON T NIL H SetValue relocate  [IF]    drop \ SetValue NIL
   [ELSE]  >ENVIRON X NIL SetValue relocate
 [THEN]  [THEN]
   >TARGET
   
   0 Constant NIL
   
 >CROSS  >CROSS
   
Line 869  tbits/char bits/byte / Constant tbyte Line 1245  tbits/char bits/byte / Constant tbyte
   
 \ Variables                                            06oct92py  \ Variables                                            06oct92py
   
 Variable image  Variable (tlast)    
 Variable tlast    TNIL tlast !  \ Last name field  (tlast) Value tlast TNIL tlast !  \ Last name field
 Variable tlastcfa \ Last code field  Variable tlastcfa \ Last code field
 Variable tdoes    \ Resolve does> calls  
 Variable bit$  
   
 \ statistics                                            10jun97jaw  \ statistics                                            10jun97jaw
   
Line 883  Variable user-vars 0 user-vars ! Line 1257  Variable user-vars 0 user-vars !
 : target>bitmask-size ( u1 -- u2 )  : target>bitmask-size ( u1 -- u2 )
   1- tcell>bit rshift 1+ ;    1- tcell>bit rshift 1+ ;
   
 : allocatetarget ( size --- adr )  : allocatetarget ( size -- adr )
   dup allocate ABORT" CROSS: No memory for target"    dup allocate ABORT" CROSS: No memory for target"
   swap over swap erase ;    swap over swap erase ;
   
Line 895  Variable region-link            \ linked Line 1269  Variable region-link            \ linked
 Variable mirrored-link          \ linked list for mirrored regions  Variable mirrored-link          \ linked list for mirrored regions
 0 dup mirrored-link ! region-link !  0 dup mirrored-link ! region-link !
   
   : >rname 9 cells + ;
 : >rname 6 cells + ;  : >rtouch 8 cells + ; \ executed when region is accessed
 : >rbm   5 cells + ;  : >rbm   4 cells + ; \ bitfield per cell witch indicates relocation
 : >rmem  4 cells + ;  : >rmem  5 cells + ;
   : >rtype 6 cells + ; \ field per cell witch points to a type struct
   : >rrom 7 cells + ;  \ a -1 indicates that this region is rom
 : >rlink 3 cells + ;  : >rlink 3 cells + ;
 : >rdp 2 cells + ;  : >rdp 2 cells + ;
 : >rlen cell+ ;  : >rlen cell+ ;
 : >rstart ;  : >rstart ;
   
   : (region) ( addr len region -- )
   \G change startaddress and length of an existing region
     >r r@ last-defined-region !
     r@ >rlen ! dup r@ >rstart ! r> >rdp ! ;
   
   : uninitialized -1 ABORT" CROSS: Region is uninitialized" ;
   
 : region ( addr len -- )                \G create a new region  : region ( addr len -- "name" )                
   \G create a new region
   \ check whether predefined region exists     \ check whether predefined region exists 
   save-input bl word find >r >r restore-input throw r> r> 0=     save-input bl word find >r >r restore-input throw r> r> 0= 
   IF    \ make region    IF    \ make region
Line 913  Variable mirrored-link          \ linked Line 1296  Variable mirrored-link          \ linked
         save-input create restore-input throw          save-input create restore-input throw
         here last-defined-region !          here last-defined-region !
         over ( startaddr ) , ( length ) , ( dp ) ,          over ( startaddr ) , ( length ) , ( dp ) ,
         region-link linked 0 , 0 , bl word count string,          region-link linked 0 , 0 , 0 , 0 , 
           ['] uninitialized ,
           bl word count string,
   ELSE  \ store new parameters in region    ELSE  \ store new parameters in region
         bl word drop          bl word drop
         >body >r r@ last-defined-region !          >body (region)
         r@ >rlen ! dup r@ >rstart ! r> >rdp !  
   THEN ;    THEN ;
   
 : borders ( region -- startaddr endaddr ) \G returns lower and upper region border  : borders ( region -- startaddr endaddr ) 
   \G returns lower and upper region border
   dup >rstart @ swap >rlen @ over + ;    dup >rstart @ swap >rlen @ over + ;
   
 : extent  ( region -- startaddr len )   \G returns the really used area  : extent  ( region -- startaddr len )   
   \G returns the really used area
   dup >rstart @ swap >rdp @ over - ;    dup >rstart @ swap >rdp @ over - ;
   
 : area ( region -- startaddr totallen ) \G returns the total area  : area ( region -- startaddr totallen ) 
   \G returns the total area
   dup >rstart @ swap >rlen @ ;    dup >rstart @ swap >rlen @ ;
   
 : mirrored                              \G mark a region as mirrored  : dp@ ( region -- dp )
     >rdp @ ;
   
   : mirrored ( -- )                              
   \G mark last defined region as mirrored
   mirrored-link    mirrored-link
   align linked last-defined-region @ , ;    align linked last-defined-region @ , ;
   
   : writeprotected
   \G mark a region as write protected
     -1 last-defined-region @ >rrom ! ;
   
 : .addr ( u -- )  : .addr ( u -- )
 \G prints a 16 or 32 Bit nice hex value  \G prints a 16 or 32 Bit nice hex value
   base @ >r hex    base @ >r hex
   tcell 2 u>    tcell 2 u>
   IF s>d <# # # # # [char] . hold # # # # #> type    IF s>d <# # # # # [char] . hold # # # # #> type
   ELSE s>d <# # # # # # #> type    ELSE s>d <# # # # # # #> type
   THEN r> base ! ;    THEN r> base ! space ;
   
 : .regions                      \G display region statistic  : .regions                      \G display region statistic
   
Line 969  Variable mirrored-link          \ linked Line 1364  Variable mirrored-link          \ linked
 0 0 region address-space  0 0 region address-space
 \ total memory addressed and used by the target system  \ total memory addressed and used by the target system
   
   0 0 region user-region
   \ data for user variables goes here
   \ this has to be defined before dictionary or ram-dictionary
   
 0 0 region dictionary  0 0 region dictionary
 \ rom area for the compiler  \ rom area for the compiler
   
Line 988  T has? rom H Line 1387  T has? rom H
   
 ' dictionary ALIAS rom-dictionary  ' dictionary ALIAS rom-dictionary
   
   : setup-region ( region -- )
     >r
     \ allocate mem
     r@ >rlen @ allocatetarget
     r@ >rmem !
   
     r@ >rlen @
     target>bitmask-size allocatetarget
     r@ >rbm !
   
 : setup-target ( -- )   \G initialize targets memory space    r@ >rlen @
     tcell / 1+ cells allocatetarget r@ >rtype !
   
     ['] noop r@ >rtouch !
     rdrop ;
   
   : setup-target ( -- )   \G initialize target's memory space
   s" rom" T $has? H    s" rom" T $has? H
   IF  \ check for ram and rom...    IF  \ check for ram and rom...
       \ address-space area nip 0<>        \ address-space area nip 0<>
Line 1013  T has? rom H Line 1427  T has? rom H
   WHILE dup    WHILE dup
         0 >rlink - >r          0 >rlink - >r
         r@ >rlen @          r@ >rlen @
         IF      \ allocate mem          IF      r@ setup-region
                 r@ >rlen @ dup          THEN    rdrop
   
                 allocatetarget dup image !  
                 r@ >rmem !  
   
                 target>bitmask-size allocatetarget  
                 dup bit$ !  
                 r> >rbm !  
   
         ELSE    r> drop THEN  
    REPEAT drop ;     REPEAT drop ;
   
 \ MakeKernal                                                    22feb99jaw  \ MakeKernel                                                    22feb99jaw
   
 : makekernel ( targetsize -- targetsize )  : makekernel ( start targetsize -- )
   dup dictionary >rlen ! setup-target ;  \G convenience word to setup the memory of the target
   \G used by main.fs of the c-engine based systems
     dictionary (region) setup-target ;
   
 >MINIMAL  >MINIMAL
 : makekernel makekernel ;  : makekernel makekernel ;
Line 1054  variable sromdp  \ start of rom-area for Line 1461  variable sromdp  \ start of rom-area for
   
 [THEN]  [THEN]
   
   0 Value current-region
 0 value tdp  0 Value tdp
 variable fixed          \ flag: true: no automatic switching  Variable fixed          \ flag: true: no automatic switching
                         \       false: switching is done automatically                          \       false: switching is done automatically
   
 \ Switch-Policy:  \ Switch-Policy:
Line 1071  variable constflag constflag off Line 1478  variable constflag constflag off
   
 : activate ( region -- )  : activate ( region -- )
 \G next code goes to this region  \G next code goes to this region
   >rdp to tdp ;    dup to current-region >rdp to tdp ;
   
 : (switchram)  : (switchram)
   fixed @ ?EXIT s" rom" T $has? H 0= ?EXIT    fixed @ ?EXIT s" rom" T $has? H 0= ?EXIT
Line 1126  variable constflag constflag off Line 1533  variable constflag constflag off
   
 bigendian  bigendian
 [IF]  [IF]
    : S!  ( n addr -- )  >r s>d r> tcell bounds swap 1-     : DS!  ( d addr -- )  tcell bounds swap 1-
      DO  maxbyte ud/mod rot I c!  -1 +LOOP  2drop ;       DO  maxbyte ud/mod rot I c!  -1 +LOOP  2drop ;
    : S@  ( addr -- n )  >r 0 0 r> tcell bounds     : DS@  ( addr -- d )  >r 0 0 r> tcell bounds
      DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  LOOP d>s ;       DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  LOOP ;
    : Sc!  ( n addr -- )  >r s>d r> tchar bounds swap 1-     : Sc!  ( n addr -- )  >r s>d r> tchar bounds swap 1-
      DO  maxbyte ud/mod rot I c!  -1 +LOOP  2drop ;       DO  maxbyte ud/mod rot I c!  -1 +LOOP  2drop ;
    : Sc@  ( addr -- n )  >r 0 0 r> tchar bounds     : Sc@  ( addr -- n )  >r 0 0 r> tchar bounds
      DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  LOOP d>s ;       DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  LOOP d>s ;
 [ELSE]  [ELSE]
    : S!  ( n addr -- )  >r s>d r> tcell bounds     : DS!  ( d addr -- )  tcell bounds
      DO  maxbyte ud/mod rot I c!  LOOP  2drop ;       DO  maxbyte ud/mod rot I c!  LOOP  2drop ;
    : S@  ( addr -- n )  >r 0 0 r> tcell bounds swap 1-     : DS@  ( addr -- n )  >r 0 0 r> tcell bounds swap 1-
      DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  -1 +LOOP d>s ;       DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  -1 +LOOP ;
    : Sc!  ( n addr -- )  >r s>d r> tchar bounds     : Sc!  ( n addr -- )  >r s>d r> tchar bounds
      DO  maxbyte ud/mod rot I c!  LOOP  2drop ;       DO  maxbyte ud/mod rot I c!  LOOP  2drop ;
    : Sc@  ( addr -- n )  >r 0 0 r> tchar bounds swap 1-     : Sc@  ( addr -- n )  >r 0 0 r> tchar bounds swap 1-
      DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  -1 +LOOP d>s ;       DO  maxbyte * swap maxbyte um* rot + swap I c@ + swap  -1 +LOOP d>s ;
 [THEN]  [THEN]
   
   : S! ( n addr -- ) >r s>d r> DS! ;
   : S@ ( addr -- n ) DS@ d>s ;
   
 : taddr>region ( taddr -- region | 0 )  : taddr>region ( taddr -- region | 0 )
 \G finds for a target-address the correct region  \G finds for a target-address the correct region
 \G returns 0 if taddr is not in range of a target memory region  \G returns 0 if taddr is not in range of a target memory region
Line 1154  bigendian Line 1564  bigendian
         0 >rlink - >r          0 >rlink - >r
         r@ >rlen @          r@ >rlen @
         IF      dup r@ borders within          IF      dup r@ borders within
                 IF r> r> drop nip EXIT THEN                  IF r> r> drop nip 
                      dup >rtouch @ EXECUTE EXIT 
                   THEN
         THEN          THEN
         r> drop          r> drop
         r>          r>
   REPEAT    REPEAT
   2drop 0 ;    2drop 0 ;
   
   : taddr>region-abort ( taddr -- region | 0 )
   \G Same as taddr>region but aborts if taddr is not
   \G a valid address in the target address space
     dup taddr>region dup 0= 
     IF    drop cr ." Wrong address: " .addr
           -1 ABORT" Address out of range!"
     THEN nip ;
   
 : (>regionimage) ( taddr -- 'taddr )  : (>regionimage) ( taddr -- 'taddr )
   dup    dup
   \ find region we want to address    \ find region we want to address
   taddr>region dup 0= ABORT" Address out of range!"    taddr>region-abort
     >r
     \ calculate offset in region
     r@ >rstart @ -
     \ add regions real address in our memory
     r> >rmem @ + ;
   
   : (>regionramimage) ( taddr -- 'taddr )
   \G same as (>regionimage) but aborts if the region is rom
     dup
     \ find region we want to address
     taddr>region-abort
   >r    >r
     r@ >rrom @ ABORT" CROSS: region is write-protected!"
   \ calculate offset in region    \ calculate offset in region
   r@ >rstart @ -    r@ >rstart @ -
   \ add regions real address in our memory    \ add regions real address in our memory
   r> >rmem @ + ;    r> >rmem @ + ;
   
   : (>regionbm) ( taddr -- 'taddr bitmaskbaseaddr )
     dup
     \ find region we want to address
     taddr>region-abort
     >r
     \ calculate offset in region
     r@ >rstart @ -
     \ add regions real address in our memory
     r> >rbm @ ;
   
   : (>regiontype) ( taddr -- 'taddr )
     dup
     \ find region we want to address
     taddr>region-abort
     >r
     \ calculate offset in region
     r@ >rstart @ - tcell / cells
     \ add regions real address in our memory
     r> >rtype @ + ;
     
 \ Bit string manipulation                               06oct92py  \ Bit string manipulation                               06oct92py
 \                                                       9may93jaw  \                                                       9may93jaw
 CREATE Bittable 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,  CREATE Bittable 80 c, 40 c, 20 c, 10 c, 8 c, 4 c, 2 c, 1 c,
Line 1180  CREATE Bittable 80 c, 40 c, 20 c, 10 c, Line 1632  CREATE Bittable 80 c, 40 c, 20 c, 10 c,
 : +bit ( addr n -- )  >bit over c@ or swap c! ;  : +bit ( addr n -- )  >bit over c@ or swap c! ;
 : -bit ( addr n -- )  >bit invert over c@ and swap c! ;  : -bit ( addr n -- )  >bit invert over c@ and swap c! ;
   
 : (relon) ( taddr -- )  bit$ @ swap cell/ +bit ;  : @relbit ( taddr -- f ) (>regionbm) swap cell/ >bit swap c@ and ;
 : (reloff) ( taddr -- ) bit$ @ swap cell/ -bit ;  
   
 : (>image) ( taddr -- absaddr ) image @ + ;  : (relon) ( taddr -- )  
     [ [IFDEF] fd-relocation-table ]
     s" +" fd-relocation-table write-file throw
     dup s>d <# #s #> fd-relocation-table write-line throw
     [ [THEN] ]
     (>regionbm) swap cell/ +bit ;
   
   : (reloff) ( taddr -- ) 
     [ [IFDEF] fd-relocation-table ]
     s" -" fd-relocation-table write-file throw
     dup s>d <# #s #> fd-relocation-table write-line throw
     [ [THEN] ]
     (>regionbm) swap cell/ -bit ;
   
 DEFER >image  DEFER >image
   DEFER >ramimage
 DEFER relon  DEFER relon
 DEFER reloff  DEFER reloff
 DEFER correcter  DEFER correcter
Line 1194  T has? relocate H Line 1658  T has? relocate H
 [IF]  [IF]
 ' (relon) IS relon  ' (relon) IS relon
 ' (reloff) IS reloff  ' (reloff) IS reloff
 ' (>image) IS >image  ' (>regionimage) IS >image
   ' (>regionimage) IS >ramimage
 [ELSE]  [ELSE]
 ' drop IS relon  ' drop IS relon
 ' drop IS reloff  ' drop IS reloff
 ' (>regionimage) IS >image  ' (>regionimage) IS >image
   ' (>regionimage) IS >ramimage
 [THEN]  [THEN]
   
   : enforce-writeprotection ( -- )
     ['] (>regionramimage) IS >ramimage ;
   
   : relax-writeprotection ( -- )
     ['] (>regionimage) IS >ramimage ;
   
   : writeprotection-relaxed? ( -- )
     ['] >ramimage >body @ ['] (>regionimage) = ;
   
 \ Target memory access                                 06oct92py  \ Target memory access                                 06oct92py
   
 : align+  ( taddr -- rest )  : align+  ( taddr -- rest )
Line 1218  T has? relocate H Line 1693  T has? relocate H
     dup cfalign+ + ;      dup cfalign+ + ;
   
 : @  ( taddr -- w )     >image S@ ;  : @  ( taddr -- w )     >image S@ ;
 : !  ( w taddr -- )     >image S! ;  : !  ( w taddr -- )     >ramimage S! ;
 : c@ ( taddr -- char )  >image Sc@ ;  : c@ ( taddr -- char )  >image Sc@ ;
 : c! ( char taddr -- )  >image Sc! ;  : c! ( char taddr -- )  >ramimage Sc! ;
 : 2@ ( taddr -- x1 x2 ) T dup cell+ @ swap @ H ;  : 2@ ( taddr -- x1 x2 ) T dup cell+ @ swap @ H ;
 : 2! ( x1 x2 taddr -- ) T tuck ! cell+ ! H ;  : 2! ( x1 x2 taddr -- ) T tuck ! cell+ ! H ;
   
Line 1239  T has? relocate H Line 1714  T has? relocate H
 : A!                    swap >address swap dup relon T ! H ;  : A!                    swap >address swap dup relon T ! H ;
 : A,    ( w -- )        >address T here H relon T , H ;  : A,    ( w -- )        >address T here H relon T , H ;
   
   \ high-level ghosts
   
 >CROSS  >CROSS
   
   Ghost (do)      Ghost (?do)                     2drop
   Ghost (for)                                     drop
   Ghost (loop)    Ghost (+loop)                   2drop
   Ghost (next)                                    drop
   Ghost (does>)   Ghost (does>1)  Ghost (does>2)  2drop drop
   Ghost compile,                                  drop
   Ghost (.")      Ghost (S")      Ghost (ABORT")  2drop drop
   Ghost (C")      Ghost c(abort") Ghost type      2drop drop
   Ghost '                                         drop
   
   \ user ghosts
   
   Ghost state drop
   
   \ \ --------------------        Host/Target copy etc.           29aug01jaw
   
   
   >CROSS
   
   : TD! >image DS! ;
   : TD@ >image DS@ ;
   
   : th-count ( taddr -- host-addr len )
   \G returns host address of target string
     assert1( tbyte 1 = )
     dup X c@ swap X char+ >image swap ;
   
   : ht-move ( haddr taddr len -- )
   \G moves data from host-addr to destination in target-addr
   \G character by character
     swap -rot bounds ?DO I c@ over X c! X char+ LOOP drop ;
   
   2Variable last-string
   
   : ht-string,  ( addr count -- )
     dup there swap last-string 2!
       dup T c, H bounds  ?DO  I c@ T c, H  LOOP ;
   : ht-mem, ( addr count )
       bounds ?DO  I c@  T c, H  LOOP ;
   
   >TARGET
   
   : count dup X c@ swap X char+ swap ;
   
   : on            >r -1 -1 r> TD!  ; 
   : off           T 0 swap ! H ;
   
 : tcmove ( source dest len -- )  : tcmove ( source dest len -- )
 \G cmove in target memory  \G cmove in target memory
   tchar * bounds    tchar * bounds
   ?DO  dup T c@ H I T c! H 1+    ?DO  dup T c@ H I T c! H 1+
   tchar +LOOP  drop ;    tchar +LOOP  drop ;
   
   : td, ( d -- )
   \G Store a host value as one cell into the target
     there tcell X allot TD! ;
   
 \ \ Load Assembler  \ \ Load Assembler
   
 >TARGET  >TARGET
 H also Forth definitions  H also Forth definitions
   
 : X     bl word count [ ' target >wordlist ] Literal search-wordlist  \ FIXME: should we include the assembler really in the forth 
         IF      state @ IF compile,  \ dictionary?!?!?!? This conflicts with the existing assembler 
                 ELSE execute THEN  \ of the host forth system!!
         ELSE    -1 ABORT" Cross: access method not supported!"  
         THEN ; immediate  
   
 [IFDEF] asm-include asm-include [THEN] hex  [IFDEF] asm-include asm-include [THEN] hex
   
 previous  previous
 >CROSS H  
   
 \ \ --------------------        Compiler Plug Ins               01aug97jaw  
   
 \  Compiler States  
   
 Variable comp-state  
 0 Constant interpreting  
 1 Constant compiling  
 2 Constant resolving  
 3 Constant assembling  
   
 Defer lit, ( n -- )  
 Defer alit, ( n -- )  
   
 Defer branch, ( target-addr -- )        \ compiles a branch  
 Defer ?branch, ( target-addr -- )       \ compiles a ?branch  
 Defer branchmark, ( -- branch-addr )    \ reserves room for a branch  
 Defer ?branchmark, ( -- branch-addr )   \ reserves room for a ?branch  
 Defer ?domark, ( -- branch-addr )       \ reserves room for a ?do branch  
 Defer branchto, ( -- )                  \ actual program position is target of a branch (do e.g. alignment)  
 Defer branchtoresolve, ( branch-addr -- ) \ resolves a forward reference from branchmark  
 Defer branchfrom, ( -- )                \ ?!  
 Defer branchtomark, ( -- target-addr )  \ marks a branch destination  
   
 Defer colon, ( tcfa -- )                \ compiles call to tcfa at current position  
 Defer colonmark, ( -- addr )            \ marks a colon call  
 Defer colon-resolve ( tcfa addr -- )  
   
 Defer addr-resolve ( target-addr addr -- )  
 Defer doer-resolve ( ghost res-pnt target-addr addr -- ghost res-pnt )  
   
 Defer do,       ( -- do-token )  
 Defer ?do,      ( -- ?do-token )  
 Defer for,      ( -- for-token )  
 Defer loop,     ( do-token / ?do-token -- )  
 Defer +loop,    ( do-token / ?do-token -- )  
 Defer next,     ( for-token )  
   
 [IFUNDEF] ca>native  
 defer ca>native   
 [THEN]  
   
 >TARGET  
 DEFER >body             \ we need the system >body  
                         \ and the target >body  
 >CROSS  >CROSS
 T 2 cells H VALUE xt>body  
 DEFER doprim,   \ compiles start of a primitive  
 DEFER docol,    \ compiles start of a colon definition  
 DEFER doer,               
 DEFER fini,      \ compiles end of definition ;s  
 DEFER doeshandler,  
 DEFER dodoes,  
   
 DEFER ]comp     \ starts compilation  
 DEFER comp[     \ ends compilation  
   
 : (cc) T a, H ;                                 ' (cc) IS colon,  : (cc) T a, H ;                                 ' (cc) plugin-of colon,
   : (prim) T a, H ;                               ' (prim) plugin-of prim,
   
 : (cr) >tempdp ]comp colon, comp[ tempdp> ;     ' (cr) IS colon-resolve  : (cr) >tempdp colon, tempdp> ;                 ' (cr) plugin-of colon-resolve
 : (ar) T ! H ;                                  ' (ar) IS addr-resolve  : (ar) T ! H ;                                  ' (ar) plugin-of addr-resolve
 : (dr)  ( ghost res-pnt target-addr addr )  : (dr)  ( ghost res-pnt target-addr addr )
         >tempdp drop over           >tempdp drop over 
         dup >magic @ <do:> =          dup >magic @ <do:> =
         IF      doer,          IF      doer,
         ELSE    dodoes,          ELSE    dodoes,
         THEN           THEN 
         tempdp> ;                               ' (dr) IS doer-resolve          tempdp> ;                               ' (dr) plugin-of doer-resolve
   
 : (cm) ( -- addr )  : (cm) ( -- addr )
     T here align H      there -1 colon, ;                           ' (cm) plugin-of colonmark,
     -1 colon, ;                                 ' (cm) IS colonmark,  
   
 >TARGET  >TARGET
 : compile, colon, ;  : compile, ( xt -- )
     dup xt>ghost >comp @ EXECUTE ;
 >CROSS  >CROSS
   
 \ resolve structure  \ resolve structure
Line 1350  DEFER comp[     \ ends compilation Line 1822  DEFER comp[     \ ends compilation
   
 : (refered) ( ghost addr tag -- )  : (refered) ( ghost addr tag -- )
 \G creates a reference to ghost at address taddr  \G creates a reference to ghost at address taddr
     rot >r here r@ >link @ , r> >link !       >space
       rot >link linked
     ( taddr tag ) ,      ( taddr tag ) ,
     ( taddr ) ,       ( taddr ) , 
     last-header-ghost @ ,       last-header-ghost @ , 
     loadfile ,       loadfile , 
     sourceline# ,       sourceline# , 
   ;      space>
   ;
   
 : refered ( ghost tag -- )  : refered ( ghost tag -- )
 \G creates a resolve structure  \G creates a resolve structure
Line 1409  Defer resolve-warning Line 1883  Defer resolve-warning
   
 \ exists                                                9may93jaw  \ exists                                                9may93jaw
   
 Variable TWarnings  
 TWarnings on  
 Variable Exists-Warnings  
 Exists-Warnings on  
   
 : exists ( ghost tcfa -- )  : exists ( ghost tcfa -- )
   over GhostNames  \G print warning and set new target link in ghost
   BEGIN @ dup    swap exists-warning
   WHILE 2dup cell+ @ =    >link ! ;
   UNTIL  
         2 cells + count  : colon-resolved   ( ghost -- )
         TWarnings @ Exists-Warnings @ and  \ compiles a call to a colon definition,
         IF warnhead type ."  exists"  \ compile action for >comp field
         ELSE 2drop THEN      >link @ colon, ; 
         drop swap >link !  
   ELSE  true abort" CROSS: Ghostnames inconsistent "  : prim-resolved  ( ghost -- )
   THEN ;  \ compiles a call to a primitive
       >link @ prim, ;
   
   : (is-forward)   ( ghost -- )
       colonmark, 0 (refered) ; \ compile space for call
   ' (is-forward) IS is-forward
   
 : resolve  ( ghost tcfa -- )  0 Value resolved
 \G resolve referencies to ghost with tcfa  
     \ is ghost resolved?, second resolve means another definition with the  : resolve-forward-references ( ghost resolve-list -- )
     \ same name  
     over undefined? 0= IF  exists EXIT THEN  
     \ get linked-list  
     swap >r r@ >link @ swap \ ( list tcfa R: ghost )  
     \ mark ghost as resolved  
     dup r@ >link ! <res> r@ >magic !  
     \ loop through forward referencies      \ loop through forward referencies
     r> -rot   
     comp-state @ >r Resolving comp-state !      comp-state @ >r Resolving comp-state !
     resolve-loop       over >link @ resolve-loop 
     r> comp-state !      r> comp-state !
   
     ['] noop IS resolve-warning       ['] noop IS resolve-warning ;
   ;  
   
 \ gexecute ghost,                                      01nov92py  
   
 : is-forward   ( ghost -- )  : (resolve) ( ghost tcfa -- ghost resolve-list )
   colonmark, 0 (refered) ; \ compile space for call      \ check for a valid address, it is a primitive reference
       \ otherwise
       dup taddr>region 0<> IF
         \ define this address in the region address type table
         2dup (>regiontype) define-addr-struct addr-xt-ghost 
         \ we define new address only if empty
         \ this is for not to take over the alias ghost
         \ (different ghost, but identical xt)
         \ but the very first that really defines it
         dup @ 0= IF ! ELSE 2drop THEN
       THEN
       swap >r
       r@ to resolved
   
 : is-resolved   ( ghost -- )  \    r@ >comp @ ['] is-forward =
   >link @ colon, ; \ compile-call  \    ABORT" >comp action not set on a resolved ghost"
   
 : gexecute   ( ghost -- )      \ copmile action defaults to colon-resolved
   dup @ <fwd> = IF  is-forward  ELSE  is-resolved  THEN ;      \ if this is not right something must be set before
       \ calling resolve
       r@ >comp @ ['] is-forward = IF
          ['] colon-resolved r@ >comp !
      THEN
       r@ >link @ swap \ ( list tcfa R: ghost )
       \ mark ghost as resolved
       r@ >link ! <res> r@ >magic !
       r> swap ;
   
 : addr,  ( ghost -- )  : resolve  ( ghost tcfa -- )
   dup @ <fwd> = IF  1 refered 0 T a, H ELSE >link @ T a, H THEN ;  \G resolve referencies to ghost with tcfa
       \ is ghost resolved?, second resolve means another 
       \ definition with the same name
       over undefined? 0= IF  exists EXIT THEN
       (resolve)
       ( ghost resolve-list )
       resolve-forward-references ;
   
   : resolve-noforwards ( ghost tcfa -- )
   \G Same as resolve but complain if there are any
   \G forward references on this ghost
      \ is ghost resolved?, second resolve means another 
      \ definition with the same name
      over undefined? 0= IF  exists EXIT THEN
      (resolve)
      IF cr ." No forward references allowed on: " .ghost cr
         -1 ABORT" Illegal forward reference"
      THEN
      drop ;
   
   \ gexecute ghost,                                      01nov92py
   
 \ !! : ghost,     ghost  gexecute ;  : (gexecute)   ( ghost -- )
     dup >comp @ EXECUTE ;
   
   : gexecute ( ghost -- )
     dup >magic @ <imm> = ABORT" CROSS: gexecute on immediate word"
     (gexecute) ;
   
   : addr,  ( ghost -- )
     dup forward? IF  1 refered 0 T a, H ELSE >link @ T a, H THEN ;
   
 \ .unresolved                                          11may93jaw  \ .unresolved                                          11may93jaw
   
Line 1471  variable ResolveFlag Line 1984  variable ResolveFlag
                                0 <> and ;                                 0 <> and ;
   
 : .forwarddefs ( ghost -- )  : .forwarddefs ( ghost -- )
         ."  appeared in:"    ."  appeared in:"
         >link    >link
         BEGIN   @ dup    BEGIN @ dup
         WHILE   cr 5 spaces    WHILE cr 5 spaces
                 dup >ghost @ .ghost          dup >ghost @ .ghost
                 ."  file " dup >file @ ?dup IF count type ELSE ." CON" THEN          ."  file " dup >file @ ?dup IF count type ELSE ." CON" THEN
                 ."  line " dup >line @ .dec          ."  line " dup >line @ .dec
         REPEAT     REPEAT 
         drop ;    drop ;
   
 : ?resolved  ( ghostname -- )  : ?resolved  ( ghost -- )
   dup cell+ @ ?touched    dup ?touched
   IF    dup     IF    ResolveFlag on 
         cell+ cell+ count cr type ResolveFlag on           dup cr .ghost .forwarddefs
         cell+ @ .forwarddefs  
   ELSE  drop     ELSE  drop 
   THEN ;    THEN ;
   
 : .unresolved  ( -- )  : .unresolved  ( -- )
   ResolveFlag off cr ." Unresolved: "    ResolveFlag off cr ." Unresolved: "
   Ghostnames    ghost-list
   BEGIN @ dup    BEGIN @ dup
   WHILE dup ?resolved    WHILE dup ?resolved
   REPEAT drop ResolveFlag @    REPEAT drop ResolveFlag @
Line 1514  variable ResolveFlag Line 2026  variable ResolveFlag
 >CROSS  >CROSS
 \ Header states                                        12dec92py  \ Header states                                        12dec92py
   
 : flag! ( 8b -- )   tlast @ dup >r T c@ xor r> c! H ;  \ : flag! ( 8b -- )   tlast @ dup >r T c@ xor r> c! H ;
   X has? f83headerstring bigendian or [IF] 0 [ELSE] tcell 1- [THEN] Constant flag+
   : flag! ( w -- )   tlast @ flag+ + dup >r T c@ xor r> c! H ;
   
 VARIABLE ^imm  VARIABLE ^imm
   
   \ !! should be target wordsize specific
   $80 constant alias-mask
   $40 constant immediate-mask
   $20 constant restrict-mask
   
 >TARGET  >TARGET
 : immediate     40 flag!  : immediate     immediate-mask flag!
                 ^imm @ @ dup <imm> = IF  drop  EXIT  THEN                  ^imm @ @ dup <imm> = IF  drop  EXIT  THEN
                 <res> <> ABORT" CROSS: Cannot immediate a unresolved word"                  <res> <> ABORT" CROSS: Cannot immediate a unresolved word"
                 <imm> ^imm @ ! ;                  <imm> ^imm @ ! ;
 : restrict      20 flag! ;  : restrict      restrict-mask flag! ;
   
 : isdoer          : isdoer        
 \G define a forth word as doer, this makes obviously only sence on  \G define a forth word as doer, this makes obviously only sence on
Line 1533  VARIABLE ^imm Line 2052  VARIABLE ^imm
   
 \ Target Header Creation                               01nov92py  \ Target Header Creation                               01nov92py
   
   : ht-lstring, ( addr count -- )
     dup T , H bounds  ?DO  I c@ T c, H  LOOP ;
   
 >TARGET  >TARGET
 : string,  ( addr count -- )  X has? f83headerstring [IF]
   dup T c, H bounds  ?DO  I c@ T c, H  LOOP ;   : name,  ( "name" -- )  bl word count ht-string, X cfalign ;
 : name,  ( "name" -- )  bl word count T string, cfalign H ;  [ELSE]
   : name,  ( "name" -- )  bl word count ht-lstring, X cfalign ;
   [THEN]
 : view,   ( -- ) ( dummy ) ;  : view,   ( -- ) ( dummy ) ;
 >CROSS  >CROSS
   
Line 1557  Variable to-doc  to-doc on Line 2081  Variable to-doc  to-doc on
         s" " doc-file-id write-line throw          s" " doc-file-id write-line throw
         s" make-doc " doc-file-id write-file throw          s" make-doc " doc-file-id write-file throw
   
         tlast @ >image count 1F and doc-file-id write-file throw          Last-Header-Ghost @ >ghostname doc-file-id write-file throw
         >in @          >in @
         [char] ( parse 2drop          [char] ( parse 2drop
         [char] ) parse doc-file-id write-file throw          [char] ) parse doc-file-id write-file throw
Line 1570  Variable to-doc  to-doc on Line 2094  Variable to-doc  to-doc on
 \ Target TAGS creation  \ Target TAGS creation
   
 s" kernel.TAGS" r/w create-file throw value tag-file-id  s" kernel.TAGS" r/w create-file throw value tag-file-id
   s" kernel.tags" r/w create-file throw value vi-tag-file-id
 \ contains the file-id of the tags file  \ contains the file-id of the tags file
   
 Create tag-beg 2 c,  7F c, bl c,  Create tag-beg 1 c,  7F c,
 Create tag-end 2 c,  bl c, 01 c,  Create tag-end 1 c,  01 c,
 Create tag-bof 1 c,  0C c,  Create tag-bof 1 c,  0C c,
   Create tag-tab 1 c,  09 c,
   
 2variable last-loadfilename 0 0 last-loadfilename 2!  2variable last-loadfilename 0 0 last-loadfilename 2!
                           
Line 1588  Create tag-bof 1 c,  0C c, Line 2114  Create tag-bof 1 c,  0C c,
         s" ,0" tag-file-id write-line throw          s" ,0" tag-file-id write-line throw
     THEN ;      THEN ;
   
 : cross-tag-entry  ( -- )  : cross-gnu-tag-entry  ( -- )
     tlast @ 0<> \ not an anonymous (i.e. noname) header      tlast @ 0<> \ not an anonymous (i.e. noname) header
     IF      IF
         put-load-file-name          put-load-file-name
         source >in @ min tag-file-id write-file throw          source >in @ min tag-file-id write-file throw
         tag-beg count tag-file-id write-file throw          tag-beg count tag-file-id write-file throw
         tlast @ >image count 1F and tag-file-id write-file throw          Last-Header-Ghost @ >ghostname tag-file-id write-file throw
         tag-end count tag-file-id write-file throw          tag-end count tag-file-id write-file throw
         base @ decimal sourceline# 0 <# #s #> tag-file-id write-file throw          base @ decimal sourceline# 0 <# #s #> tag-file-id write-file throw
 \       >in @ 0 <# #s [char] , hold #> tag-file-id write-line throw  \       >in @ 0 <# #s [char] , hold #> tag-file-id write-line throw
Line 1602  Create tag-bof 1 c,  0C c, Line 2128  Create tag-bof 1 c,  0C c,
         base !          base !
     THEN ;      THEN ;
   
   : cross-vi-tag-entry ( -- )
       tlast @ 0<> \ not an anonymous (i.e. noname) header
       IF
           sourcefilename vi-tag-file-id write-file throw
           tag-tab count vi-tag-file-id write-file throw
           Last-Header-Ghost @ >ghostname vi-tag-file-id write-file throw
           tag-tab count vi-tag-file-id write-file throw
           s" /^" vi-tag-file-id write-file throw
           source vi-tag-file-id write-file throw
           s" $/" vi-tag-file-id write-line throw
       THEN ;
   
   : cross-tag-entry ( -- )
       cross-gnu-tag-entry
       cross-vi-tag-entry ;
   
 \ Check for words  \ Check for words
   
 Defer skip? ' false IS skip?  Defer skip? ' false IS skip?
   
 : skipdef ( <name> -- )  : skipdef ( "name" -- )
 \G skip definition of an undefined word in undef-words and  \G skip definition of an undefined word in undef-words and
 \G all-words mode  \G all-words mode
     ghost dup forward?      Ghost dup forward?
     IF  >magic <skip> swap !      IF  >magic <skip> swap !
     ELSE drop THEN ;      ELSE drop THEN ;
   
 : tdefined? ( -- flag ) \ name  : tdefined? ( "name" -- flag ) 
     ghost undefined? 0= ;      Ghost undefined? 0= ;
   
 : defined2? ( -- flag ) \ name  : defined2? ( "name" -- flag ) 
 \G return true for anything else than forward, even for <skip>  \G return true for anything else than forward, even for <skip>
 \G that's what we want  \G that's what we want
     ghost forward? 0= ;      Ghost forward? 0= ;
   
 : forced? ( -- flag ) \ name  : forced? ( "name" -- flag )
 \G return ture if it is a foreced skip with defskip  \G return ture if it is a foreced skip with defskip
     ghost >magic @ <skip> = ;      Ghost >magic @ <skip> = ;
   
 : needed? ( -- flag ) \ name  : needed? ( -- flag ) \ name
 \G returns a false flag when  \G returns a false flag when
Line 1636  Defer skip? ' false IS skip? Line 2178  Defer skip? ' false IS skip?
         0=          0=
     ELSE  drop true  THEN ;      ELSE  drop true  THEN ;
   
 : doer? ( -- flag ) \ name  : doer? ( "name" -- 0 | addr ) \ name
     ghost >magic @ <do:> = ;      Ghost dup >magic @ <do:> = 
       IF >link @ ELSE drop 0 THEN ;
   
 : skip-defs ( -- )  : skip-defs ( -- )
     BEGIN  refill  WHILE  source -trailing nip 0= UNTIL  THEN ;      BEGIN  refill  WHILE  source -trailing nip 0= UNTIL  THEN ;
Line 1651  NoHeaderFlag off Line 2194  NoHeaderFlag off
     base @ >r hex       base @ >r hex 
     0 swap <# 0 ?DO # LOOP #> type       0 swap <# 0 ?DO # LOOP #> type 
     r> base ! ;      r> base ! ;
 : .sym  
   : .sym ( adr len -- )
   \G escapes / and \ to produce sed output
   bounds     bounds 
   DO I c@ dup    DO I c@ dup
         CASE    [char] / OF drop ." \/" ENDOF          CASE    [char] / OF drop ." \/" ENDOF
Line 1660  NoHeaderFlag off Line 2205  NoHeaderFlag off
         ENDCASE          ENDCASE
     LOOP ;      LOOP ;
   
 : (Theader ( "name" -- ghost )  Defer setup-execution-semantics  ' noop IS setup-execution-semantics
   0 Value lastghost
   
   : (THeader ( "name" -- ghost )
     \  >in @ bl word count type 2 spaces >in !      \  >in @ bl word count type 2 spaces >in !
     \ wordheaders will always be compiled to rom      \ wordheaders will always be compiled to rom
     switchrom      switchrom
Line 1674  NoHeaderFlag off Line 2222  NoHeaderFlag off
         >in @ T name, H >in !          >in @ T name, H >in !
     THEN      THEN
     T cfalign here H tlastcfa !      T cfalign here H tlastcfa !
     \ Symbol table      \ Old Symbol table sed-script
 \    >in @ cr ." sym:s/CFA=" there 4 0.r ." /"  bl word count .sym ." /g" cr >in !  \    >in @ cr ." sym:s/CFA=" there 4 0.r ." /"  bl word count .sym ." /g" cr >in !
     ghost      HeaderGhost
     dup Last-Header-Ghost !      \ output symbol table to extra file
       dup >ghostname there symentry
       dup Last-Header-Ghost ! dup to lastghost
     dup >magic ^imm !     \ a pointer for immediate      dup >magic ^imm !     \ a pointer for immediate
     Already @      alias-mask flag!
     IF  dup >end tdoes !      cross-doc-entry cross-tag-entry 
     ELSE 0 tdoes !      setup-execution-semantics
     THEN      ;
     80 flag!  
     cross-doc-entry cross-tag-entry ;  
   
 VARIABLE ;Resolve 1 cells allot  
 \ this is the resolver information from ":"  \ this is the resolver information from ":"
 \ resolving is done by ";"  \ resolving is done by ";"
   Variable ;Resolve 1 cells allot
   
   : hereresolve ( ghost -- )
     there resolve 0 ;Resolve ! ;
   
 : Theader  ( "name" -- ghost )  : Theader  ( "name" -- ghost )
   (THeader dup there resolve 0 ;Resolve ! ;    (THeader dup hereresolve ;
   
   Variable aprim-nr -20 aprim-nr !
   
   : copy-execution-semantics ( ghost-from ghost-dest -- )
     >r
     dup >exec @ r@ >exec !
     dup >comp @ r@ >comp !
     dup >exec2 @ r@ >exec2 !
     dup >exec-compile @ r@ >exec-compile !
     dup >ghost-xt @ r@ >ghost-xt !
     dup >created @ r@ >created !
     rdrop drop ;
   
 >TARGET  >TARGET
   
 : Alias    ( cfa -- ) \ name  : Alias    ( cfa -- ) \ name
     >in @ skip? IF  2drop  EXIT  THEN  >in !    >in @ skip? IF  2drop  EXIT  THEN  >in !
     dup 0< s" prims" T $has? H 0= and    (THeader ( S xt ghost )
     IF    2dup swap xt>ghost swap copy-execution-semantics
         .sourcepos ." needs prim: " >in @ bl word count type >in ! cr    over resolve T A, H alias-mask flag! ;
     THEN  
     (THeader over resolve T A, H 80 flag! ;  Variable last-prim-ghost
 : Alias:   ( cfa -- ) \ name  0 last-prim-ghost !
     >in @ skip? IF  2drop  EXIT  THEN  >in !  
     dup 0< s" prims" T $has? H 0= and  : asmprimname, ( ghost -- : name ) 
     IF    dup last-prim-ghost !
         .sourcepos ." needs doer: " >in @ bl word count type >in ! cr    >r
     THEN    here bl word count string, r@ >asm-name !
     ghost tuck swap resolve <do:> swap >magic ! ;    aprim-nr @ r> >asm-dummyaddr ! ;
   
   Defer setup-prim-semantics
   
   : mapprim   ( "forthname" "asmlabel" -- ) 
     THeader -1 aprim-nr +! aprim-nr @ T A, H
     asmprimname, 
     setup-prim-semantics ;
   
   : mapprim:   ( "forthname" "asmlabel" -- ) 
     -1 aprim-nr +! aprim-nr @
     Ghost tuck swap resolve-noforwards <do:> swap tuck >magic !
     asmprimname, ;
   
   : Doer:   ( cfa -- ) \ name
     >in @ skip? IF  2drop  EXIT  THEN  >in !
     dup 0< s" prims" T $has? H 0= and
     IF
         .sourcepos ." needs doer: " >in @ bl word count type >in ! cr
     THEN
     Ghost
     tuck swap resolve-noforwards <do:> swap >magic ! ;
   
 Variable prim#  Variable prim#
 : first-primitive ( n -- )  prim# ! ;  : first-primitive ( n -- )  prim# ! ;
   : group 0 word drop prim# @ 1- -$200 and prim# ! ;
   : groupadd  ( n -- )  drop ;
 : Primitive  ( -- ) \ name  : Primitive  ( -- ) \ name
     prim# @ T Alias H  -1 prim# +! ;    >in @ skip? IF  drop  EXIT  THEN  >in !
     s" prims" T $has? H 0=
     IF
        .sourcepos ." needs prim: " >in @ bl word count type >in ! cr
     THEN
     prim# @ (THeader ( S xt ghost )
     ['] prim-resolved over >comp !
     dup >ghost-flags <primitive> set-flag
     over resolve-noforwards T A, H alias-mask flag!
     -1 prim# +! ;
 >CROSS  >CROSS
   
 \ Conditionals and Comments                            11may93jaw  \ Conditionals and Comments                            11may93jaw
   
   \G saves the existing cond action, this is used for redefining in
   \G instant
   Variable cond-xt-old
   
   : cond-target ( -- )
   \G Compiles semantic of redefined cond into new one
     cond-xt-old @ compile, ; immediate restrict
   
 : ;Cond  : ;Cond
   postpone ;    postpone ;
   swap ! ;  immediate    swap ! ;  immediate
   
 : Cond: ( -- ) \ name {code } ;  : Cond: ( "name" -- ) 
   atonce on  \g defines a conditional or another word that must
   ghost  \g be executed directly while compiling
   >exec  \g these words have no interpretative semantics by default
     Ghost
     >exec-compile
     dup @ cond-xt-old !
   :NONAME ;    :NONAME ;
   
 : restrict? ( -- )  
 \ aborts on interprete state - ae  
   state @ 0= ABORT" CROSS: Restricted" ;  
   
 : Comment ( -- )  : Comment ( -- )
   >in @ atonce on ghost swap >in ! ' swap >exec ! ;    >in @ Ghost swap >in ! ' swap 
     2dup >exec-compile ! >exec ! ;
   
 Comment (       Comment \  Comment (       Comment \
   
 \ compile                                              10may93jaw  \ compile                                              10may93jaw
   
 : compile  ( -- ) \ name  : compile  ( "name" -- ) \ name
   restrict?    findghost
   bl word gfind dup 0= ABORT" CROSS: Can't compile "    dup >exec-compile @ ?dup
   0> ( immediate? )    IF    nip compile,
   IF    >exec @ compile,    ELSE  postpone literal postpone gexecute  THEN ;  immediate restrict
   ELSE  postpone literal postpone gexecute  THEN ;              
                                         immediate  
   
 : [G']   
 \G ticks a ghost and returns its address  
   bl word gfind 0= ABORT" CROSS: Ghost don't exists"  
   state @  
   IF   postpone literal  
   THEN ; immediate  
   
 : ghost>cfa  
   dup undefined? ABORT" CROSS: forward " >link @ ;  
                  
 >TARGET  >TARGET
   
 : '  ( -- cfa )   : '  ( -- xt ) 
 \ returns the target-cfa of a ghost  \G returns the target-cfa of a ghost
   bl word gfind 0= ABORT" CROSS: Ghost don't exists"    bl word gfind 0= ABORT" CROSS: Ghost don't exists"
   ghost>cfa ;    g>xt ;
   
   \ FIXME: this works for the current use cases, but is not
   \ in all cases correct ;-) 
   : comp' X ' 0 ;
   
 Cond: [']  T ' H alit, ;Cond  Cond: [']  T ' H alit, ;Cond
   
Line 1769  Cond: [']  T ' H alit, ;Cond Line 2366  Cond: [']  T ' H alit, ;Cond
   
 : [T']  : [T']
 \ returns the target-cfa of a ghost, or compiles it as literal  \ returns the target-cfa of a ghost, or compiles it as literal
   postpone [G'] state @ IF postpone ghost>cfa ELSE ghost>cfa THEN ; immediate    postpone [G'] 
     state @ IF postpone g>xt ELSE g>xt THEN ; immediate
   
 \ \ threading modell                                    13dec92py  \ \ threading modell                                    13dec92py
 \ modularized                                           14jun97jaw  \ modularized                                           14jun97jaw
   
   T 2 cells H Value xt>body
   
   : (>body)   ( cfa -- pfa ) 
     xt>body + ;                                           ' (>body) plugin-of t>body
   
 : fillcfa   ( usedcells -- )  : fillcfa   ( usedcells -- )
   T cells H xt>body swap - 0 ?DO 0 X c, tchar +LOOP ;    T cells H xt>body swap -
     assert1( dup 0 >= )
     0 ?DO 0 X c, tchar +LOOP ;
   
 : (>body)   ( cfa -- pfa ) xt>body + ;          ' (>body) T IS >body H  : (doer,)   ( ghost -- ) 
     addr, 1 fillcfa ;                                     ' (doer,) plugin-of doer,
   
 : (doer,)   ( ghost -- ) ]comp gexecute comp[ 1 fillcfa ;   ' (doer,) IS doer,  : (docol,)  ( -- ) [G'] :docol (doer,) ;                ' (docol,) plugin-of docol,
   
 : (docol,)  ( -- ) [G'] :docol doer, ;          ' (docol,) IS docol,                                                          ' NOOP plugin-of ca>native
   
 : (doprim,) ( -- )  : (doprim,) ( -- )
   there xt>body + ca>native T a, H 1 fillcfa ;  ' (doprim,) IS doprim,    there xt>body + ca>native T a, H 1 fillcfa ;          ' (doprim,) plugin-of doprim,
   
 : (doeshandler,) ( -- )   : (doeshandler,) ( -- ) 
   T cfalign H compile :doesjump T 0 , H ;       ' (doeshandler,) IS doeshandler,    T cfalign H [G'] :doesjump addr, T 0 , H ;            ' (doeshandler,) plugin-of doeshandler,
   
 : (dodoes,) ( does-action-ghost -- )  : (dodoes,) ( does-action-ghost -- )
   ]comp [G'] :dodoes gexecute comp[    ]comp [G'] :dodoes addr, comp[
   addr,    addr,
   T here H tcell - reloff 2 fillcfa ;           ' (dodoes,) IS dodoes,    \ the relocator in the c engine, does not like the
     \ does-address to marked for relocation
     [ T e? ec H 0= [IF] ] T here H tcell - reloff [ [THEN] ]
     2 fillcfa ;                                           ' (dodoes,) plugin-of dodoes,
   
   : (dlit,) ( n -- ) compile lit td, ;                    ' (dlit,) plugin-of dlit,
   
 : (lit,) ( n -- )   compile lit T  ,  H ;       ' (lit,) IS lit,  : (lit,) ( n -- )  s>d dlit, ;                          ' (lit,) plugin-of lit,
   
 \ if we dont produce relocatable code alit, defaults to lit, jaw  \ if we dont produce relocatable code alit, defaults to lit, jaw
 has? relocate  \ this is just for convenience, so we don't have to define alit,
   \ seperately for embedded systems....
   T has? relocate H
 [IF]  [IF]
 : (alit,) ( n -- )  compile lit T  a, H ;       ' (alit,) IS alit,  : (alit,) ( n -- )  compile lit T  a, H ;               ' (alit,) plugin-of alit,
 [ELSE]  [ELSE]
 : (alit,) ( n -- )  lit, ;                      ' (alit,) IS alit,  : (alit,) ( n -- )  lit, ;                              ' (alit,) plugin-of alit,
 [THEN]  [THEN]
   
 : (fini,)         compile ;s ;                ' (fini,) IS fini,  : (fini,)         compile ;s ;                          ' (fini,) plugin-of fini,
   
 [IFUNDEF] (code)   [IFUNDEF] (code) 
 Defer (code)  Defer (code)
Line 1814  Defer (end-code) Line 2427  Defer (end-code)
 >TARGET  >TARGET
 : Code  : Code
   defempty?    defempty?
   (THeader there resolve    (THeader ( ghost )
     ['] prim-resolved over >comp !
     there resolve-noforwards
     
   [ T e? prims H 0= [IF] T e? ITC H [ELSE] true [THEN] ] [IF]    [ T e? prims H 0= [IF] T e? ITC H [ELSE] true [THEN] ] [IF]
   doprim,     doprim, 
   [THEN]    [THEN]
   depth (code) ;    depth (code) ;
   
   \ FIXME : no-compile -1 ABORT" this ghost is not for compilation" ;
   
 : Code:  : Code:
   defempty?    defempty?
     ghost dup there ca>native resolve  <do:> swap >magic !      Ghost >r 
       r@ >ghostname there symentry
       r@ there ca>native resolve-noforwards
       <do:> r@ >magic !
       r> drop
     depth (code) ;      depth (code) ;
   
 : end-code  : end-code
Line 1838  Defer (end-code) Line 2460  Defer (end-code)
 >TARGET  >TARGET
 Cond: \G  T-\G ;Cond  Cond: \G  T-\G ;Cond
   
 Cond:  Literal ( n -- )   restrict? lit, ;Cond  Cond: Literal  ( n -- )   lit, ;Cond
 Cond: ALiteral ( n -- )   restrict? alit, ;Cond  Cond: ALiteral ( n -- )   alit, ;Cond
   
 : Char ( "<char>" -- )  bl word char+ c@ ;  : Char ( "<char>" -- )  bl word char+ c@ ;
 Cond: [Char]   ( "<char>" -- )  restrict? Char  lit, ;Cond  Cond: [Char]   ( "<char>" -- )  Char  lit, ;Cond
   
 \ some special literals                                 27jan97jaw  : (x#) ( adr len base -- )
     base @ >r base ! 0 0 name >number 2drop drop r> base ! ;
   
   : d# $0a (x#) ;
   : h# $010 (x#) ;
   
   Cond: d# $0a (x#) lit, ;Cond
   Cond: h# $010 (x#) lit, ;Cond
   
 \ !! Known Bug: Special Literals and plug-ins work only correct  tchar 1 = [IF]
 \ on 16 and 32 Bit Targets and 32 Bit Hosts!  Cond: chars ;Cond 
   [THEN]
   
   \ some special literals                                 27jan97jaw
   
 Cond: MAXU  Cond: MAXU
   restrict?     -1 s>d dlit,
   tcell 1 cells u>   
   IF    compile lit tcell 0 ?DO FF T c, H LOOP   
   ELSE  ffffffff lit, THEN  
   ;Cond    ;Cond
   
   tcell 2 = tcell 4 = or tcell 8 = or 0=
   [IF]
   .( Warning: MINI and MAXI may not work with this host) cr
   [THEN]
   
 Cond: MINI  Cond: MINI
   restrict?    tcell 2 = IF $8000 ELSE $80000000 THEN 0
   tcell 1 cells u>    tcell 8 = IF swap THEN dlit,
   IF    compile lit bigendian   
         IF      80 T c, H tcell 1 ?DO 0 T c, H LOOP   
         ELSE    tcell 1 ?DO 0 T c, H LOOP 80 T c, H  
         THEN  
   ELSE  tcell 2 = IF 8000 ELSE 80000000 THEN lit, THEN  
   ;Cond    ;Cond
     
 Cond: MAXI  Cond: MAXI
  restrict?    tcell 2 = IF $7fff ELSE $7fffffff THEN 0
  tcell 1 cells u>    tcell 8 = IF drop -1 swap THEN dlit,
  IF     compile lit bigendian     ;Cond
         IF      7F T c, H tcell 1 ?DO FF T c, H LOOP  
         ELSE    tcell 1 ?DO FF T c, H LOOP 7F T c, H  
         THEN  
  ELSE   tcell 2 = IF 7fff ELSE 7fffffff THEN lit, THEN  
  ;Cond  
   
 >CROSS  >CROSS
   
 \ Target compiling loop                                12dec92py  \ Target compiling loop                                12dec92py
 \ ">tib trick thrown out                               10may93jaw  \ ">tib trick thrown out                               10may93jaw
 \ number? defined at the top                           11may93jaw  \ number? defined at the top                           11may93jaw
Line 1887  Cond: MAXI Line 2512  Cond: MAXI
 \ compiled word might leave items on stack!  \ compiled word might leave items on stack!
 : tcom ( x1 .. xn n name -- )  : tcom ( x1 .. xn n name -- )
 \  dup count type space  \  dup count type space
   gfind  ?dup    gfind 
   IF    >r >r discard r> r>    IF    >r ( discard saved input state ) discard r>
         0> IF   >exec @ execute          dup >exec-compile @ ?dup
         ELSE    gexecute  THEN           IF   nip execute-exec-compile ELSE gexecute  THEN 
         EXIT           EXIT 
   THEN    THEN
   number? dup      number? dup  
   IF    0> IF swap lit,  THEN  lit, discard    IF    0> IF swap lit,  THEN  lit, discard
   ELSE  2drop restore-input throw ghost gexecute THEN  ;    ELSE  2drop restore-input throw Ghost gexecute THEN  ;
   
 >TARGET  
 \ : ; DOES>                                            13dec92py  \ : ; DOES>                                            13dec92py
 \ ]                                                     9may93py/jaw  \ ]                                                     9may93py/jaw
   
 : ] state on  >CROSS
   
   : compiling-state ( -- )
   \G set states to compililng
     Compiling comp-state !      Compiling comp-state !
       \ if we have a state in target, change it with the compile state
       [G'] state dup undefined? 0= 
       IF >ghost-xt @ execute X on ELSE drop THEN ;
   
   : interpreting-state ( -- )
   \G set states to interpreting
      \ if target has a state variable, change it according to our state
      [G'] state dup undefined? 0= 
      IF >ghost-xt @ execute X off ELSE drop THEN
      Interpreting comp-state ! ;
   
   >TARGET
   
   : ] 
       compiling-state
     BEGIN      BEGIN
         BEGIN save-input bl word          BEGIN save-input bl word
               dup c@ 0= WHILE drop discard refill 0=                dup c@ 0= WHILE drop discard refill 0=
               ABORT" CROSS: End of file while target compiling"                ABORT" CROSS: End of file while target compiling"
         REPEAT          REPEAT
         tcom          tcom
         state @          compiling? 0=
         0=  
     UNTIL ;      UNTIL ;
   
 \ by the way: defining a second interpreter (a compiler-)loop  \ by the way: defining a second interpreter (a compiler-)loop
 \             is not allowed if a system should be ans conform  \             is not allowed if a system should be ans conform
   
   : (:) ( ghost -- ) 
   \ common factor of : and :noname. Prepare ;Resolve and start definition
      ;Resolve ! there ;Resolve cell+ !
      docol, ]comp  colon-start depth T ] H ;
   
 : : ( -- colon-sys ) \ Name  : : ( -- colon-sys ) \ Name
   defempty?    defempty?
   constflag off \ don't let this flag work over colon defs    constflag off \ don't let this flag work over colon defs
                 \ just to go sure nothing unwanted happens                  \ just to go sure nothing unwanted happens
   >in @ skip? IF  drop skip-defs  EXIT  THEN  >in !    >in @ skip? IF  drop skip-defs  EXIT  THEN  >in !
   (THeader ;Resolve ! there ;Resolve cell+ !    (THeader (:) ;
   docol, ]comp depth T ] H ;  
   
 : :noname ( -- colon-sys )  : :noname ( -- colon-sys )
   T cfalign H there docol, 0 ;Resolve ! depth T ] H ;    X cfalign there 
     \ define a nameless ghost
     here ghostheader dup last-header-ghost ! dup to lastghost
     (:) ;  
   
 Cond: EXIT ( -- )  restrict?  compile ;S  ;Cond  Cond: EXIT ( -- )   compile ;S  ;Cond
   
 Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond  Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond
   
Line 1937  Cond: ?EXIT ( -- ) 1 abort" CROSS: using Line 2585  Cond: ?EXIT ( -- ) 1 abort" CROSS: using
   
 >TARGET  >TARGET
   
 Cond: recurse ( -- ) Last-Ghost @ gexecute ;Cond  Cond: recurse ( -- ) Last-Header-Ghost @ gexecute ;Cond
   
 Cond: ; ( -- ) restrict?  Cond: ; ( -- ) 
                depth ?dup IF   1- <> ABORT" CROSS: Stack changed"          depth ?dup 
                           ELSE true ABORT" CROSS: Stack empty" THEN          IF   1- <> ABORT" CROSS: Stack changed"
                fini,          ELSE true ABORT" CROSS: Stack empty" 
                comp[          THEN
                state off          colon-end
                ;Resolve @          fini,
                IF ;Resolve @ ;Resolve cell+ @ resolve THEN          comp[
                 Interpreting comp-state !          ;Resolve @ 
                ;Cond          IF  ['] colon-resolved ;Resolve @ >comp !
 Cond: [  restrict? state off Interpreting comp-state ! ;Cond              ;Resolve @ ;Resolve cell+ @ resolve 
           THEN
           interpreting-state
           ;Cond
   
   Cond: [ ( -- ) interpreting-state ;Cond
   
 >CROSS  >CROSS
   
 Create GhostDummy ghostheader  0 Value created
 <res> GhostDummy >magic !  
   
 : !does ( does-action -- )  : !does ( does-action -- )
 \ !! zusammenziehen und dodoes, machen!  
     tlastcfa @ [G'] :dovar killref      tlastcfa @ [G'] :dovar killref
 \    tlastcfa @ dup there >r tdp ! compile :dodoes r> tdp ! T cell+ ! H ;      >space here >r ghostheader space>
 \ !! geht so nicht, da dodoes, ghost will!      ['] colon-resolved r@ >comp !
     GhostDummy >link ! GhostDummy       r@ created >do:ghost ! r@ swap resolve
     tlastcfa @ >tempdp dodoes, tempdp> ;      r> tlastcfa @ >tempdp dodoes, tempdp> ;
   
   Defer instant-interpret-does>-hook  ' noop IS instant-interpret-does>-hook
   
   T has? peephole H [IF]
   : does-resolved ( ghost -- )
       compile does-exec g>xt T a, H ;
   [ELSE]
   : does-resolved ( ghost -- )
       g>xt T a, H ;
   [THEN]
   
   : resolve-does>-part ( -- )
   \ resolve words made by builders
     Last-Header-Ghost @ >do:ghost @ ?dup 
     IF  there resolve  THEN ;
   
 >TARGET  >TARGET
 Cond: DOES> restrict?  Cond: DOES>
         compile (does>) doeshandler,           T here 5 cells H + alit, compile (does>2) compile ;s
         \ resolve words made by builders          doeshandler, resolve-does>-part
         tdoes @ ?dup IF  @ T here H resolve THEN  
         ;Cond          ;Cond
 : DOES> switchrom doeshandler, T here H !does depth T ] H ;  
   : DOES>
       ['] does-resolved created >comp !
       switchrom doeshandler, T here H !does 
       instant-interpret-does>-hook
       depth T ] H ;
   
 >CROSS  >CROSS
 \ Creation                                             01nov92py  \ Creation                                              01nov92py
   
 \ Builder                                               11may93jaw  \ Builder                                               11may93jaw
   
 : Builder    ( Create-xt do:-xt "name" -- )  0 Value built
   
   : Builder    ( Create-xt do-ghost "name" -- )
 \ builds up a builder in current vocabulary  \ builds up a builder in current vocabulary
 \ create-xt is executed when word is interpreted  \ create-xt is executed when word is interpreted
 \ do:-xt is executet when the created word from builder is executed  \ do:-xt is executed when the created word from builder is executed
 \ for do:-xt an additional entry after the normal ghost-enrys is used  \ for do:-xt an additional entry after the normal ghost-entrys is used
   
   Make-Ghost            ( Create-xt do:-xt ghost )    ghost to built 
   rot swap              ( do:-xt Create-xt ghost )    built >created @ 0= IF
   >exec ! , ;      built >created on
 \  rot swap >exec dup @ ['] NoExec <>    THEN ;
 \  IF 2drop ELSE ! THEN , ;  
   
 : gdoes,  ( ghost -- )  : gdoes,  ( ghost -- )
 \ makes the codefield for a word that is built  \ makes the codefield for a word that is built
   >end @ dup undefined? 0=    >do:ghost @ dup undefined? 0=
   IF    IF
         dup >magic @ <do:> =          dup >magic @ <do:> =
         IF       doer,           IF       doer, 
Line 2005  Cond: DOES> restrict? Line 2676  Cond: DOES> restrict?
   0 fillcfa    0 fillcfa
   ;    ;
   
   : takeover-x-semantics ( S constructor-ghost new-ghost -- )
      \g stores execution semantic and compilation semantic in the built word
      swap >do:ghost @ 2dup swap >do:ghost !
      \ we use the >exec2 field for the semantic of a created word,
      \ using exec or exec2 makes no difference for normal cross-compilation
      \ but is usefull for instant where the exec field is already
      \ defined (e.g. Vocabularies)
      2dup >exec @ swap >exec2 ! 
      >comp @ swap >comp ! ;
   
   0 Value createhere
   
   : create-resolve ( -- )
       created createhere resolve 0 ;Resolve ! ;
   : create-resolve-immediate ( -- )
       create-resolve T immediate H ;
   
 : TCreate ( <name> -- )  : TCreate ( <name> -- )
   executed-ghost @  
   create-forward-warn    create-forward-warn
   IF ['] reswarn-forward IS resolve-warning THEN    IF ['] reswarn-forward IS resolve-warning THEN
   Theader >r dup gdoes,    executed-ghost @ (Theader
 \ stores execution semantic in the built word    dup >created on  dup to created
 \ if the word already has a semantic (concerns S", IS, .", DOES>)    2dup takeover-x-semantics
 \ then keep it    there to createhere drop gdoes, ;
   >end @ >exec @ r> >exec dup @ ['] NoExec =  
   IF ! ELSE 2drop THEN ;  
   
 : RTCreate ( <name> -- )  : RTCreate ( <name> -- )
 \ creates a new word with code-field in ram  \ creates a new word with code-field in ram
   executed-ghost @  
   create-forward-warn    create-forward-warn
   IF ['] reswarn-forward IS resolve-warning THEN    IF ['] reswarn-forward IS resolve-warning THEN
   \ make Alias    \ make Alias
   (THeader there 0 T a, H 80 flag! ( S executed-ghost new-ghost )    executed-ghost @ (THeader 
   \ store  poiter to code-field    dup >created on  dup to created
     2dup takeover-x-semantics
     there 0 T a, H alias-mask flag!
     \ store poiter to code-field
   switchram T cfalign H    switchram T cfalign H
   there swap T ! H    there swap T ! H
   there tlastcfa !     there tlastcfa ! 
   dup there resolve 0 ;Resolve !    there to createhere drop gdoes, ;
   >r dup gdoes,  
 \ stores execution semantic in the built word  
 \ if the word already has a semantic (concerns S", IS, .", DOES>)  
 \ then keep it  
   >end @ >exec @ r> >exec dup @ ['] NoExec =  
   IF ! ELSE 2drop THEN ;  
   
 : Build:  ( -- [xt] [colon-sys] )  : Build:  ( -- [xt] [colon-sys] )
   :noname postpone TCreate ;    :noname postpone TCreate ;
Line 2046  Cond: DOES> restrict? Line 2727  Cond: DOES> restrict?
   postpone TCreate     postpone TCreate 
   [ [THEN] ] ;    [ [THEN] ] ;
   
   : ;Build
     postpone create-resolve postpone ; built >exec ! ; immediate
   
   : ;Build-immediate
       postpone create-resolve-immediate
       postpone ; built >exec ! ; immediate
   
 : gdoes>  ( ghost -- addr flag )  : gdoes>  ( ghost -- addr flag )
   executed-ghost @    executed-ghost @ g>body ;
   state @ IF  gexecute true EXIT  THEN  
   >link @ T >body H false ;  
   
 \ DO: ;DO                                               11may93jaw  \ DO: ;DO                                               11may93jaw
 \ changed to ?EXIT                                      10may93jaw  
   
 : DO:     ( -- addr [xt] [colon-sys] )  : do:ghost! ( ghost -- ) built >do:ghost ! ;
   here ghostheader  : doexec! ( xt -- ) built >do:ghost @ >exec ! ;
   :noname postpone gdoes> postpone ?EXIT ;  
   
 : by:     ( -- addr [xt] [colon-sys] ) \ name  
   ghost  
   :noname postpone gdoes> postpone ?EXIT ;  
   
 : ;DO ( addr [xt] [colon-sys] -- addr )  
   postpone ;    ( S addr xt )  
   over >exec ! ; immediate  
   
 : by      ( -- addr ) \ Name  : DO:     ( -- [xt] [colon-sys] )
   ghost >end @ ;    here ghostheader do:ghost!
     :noname postpone gdoes> ;
   
   : by:     ( -- [xt] [colon-sys] ) \ name
     Ghost do:ghost!
     :noname postpone gdoes> ;
   
   : ;DO ( [xt] [colon-sys] -- )
     postpone ; doexec! ; immediate
   
   : by      ( -- ) \ Name
     Ghost >do:ghost @ do:ghost! ;
   
   : compile: ( --[xt] [colon-sys] )
   \G defines a compile time action for created words
   \G by this builder
     :noname ;
   
   : ;compile ( [xt] [colon-sys] -- )
     postpone ; built >do:ghost @ >comp ! ; immediate
   
 >TARGET  
 \ Variables and Constants                              05dec92py  \ Variables and Constants                              05dec92py
   
 Build:  ( n -- ) ;  
 by: :docon ( ghost -- n ) T @ H ;DO  
 Builder (Constant)  Builder (Constant)
   Build:  ( n -- ) ;Build
   by: :docon ( target-body-addr -- n ) T @ H ;DO
   
 Build:  ( n -- ) T , H ;  
 by (Constant)  
 Builder Constant  Builder Constant
   Build:  ( n -- ) T , H ;Build
 Build:  ( n -- ) T A, H ;  
 by (Constant)  by (Constant)
   
 Builder AConstant  Builder AConstant
   Build:  ( n -- ) T A, H ;Build
   by (Constant)
   
 Build:  ( d -- ) T , , H ;  
 DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO  
 Builder 2Constant  Builder 2Constant
   Build:  ( d -- ) T , , H ;Build
   DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO
   
 BuildSmart: ;  
 by: :dovar ( ghost -- addr ) ;DO  
 Builder Create  Builder Create
   BuildSmart: ;Build
   by: :dovar ( target-body-addr -- addr ) ;DO
   
   Builder Variable
 T has? rom H [IF]  T has? rom H [IF]
 Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , H ( switchrom ) ;  Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 , H ( switchrom ) ;Build
 by (Constant)  by (Constant)
 Builder Variable  
 [ELSE]  [ELSE]
 Build: T 0 , H ;  Build: T 0 , H ;Build
 by Create  by Create
 Builder Variable  
 [THEN]  [THEN]
   
   Builder 2Variable
 T has? rom H [IF]  T has? rom H [IF]
 Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , 0 , H ( switchrom ) ;  Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 , 0 , H ( switchrom ) ;Build
 by (Constant)  by (Constant)
 Builder 2Variable  
 [ELSE]  [ELSE]
 Build: T 0 , 0 , H ;  Build: T 0 , 0 , H ;Build
 by Create  by Create
 Builder 2Variable  
 [THEN]  [THEN]
   
   Builder AVariable
 T has? rom H [IF]  T has? rom H [IF]
 Build: ( -- ) T here 0 , H switchram T align here swap ! 0 , H ( switchrom ) ;  Build: ( -- ) T here 0 A, H switchram T align here swap ! 0 A, H ( switchrom ) ;Build
 by (Constant)  by (Constant)
 Builder AVariable  
 [ELSE]  [ELSE]
 Build: T 0 A, H ;  Build: T 0 A, H ;Build
 by Create  by Create
 Builder AVariable  
 [THEN]  [THEN]
   
 \ User variables                                       04may94py  \ User variables                                       04may94py
   
 >CROSS  : tup@ user-region >rstart @ ;
   
 Variable tup  0 tup !  \ Variable tup  0 tup !
 Variable tudp 0 tudp !  \ Variable tudp 0 tudp !
   
 : u,  ( n -- udp )  : u,  ( n -- udp )
   tup @ tudp @ + T  ! H    current-region >r user-region activate
   tudp @ dup T cell+ H tudp ! ;    X here swap X , tup@ - 
     r> activate ;
   
 : au, ( n -- udp )  : au, ( n -- udp )
   tup @ tudp @ + T A! H    current-region >r user-region activate
   tudp @ dup T cell+ H tudp ! ;    X here swap X a, tup@ - 
     r> activate ;
   
 >TARGET  T has? no-userspace H [IF]
   
   : buildby
     ghost >exec @ built >exec ! ;
   
 Build: 0 u, X , ;  
 by: :douser ( ghost -- up-addr )  X @ tup @ + ;DO  
 Builder User  Builder User
   buildby Variable
   by Variable
   
 Build: 0 u, X , 0 u, drop ;  
 by User  
 Builder 2User  Builder 2User
   buildby 2Variable
   by 2Variable
   
 Build: 0 au, X , ;  Builder AUser
   buildby AVariable
   by AVariable
   
   [ELSE]
   
   Builder User
   Build: 0 u, X , ;Build
   by: :douser ( ghost -- up-addr )  X @ tup@ + ;DO
   
   Builder 2User
   Build: 0 u, X , 0 u, drop ;Build
 by User  by User
   
 Builder AUser  Builder AUser
   Build: 0 au, X , ;Build
   by User
   
   [THEN]
   
   Builder (Value)
   Build:  ( n -- ) ;Build
   by: :docon ( target-body-addr -- n ) T @ H ;DO
   
 BuildSmart: T , H ;  
 by (Constant)  
 Builder Value  Builder Value
   BuildSmart: T , H ;Build
   by (Value)
   
 BuildSmart: T A, H ;  
 by (Constant)  
 Builder AValue  Builder AValue
   BuildSmart: T A, H ;Build
   by (Value)
   
   Defer texecute
   
 BuildSmart:  ( -- ) [T'] noop T A, H ;  
 by: :dodefer ( ghost -- ) ABORT" CROSS: Don't execute" ;DO  
 Builder Defer  Builder Defer
   BuildSmart:  ( -- ) [T'] noop T A, H ;Build
   by: :dodefer ( ghost -- ) X @ texecute ;DO
   
 Build: ( inter comp -- ) swap T immediate A, A, H ;  
 DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO  
 Builder interpret/compile:  Builder interpret/compile:
   Build: ( inter comp -- ) swap T A, A, H ;Build-immediate
   DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
   
 \ Sturctures                                           23feb95py  \ Sturctures                                           23feb95py
   
 >CROSS  
 : nalign ( addr1 n -- addr2 )  : nalign ( addr1 n -- addr2 )
 \ addr2 is the aligned version of addr1 wrt the alignment size n  \ addr2 is the aligned version of addr1 wrt the alignment size n
  1- tuck +  swap invert and ;   1- tuck +  swap invert and ;
 >TARGET  
   
 Build: ;  
 by: :dofield T @ H + ;DO  
 Builder (Field)  Builder (Field)
   Build: ;Build
   by: :dofield T @ H + ;DO
   
   Builder Field
 Build: ( align1 offset1 align size "name" --  align2 offset2 )  Build: ( align1 offset1 align size "name" --  align2 offset2 )
     rot dup T , H ( align1 align size offset1 )      rot dup T , H ( align1 align size offset1 )
     + >r nalign r> ;      + >r nalign r> ;Build
 by (Field)  by (Field)
 Builder Field  
   
   >TARGET
 : struct  T 1 chars 0 H ;  : struct  T 1 chars 0 H ;
 : end-struct  T 2Constant H ;  : end-struct  T 2Constant H ;
   
 : cell% ( n -- size align )  : cell% ( n -- size align )
     T 1 cells H dup ;      T 1 cells H dup ;
   >CROSS
   
   \ Input-Methods                                            01py
   
   Builder input-method
   Build: ( m v -- m' v )  dup T , cell+ H ;Build
   DO:  abort" Not in cross mode" ;DO
   
   Builder input-var
   Build: ( m v size -- m v' )  over T , H + ;Build
   DO:  abort" Not in cross mode" ;DO
   
   \ Peephole optimization                                 05sep01jaw
   
   \ this section defines different compilation
   \ actions for created words
   \ this will help the peephole optimizer
   \ I (jaw) took this from bernds latest cross-compiler
   \ changes but seperated it from the original
   \ Builder words. The final plan is to put this
   \ into a seperate file, together with the peephole
   \ optimizer for cross
   
   
   T has? peephole H [IF]
   
   \ .( loading peephole optimization) cr
   
   >CROSS
   
   : (callc) compile call T >body a, H ;           ' (callc) plugin-of colon,
   : (callcm) T here 0 a, 0 a, H ;                 ' (callcm) plugin-of colonmark,
   : (call-res) >tempdp resolved gexecute tempdp> drop ;
                                                   ' (call-res) plugin-of colon-resolve
   : (pprim) dup 0< IF  $4000 -  ELSE
       cr ." wrong usage of (prim) "
       dup gdiscover IF  .ghost  ELSE  .  THEN  cr -1 throw  THEN
       T a, H ;                                    ' (pprim) plugin-of prim,
   
   \ if we want this, we have to spilt aconstant
   \ and constant!!
   \ Builder (Constant)
   \ compile: g>body X @ lit, ;compile
   
   Builder (Constant)
   compile: g>body compile lit@ T a, H ;compile
   
   Builder (Value)
   compile: g>body compile lit@ T a, H ;compile
   
   \ this changes also Variable, AVariable and 2Variable
   Builder Create
   compile: g>body alit, ;compile
   
   Builder User
   compile: g>body compile useraddr T @ , H ;compile
   
   Builder Defer
   compile: g>body compile lit-perform T A, H ;compile
   
   Builder (Field)
   compile: g>body T @ H compile lit+ T , H ;compile
   
   Builder interpret/compile:
   compile: does-resolved ;compile
   
   Builder input-method
   compile: does-resolved ;compile
   
   Builder input-var
   compile: does-resolved ;compile
   
   [THEN]
   
 \ structural conditionals                              17dec92py  \ structural conditionals                              17dec92py
   
 >CROSS  >CROSS
 : ?struc      ( flag -- )       ABORT" CROSS: unstructured " ;  : (ncontrols?) ( n -- ) 
 : sys?        ( sys -- sys )    dup 0= ?struc ;  \g We expect n open control structures
 : >mark       ( -- sys )        T here  ( dup ." M" hex. ) 0 , H ;    depth over u<= 
     ABORT" CROSS: unstructured, stack underflow"
     0 ?DO I pick 0= 
           ABORT" CROSS: unstructured" 
     LOOP ;                                        ' (ncontrols?) plugin-of ncontrols?
   
 : branchoffset ( src dest -- )  - tchar / ; \ ?? jaw  \ : ?struc      ( flag -- )       ABORT" CROSS: unstructured " ;
   \ : sys?        ( sys -- sys )    dup 0= ?struc ;
   
 : >resolve    ( sys -- )          : >mark       ( -- sys )        T here  ( dup ." M" hex. ) 0 , H ;
         X here ( dup ." >" hex. ) over branchoffset swap X ! ;  
   
 : <resolve    ( sys -- )  X has? abranch [IF]
         X here ( dup ." <" hex. ) branchoffset X , ;      : branchoffset ( src dest -- )  drop ;
       : offset, ( n -- )  X A, ;
   [ELSE]
       : branchoffset ( src dest -- )  - tchar / ; \ ?? jaw
       : offset, ( n -- )  X , ;
   [THEN]
   
 :noname compile branch X here branchoffset X , ;  :noname compile branch X here branchoffset offset, ;
   IS branch, ( target-addr -- )    IS branch, ( target-addr -- )
 :noname compile ?branch X here branchoffset X , ;  :noname compile ?branch X here branchoffset offset, ;
   IS ?branch, ( target-addr -- )    IS ?branch, ( target-addr -- )
 :noname compile branch T here 0 , H ;  :noname compile branch T here 0 H offset, ;
   IS branchmark, ( -- branchtoken )    IS branchmark, ( -- branchtoken )
 :noname compile ?branch T here 0 , H ;  :noname compile ?branch T here 0 H offset, ;
   IS ?branchmark, ( -- branchtoken )    IS ?branchmark, ( -- branchtoken )
 :noname T here 0 , H ;  :noname T here 0 H offset, ;
   IS ?domark, ( -- branchtoken )    IS ?domark, ( -- branchtoken )
 :noname dup X @ ?struc X here over branchoffset swap X ! ;  :noname dup X @ ?struc X here over branchoffset swap X ! ;
   IS branchtoresolve, ( branchtoken -- )    IS branchtoresolve, ( branchtoken -- )
Line 2225  Builder Field Line 3025  Builder Field
   
 \ Structural Conditionals                              12dec92py  \ Structural Conditionals                              12dec92py
   
 Cond: BUT       restrict? sys? swap ;Cond  \ CLEANUP Cond: BUT       sys? swap ;Cond
 Cond: YET       restrict? sys? dup ;Cond  \ CLEANUP Cond: YET       sys? dup ;Cond
   
 >CROSS  >CROSS
   
 Variable tleavings 0 tleavings !  Variable tleavings 0 tleavings !
   
 : (done) ( addr -- )  : (done) ( do-addr -- )
   \G resolve branches of leave and ?leave and ?do
   \G do-addr is the address of the beginning of our
   \G loop so we can take care of nested loops
     tleavings @      tleavings @
     BEGIN  dup      BEGIN  dup
     WHILE      WHILE
Line 2247  Variable tleavings 0 tleavings ! Line 3050  Variable tleavings 0 tleavings !
   
 >TARGET  >TARGET
   
 Cond: DONE   ( addr -- )  restrict? (done) ;Cond  \ What for? ANS? JAW Cond: DONE   ( addr -- )  (done) ;Cond
   
 >CROSS  >CROSS
 : (leave) ( branchtoken -- )  : (leave) ( branchtoken -- )
Line 2258  Cond: DONE   ( addr -- )  restrict? (don Line 3061  Cond: DONE   ( addr -- )  restrict? (don
     r> tleavings ! ;      r> tleavings ! ;
 >TARGET  >TARGET
   
 Cond: LEAVE     restrict? branchmark, (leave) ;Cond  : (leave,) ( -- ) 
 Cond: ?LEAVE    restrict? compile 0=  ?branchmark, (leave)  ;Cond    branchmark, (leave) ;                         ' (leave,) plugin-of leave,
   
   : (?leave,) ( -- )
     compile 0= ?branchmark, (leave) ;             ' (?leave,) plugin-of ?leave,
   
   Cond: LEAVE     leave, ;Cond
   Cond: ?LEAVE    ?leave, ;Cond
   
 >CROSS  >CROSS
 \ !!JW ToDo : Move to general tools section  \ !!JW ToDo : Move to general tools section
   
 : to1 ( x1 x2 xn n -- addr )  : to1 ( x1 x2 xn n -- addr )
 \G packs n stack elements in a allocated memory region  \G packs n stack elements in am allocated memory region
    dup dup 1+ cells allocate throw dup >r swap 1+     dup dup 1+ cells allocate throw dup >r swap 1+
    0 DO tuck ! cell+ LOOP     0 DO tuck ! cell+ LOOP
    drop r> ;     drop r> ;
   
 : 1to ( addr -- x1 x2 xn )  : 1to ( addr -- x1 x2 xn )
 \G unpacks the elements saved by to1  \G unpacks the elements saved by to1
     dup @ swap over cells + swap      dup @ swap over cells + swap
     0 DO  dup @ swap 1 cells -  LOOP      0 DO  dup @ swap 1 cells -  LOOP
     free throw ;      free throw ;
   
 : loop]     branchto, dup <resolve tcell - (done) ;  : loop] ( target-addr -- )
     branchto, 
     dup   X here branchoffset offset, 
     tcell - (done) ;
   
 : skiploop] ?dup IF branchto, branchtoresolve, THEN ;  : skiploop] ?dup IF branchto, branchtoresolve, THEN ;
   
Line 2283  Cond: ?LEAVE    restrict? compile 0=  ?b Line 3096  Cond: ?LEAVE    restrict? compile 0=  ?b
   
 \ Structural Conditionals                              12dec92py  \ Structural Conditionals                              12dec92py
   
   : (cs-swap) ( x1 x2 -- x2 x1 )
     swap ;                                        ' (cs-swap) plugin-of cs-swap
   
   : (ahead,) branchmark, ;                        ' (ahead,) plugin-of ahead,
   
   : (if,) ?branchmark, ;                          ' (if,) plugin-of if,
   
   : (then,) branchto, branchtoresolve, ;          ' (then,) plugin-of then,
   
   : (else,) ( ahead ) branchmark, 
             swap 
             ( then ) branchto, branchtoresolve, ; ' (else,) plugin-of else,
   
   : (begin,) branchtomark, ;                      ' (begin,) plugin-of begin,
   
   : (while,) ( if ) ?branchmark,
              swap ;                               ' (while,) plugin-of while,
   
   : (again,) branch, ;                            ' (again,) plugin-of again,
   
   : (until,) ?branch, ;                           ' (until,) plugin-of until,
   
   : (repeat,) ( again ) branch,
               ( then ) branchto, branchtoresolve, ; ' (repeat,) plugin-of repeat,
   
   : (case,)   ( -- n )
     0 ;                                           ' (case,) plugin-of case,
   
   : (of,) ( n -- x1 n )
     1+ >r 
     compile over compile = 
     if, compile drop r> ;                         ' (of,) plugin-of of,
   
   : (endof,) ( x1 n -- x2 n )
     >r 1 ncontrols? else, r> ;                    ' (endof,) plugin-of endof,
   
   : (endcase,) ( x1 .. xn n -- )
     compile drop 0 ?DO 1 ncontrols? then, LOOP ;  ' (endcase,) plugin-of endcase,
   
 >TARGET  >TARGET
 Cond: AHEAD     restrict? branchmark, ;Cond  Cond: AHEAD     ahead, ;Cond
 Cond: IF        restrict? ?branchmark, ;Cond  Cond: IF        if,  ;Cond
 Cond: THEN      restrict? sys? branchto, branchtoresolve, ;Cond  Cond: THEN      1 ncontrols? then, ;Cond
 Cond: ELSE      restrict? sys? compile AHEAD swap compile THEN ;Cond  Cond: ENDIF     1 ncontrols? then, ;Cond
   Cond: ELSE      1 ncontrols? else, ;Cond
 Cond: BEGIN     restrict? branchtomark, ;Cond  
 Cond: WHILE     restrict? sys? compile IF swap ;Cond  Cond: BEGIN     begin, ;Cond
 Cond: AGAIN     restrict? sys? branch, ;Cond  Cond: WHILE     1 ncontrols? while, ;Cond
 Cond: UNTIL     restrict? sys? ?branch, ;Cond  Cond: AGAIN     1 ncontrols? again, ;Cond
 Cond: REPEAT    restrict? over 0= ?struc compile AGAIN compile THEN ;Cond  Cond: UNTIL     1 ncontrols? until, ;Cond
   Cond: REPEAT    2 ncontrols? repeat, ;Cond
 Cond: CASE      restrict? 0 ;Cond  
 Cond: OF        restrict? 1+ >r compile over compile =  Cond: CASE      case, ;Cond
                 compile IF compile drop r> ;Cond  Cond: OF        of, ;Cond
 Cond: ENDOF     restrict? >r compile ELSE r> ;Cond  Cond: ENDOF     endof, ;Cond
 Cond: ENDCASE   restrict? compile drop 0 ?DO  compile THEN  LOOP ;Cond  Cond: ENDCASE   endcase, ;Cond
   
 \ Structural Conditionals                              12dec92py  \ Structural Conditionals                              12dec92py
   
 :noname \ ?? i think 0 is too much! jaw  : (do,) ( -- target-addr )
     \ ?? i think 0 is too much! jaw
     0 compile (do)      0 compile (do)
     branchtomark,  2 to1 ;      branchtomark,  2 to1 ;                      ' (do,) plugin-of do,
   IS do, ( -- target-addr )  
   
 \ :noname  \ alternative for if no ?do
   \ : (do,)
 \     compile 2dup compile = compile IF  \     compile 2dup compile = compile IF
 \     compile 2drop compile ELSE  \     compile 2drop compile ELSE
 \     compile (do) branchtomark, 2 to1 ;  \     compile (do) branchtomark, 2 to1 ;
 \   IS ?do,  
           
 :noname  : (?do,) ( -- target-addr )
     0 compile (?do)  ?domark, (leave)      0 compile (?do)  ?domark, (leave)
     branchtomark,  2 to1 ;      branchtomark,  2 to1 ;                      ' (?do,) plugin-of ?do,
   IS ?do, ( -- target-addr )  
 :noname compile (for) branchtomark, ;  : (for,) ( -- target-addr )
   IS for, ( -- target-addr )    compile (for) branchtomark, ;                 ' (for,) plugin-of for,
 :noname 1to compile (loop)  loop] compile unloop skiploop] ;  
   IS loop, ( target-addr -- )  : (loop,) ( target-addr -- )
 :noname 1to compile (+loop)  loop] compile unloop skiploop] ;    1to compile (loop)  loop] 
   IS +loop, ( target-addr -- )    compile unloop skiploop] ;                    ' (loop,) plugin-of loop,
 :noname compile (next)  loop] compile unloop ;  
   IS next, ( target-addr -- )  : (+loop,) ( target-addr -- )
     1to compile (+loop)  loop] 
 Cond: DO        restrict? do, ;Cond    compile unloop skiploop] ;                    ' (+loop,) plugin-of +loop,
 Cond: ?DO       restrict? ?do, ;Cond  
 Cond: FOR       restrict? for, ;Cond  : (next,) 
     compile (next)  loop] compile unloop ;        ' (next,) plugin-of next,
 Cond: LOOP      restrict? sys? loop, ;Cond  
 Cond: +LOOP     restrict? sys? +loop, ;Cond  Cond: DO        do, ;Cond
 Cond: NEXT      restrict? sys? next, ;Cond  Cond: ?DO       ?do, ;Cond
   Cond: FOR       for, ;Cond
   
   Cond: LOOP      1 ncontrols? loop, ;Cond
   Cond: +LOOP     1 ncontrols? +loop, ;Cond
   Cond: NEXT      1 ncontrols? next, ;Cond
   
 \ String words                                         23feb93py  \ String words                                         23feb93py
   
 : ,"            [char] " parse T string, align H ;  : ,"            [char] " parse ht-string, X align ;
   
 Cond: ."        restrict? compile (.")     T ," H ;Cond  X has? control-rack [IF]
 Cond: S"        restrict? compile (S")     T ," H ;Cond  Cond: ."        compile (.")     T ," H ;Cond
 Cond: ABORT"    restrict? compile (ABORT") T ," H ;Cond  Cond: S"        compile (S")     T ," H ;Cond
   Cond: C"        compile (C")     T ," H ;Cond
   Cond: ABORT"    compile (ABORT") T ," H ;Cond
   [ELSE]
   Cond: ."        '" parse tuck 2>r ahead, there 2r> ht-mem, X align
                   >r then, r> compile ALiteral compile Literal compile type ;Cond
   Cond: S"        '" parse tuck 2>r ahead, there 2r> ht-mem, X align
                   >r then, r> compile ALiteral compile Literal ;Cond
   Cond: C"        ahead, there [char] " parse ht-string, X align
                   >r then, r> compile ALiteral ;Cond
   Cond: ABORT"    if, ahead, there [char] " parse ht-string, X align
                   >r then, r> compile ALiteral compile c(abort") then, ;Cond
   [THEN]
   
 Cond: IS        T ' >body H compile ALiteral compile ! ;Cond  Cond: IS        T ' >body H compile ALiteral compile ! ;Cond
 : IS            T >address ' >body ! H ;  : IS            T >address ' >body ! H ;
Line 2349  Cond: TO        T ' >body H compile ALit Line 3218  Cond: TO        T ' >body H compile ALit
 : TO            T ' >body ! H ;  : TO            T ' >body ! H ;
   
 Cond: defers    T ' >body @ compile, H ;Cond  Cond: defers    T ' >body @ compile, H ;Cond
 : on            T -1 swap ! H ;   
 : off           T 0 swap ! H ;  
   
 \ LINKED ERR" ENV" 2ENV"                                18may93jaw  \ LINKED ERR" ENV" 2ENV"                                18may93jaw
   
Line 2359  Cond: defers T ' >body @ compile, H ;Con Line 3226  Cond: defers T ' >body @ compile, H ;Con
 : chained       T linked A, H ;  : chained       T linked A, H ;
   
 : err"   s" ErrLink linked" evaluate T , H  : err"   s" ErrLink linked" evaluate T , H
          [char] " parse T string, align H ;           [char] " parse ht-string, X align ;
   
 : env"  [char] " parse s" EnvLink linked" evaluate  : env"  [char] " parse s" EnvLink linked" evaluate
         T string, align , H ;          ht-string, X align X , ;
   
 : 2env" [char] " parse s" EnvLink linked" evaluate  : 2env" [char] " parse s" EnvLink linked" evaluate
         here >r T string, align , , H          here >r ht-string, X align X , X ,
         r> dup T c@ H 80 and swap T c! H ;          r> dup T c@ H 80 and swap T c! H ;
   
 \ compile must be last                                 22feb93py  \ compile must be last                                 22feb93py
   
 Cond: compile ( -- ) restrict? \ name  Cond: [compile] ( -- ) \ name
       bl word gfind dup 0= ABORT" CROSS: Can't compile"  \g For immediate words, works even if forward reference
       0> IF    gexecute        bl word gfind 0= ABORT" CROSS: Can't compile"
          ELSE  dup >magic @ <imm> =        (gexecute) ;Cond
                IF   gexecute             
                ELSE compile (compile) addr, THEN THEN ;Cond  Cond: postpone ( -- ) \ name
         bl word gfind 0= ABORT" CROSS: Can't compile"
 Cond: postpone ( -- ) restrict? \ name        dup >magic @ <fwd> =
       bl word gfind dup 0= ABORT" CROSS: Can't compile"        ABORT" CROSS: Can't postpone on forward declaration"
       0> IF    gexecute        dup >magic @ <imm> =
          ELSE  dup >magic @ <imm> =        IF   (gexecute)
                IF   gexecute        ELSE >link @ alit, compile compile,  THEN ;Cond
                ELSE compile (compile) addr, THEN THEN ;Cond  
                         
 \ save-cross                                           17mar93py  \ save-cross                                           17mar93py
   
 hex  hex
   
 >CROSS  >CROSS
 Create magic  s" Gforth2x" here over allot swap move  Create magic  s" Gforth3x" here over allot swap move
   
 bigendian 1+ \ strangely, in magic big=0, little=1  bigendian 1+ \ strangely, in magic big=0, little=1
 tcell 1 = 0 and or  tcell 1 = 0 and or
Line 2403  tchar 8 = 78 and or Line 3269  tchar 8 = 78 and or
 magic 7 + c!  magic 7 + c!
   
 : save-cross ( "image-name" "binary-name" -- )  : save-cross ( "image-name" "binary-name" -- )
     s" ec" X $has? IF  .regions  THEN
   bl parse ." Saving to " 2dup type cr    bl parse ." Saving to " 2dup type cr
   w/o bin create-file throw >r    w/o bin create-file throw >r
   TNIL IF    s" header" X $has? IF
       s" #! "           r@ write-file throw        s" #! "           r@ write-file throw
       bl parse          r@ write-file throw        bl parse          r@ write-file throw
       s"  --image-file" r@ write-file throw        s"  --image-file" r@ write-file throw
Line 2419  magic 7 + c! Line 3286  magic 7 + c!
   ELSE    ELSE
       bl parse 2drop        bl parse 2drop
   THEN    THEN
   image @ there     >rom dictionary >rmem @ there
     s" rom" X $has? IF  dictionary >rstart @ -  THEN
   r@ write-file throw \ write image    r@ write-file throw \ write image
   TNIL IF    s" relocate" X $has? IF
       bit$  @ there 1- tcell>bit rshift 1+        dictionary >rbm @ there 1- tcell>bit rshift 1+
                 r@ write-file throw \ write tags                  r@ write-file throw \ write tags
   THEN    THEN
   r> close-file throw ;    r> close-file throw ;
Line 2432  magic 7 + c! Line 3300  magic 7 + c!
   swap >image swap r@ write-file throw    swap >image swap r@ write-file throw
   r> close-file throw ;    r> close-file throw ;
   
   \ save-asm-region                                       29aug01jaw
   
   Variable name-ptr
   Create name-buf 200 chars allot
   : init-name-buf name-buf name-ptr ! ;
   : nb, name-ptr @ c! 1 chars name-ptr +! ;
   : $nb, ( adr len -- ) bounds ?DO I c@ nb, LOOP ;
   : @nb name-ptr @ name-buf tuck - ;
   
   \ stores a usefull string representation of the character
   \ in the name buffer
   : name-char, ( c -- )
     dup 'a 'z 1+ within IF nb, EXIT THEN
     dup 'A 'Z 1+ within IF $20 + nb, EXIT THEN
     dup '0 '9 1+ within IF nb, EXIT THEN
     CASE '+ OF s" _PLUS" $nb, ENDOF
          '- OF s" _MINUS" $nb, ENDOF
          '* OF s" _STAR" $nb, ENDOF
          '/ OF s" _SLASH" $nb, ENDOF
          '' OF s" _TICK" $nb, ENDOF
          '( OF s" _OPAREN" $nb, ENDOF
          ') OF s" _CPAREN" $nb, ENDOF
          '[ OF s" _OBRACKET" $nb, ENDOF
          '] OF s" _CBRACKET" $nb, ENDOF
          '! OF s" _STORE" $nb, ENDOF
          '@ OF s" _FETCH" $nb, ENDOF
          '> OF s" _GREATER" $nb, ENDOF
          '< OF s" _LESS" $nb, ENDOF
          '= OF s" _EQUAL" $nb, ENDOF
          '# OF s" _HASH" $nb, ENDOF
          '? OF s" _QUEST" $nb, ENDOF
          ': OF s" _COL" $nb, ENDOF
          '; OF s" _SEMICOL" $nb, ENDOF
          ', OF s" _COMMA" $nb, ENDOF
          '. OF s" _DOT" $nb, ENDOF
          '" OF s" _DQUOT" $nb, ENDOF
          dup 
          base @ >r hex s>d <# #s 'X hold '_ hold #> $nb, r> base !
     ENDCASE ;
    
   : label-from-ghostname ( ghost -- addr len )
     dup >ghostname init-name-buf 'L nb, bounds 
     ?DO I c@ name-char, LOOP 
     \ we add the address to a name to make in unique
     \ because one name may appear more then once
     \ there are names (e.g. boot) that may be reference from other
     \ assembler source files, so we declare them as unique
     \ and don't add the address suffix
     dup >ghost-flags @ <unique> and 0= 
     IF   s" __" $nb, >link @ base @ >r hex 0 <# #s 'L hold #> r> base ! $nb, 
     ELSE drop 
     THEN
     @nb ;
   
   \ FIXME why disabled?!
   : label-from-ghostnameXX ( ghost -- addr len )
   \ same as (label-from-ghostname) but caches generated names
     dup >asm-name @ ?dup IF nip count EXIT THEN
    \ dup >r (label-from-ghostname) 2dup
     align here >r string, align
     r> r> >asm-name ! ;
   
   : primghostdiscover ( xt -- ghost true | xt false )
     dup 0= IF false EXIT THEN
     >r last-prim-ghost
     BEGIN @ dup
     WHILE dup >asm-dummyaddr @ r@ =
           IF rdrop true EXIT THEN
     REPEAT
     drop r> false ;
   
   : gdiscover2 ( xt -- ghost true | xt false ) 
     dup taddr>region 0= IF false EXIT THEN
     dup (>regiontype) @ dup 0= IF drop false EXIT THEN
     addr-xt-ghost @ dup 0= IF drop false EXIT THEN
     nip true ;
   \  dup >ghost-name @ IF nip true ELSE drop false THEN ;
   
   \ generates a label name for the target address
   : generate-label-name ( taddr -- addr len )
     gdiscover2
     IF dup >magic @ <do:> =
        IF >asm-name @ count EXIT THEN
        label-from-ghostname
     ELSE
        primghostdiscover
        IF   >asm-name @ count 
        ELSE base @ >r hex 0 <# #s 'L hold #> r> base !
        THEN
     THEN ;
   
   Variable outfile-fd
   
   : $out ( adr len -- ) outfile-fd @ write-file throw  ;
   : nlout newline $out ;
   : .ux ( n -- ) 
     base @ hex swap 0 <# #S #> $out base ! ;
   
   : save-asm-region-part-aligned ( taddr len -- 'taddr 'len )
     dup cell/ 0 
     ?DO nlout s"    .word " $out over @relbit 
         IF   over X @ generate-label-name $out
         ELSE over X @ s" 0x0" $out .ux
         THEN
         tcell /string
     LOOP ;
   
   : print-bytes ( taddr len n -- taddr' len' )
     over min dup 0> 
     IF   nlout s"    .byte " $out 0 
          ?DO  I 0> IF s" , " $out THEN
               over X c@ s" 0x0" $out .ux 1 /string 
          LOOP 
     THEN ;
   
   : save-asm-region-part ( addr len -- )
     over dup X aligned swap - ?dup
     IF   print-bytes THEN
     save-asm-region-part-aligned
     dup dup X aligned swap - ?dup
     IF   2 pick @relbit ABORT" relocated field splitted"
          print-bytes
     THEN
     2drop ;
   
   : print-label ( taddr -- )
     nlout generate-label-name $out s" :" $out ;
   
   : snl-calc ( taddr taddr2 -- )
     tuck over - ;
   
   : skip-nolables ( taddr -- taddr2 taddr len )
   \G skips memory region where no lables are defined
   \G starting from taddr+1
   \G Labels will be introduced for each reference mark
   \G in addr-refs.
   \G This word deals with lables at byte addresses as well.
   \G The main idea is to have an intro part which
   \G skips until the next cell boundary, the middle part
   \G which skips whole cells very efficiently and the third
   \G part which skips the bytes to the label in a cell
     dup 1+ dup (>regiontype) 
     ( S taddr taddr-realstart type-addr )
     dup @ dup IF addr-refs @ THEN
     swap >r
     over align+ tuck tcell swap - rshift swap 0
     ?DO dup 1 and 
        IF drop rdrop snl-calc UNLOOP EXIT THEN 
        2/ swap 1+ swap 
     LOOP
     drop r> cell+
     ( S .. taddr2 type-addr ) dup
     BEGIN dup @ dup IF addr-refs @ THEN 0= WHILE cell+ REPEAT
     dup >r swap - 1 cells / tcell * + r>
     ( S .. taddr2+skiplencells type-addr )
     @ addr-refs @ 1 tcell lshift or
     BEGIN dup 1 and 0= WHILE swap 1+ swap 2/ REPEAT drop
     ( S .. taddr2+skiplencells+skiplenbytes )
     snl-calc ;
   
   : insert-label ( taddr -- )
     dup 0= IF drop EXIT THEN
     \ ignore everything which points outside our memory regions
     \ maybe a primitive pointer or whatever
     dup taddr>region 0= IF drop EXIT THEN
     dup >r (>regiontype) define-addr-struct addr-refs dup @ 
     r> tcell 1- and 1 swap lshift or swap ! ;
   
   \ this generates a sorted list of addresses which must be labels
   \ it scans therefore a whole region
   : generate-label-list-region ( taddr len -- )
     BEGIN over @relbit IF over X @ insert-label THEN
           tcell /string dup 0< 
     UNTIL 2drop ;
   
   : generate-label-list ( -- )
     region-link
     BEGIN @ dup WHILE 
           dup 0 >rlink - extent 
           ?dup IF generate-label-list-region ELSE drop THEN
     REPEAT drop ;
   
   : create-outfile ( addr len -- )
     w/o bin create-file throw outfile-fd ! ;
   
   : close-outfile ( -- )
     outfile-fd @ close-file throw ;
   
   : (save-asm-region) ( region -- )
     \ ." label list..."
     generate-label-list
     \ ." ok!" cr
     extent ( S taddr len )
     over insert-label
     2dup + dup insert-label >r ( R end-label )
     ( S taddr len ) drop
     BEGIN
        dup print-label
        dup r@ <> WHILE
        skip-nolables save-asm-region-part
     REPEAT drop rdrop ;
   
   : lineout ( addr len -- )
     outfile-fd @ write-line throw ;  
   
   : save-asm-region ( region adr len -- )
     create-outfile (save-asm-region) close-outfile ;
   
 \ \ minimal definitions  \ \ minimal definitions
                         
 >MINIMAL also minimal  >MINIMAL also minimal
Line 2443  magic 7 + c! Line 3519  magic 7 + c!
 \ \ [IF] [ELSE] [THEN] ...                              14sep97jaw  \ \ [IF] [ELSE] [THEN] ...                              14sep97jaw
   
 \ it is useful to define our own structures and not to rely  \ it is useful to define our own structures and not to rely
 \ on the words in the compiler  \ on the words in the host system
 \ The words in the compiler might be defined with vocabularies  \ The words in the host system might be defined with vocabularies
 \ this doesn't work with our self-made compile-loop  \ this doesn't work with our self-made compile-loop
   
 Create parsed 20 chars allot    \ store word we parsed  Create parsed 20 chars allot    \ store word we parsed
Line 2457  Create parsed 20 chars allot \ store wor Line 3533  Create parsed 20 chars allot \ store wor
     1 BEGIN      1 BEGIN
         BEGIN bl word count dup WHILE          BEGIN bl word count dup WHILE
             comment? 20 umin parsed place upcase parsed count              comment? 20 umin parsed place upcase parsed count
             2dup s" [IF]" compare 0= >r               2dup s" [IF]" str= >r 
             2dup s" [IFUNDEF]" compare 0= >r              2dup s" [IFUNDEF]" str= >r
             2dup s" [IFDEF]" compare 0= r> or r> or              2dup s" [IFDEF]" str= r> or r> or
             IF   2drop 1+              IF   2drop 1+
             ELSE 2dup s" [ELSE]" compare 0=              ELSE 2dup s" [ELSE]" str=
                 IF   2drop 1- dup                  IF   2drop 1- dup
                     IF 1+                      IF 1+
                     THEN                      THEN
                 ELSE                  ELSE
                     2dup s" [ENDIF]" compare 0= >r                      2dup s" [ENDIF]" str= >r
                     s" [THEN]" compare 0= r> or                      s" [THEN]" str= r> or
                     IF 1- THEN                      IF 1- THEN
                 THEN                  THEN
             THEN              THEN
Line 2515  Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond Line 3591  Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond
      IF    >in ! X :       IF    >in ! X :
      ELSE drop       ELSE drop
         BEGIN bl word dup c@          BEGIN bl word dup c@
               IF   count comment? s" ;" compare 0= ?EXIT                IF   count comment? s" ;" str= ?EXIT
               ELSE refill 0= ABORT" CROSS: Out of Input while C:"                ELSE refill 0= ABORT" CROSS: Out of Input while C:"
               THEN                THEN
         AGAIN          AGAIN
Line 2523  Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond Line 3599  Cond: [IFUNDEF] postpone [IFUNDEF] ;Cond
   
 : d? d? ;  : d? d? ;
   
   : \D ( -- "debugswitch" ) 
 \G doesn't skip line when debug switch is on  \G doesn't skip line when debug switch is on
 : \D D? 0= IF postpone \ THEN ;      D? 0= IF postpone \ THEN ;
   
   : \- ( -- "wordname" )
 \G interprets the line if word is not defined  \G interprets the line if word is not defined
 : \- tdefined? IF postpone \ THEN ;     tdefined? IF postpone \ THEN ;
   
   : \+ ( -- "wordname" )
 \G interprets the line if word is defined  \G interprets the line if word is defined
 : \+ tdefined? 0= IF postpone \ THEN ;     tdefined? 0= IF postpone \ THEN ;
   
   : \? ( -- "envorinstring" )
   \G Skip line if environmental variable evaluates to false
      X has? 0= IF postpone \ THEN ;
   
 Cond: \- \- ;Cond  Cond: \- \- ;Cond
 Cond: \+ \+ ;Cond  Cond: \+ \+ ;Cond
 Cond: \D \D ;Cond  Cond: \D \D ;Cond
   Cond: \? \? ;Cond
   
 : ?? bl word find IF execute ELSE drop 0 THEN ;  : ?? bl word find IF execute ELSE drop 0 THEN ;
   
 : needed:  : needed:
 \G defines ghost for words that we want to be compiled  \G defines ghost for words that we want to be compiled
   BEGIN >in @ bl word c@ WHILE >in ! ghost drop REPEAT drop ;    BEGIN >in @ bl word c@ WHILE >in ! Ghost drop REPEAT drop ;
   
 \ words that should be in minimal  \ words that should be in minimal
   
Line 2559  bigendian Constant bigendian Line 3643  bigendian Constant bigendian
 : >tempdp >tempdp ;  : >tempdp >tempdp ;
 : tempdp> tempdp> ;  : tempdp> tempdp> ;
 : const constflag on ;  : const constflag on ;
 : warnings name 3 = 0= twarnings ! drop ;  
   : Redefinitions-start
   \G Starts a redefinition section. Warnings are disabled and
   \G existing ghosts are reused. This is used in the kernel
   \G where ( and \ and the like are redefined
     twarnings off warnings off reuse-ghosts on ;
   
   : Redefinitions-end
   \G Ends a redefinition section. Warnings are enabled again.
     twarnings on warnings on reuse-ghosts off ;
   
   : warnings name 3 = 
     IF twarnings off warnings off ELSE twarnings on warnings on THEN drop ;
   
 : | ;  : | ;
 \ : | NoHeaderFlag on ; \ This is broken (damages the last word)  \ : | NoHeaderFlag on ; \ This is broken (damages the last word)
   
Line 2585  previous Line 3682  previous
 : * * ;  : * * ;
 : / / ;  : / / ;
 : dup dup ;  : dup dup ;
   : ?dup ?dup ;
 : over over ;  : over over ;
 : swap swap ;  : swap swap ;
 : rot rot ;  : rot rot ;
 : drop drop ;  : drop drop ;
   : 2drop 2drop ;
 : =   = ;  : =   = ;
   : <>  <> ;
 : 0=   0= ;  : 0=   0= ;
 : lshift lshift ;  : lshift lshift ;
 : 2/ 2/ ;  : 2/ 2/ ;
 : . . ;  : hex. base @ $10 base ! swap . base ! ;
   : invert invert ;
   \ : . . ;
   
 : all-words    ['] forced?    IS skip? ;  : all-words    ['] forced?    IS skip? ;
 : needed-words ['] needed?  IS skip? ;  : needed-words ['] needed?  IS skip? ;
Line 2604  previous Line 3706  previous
 : \G T-\G ; immediate  : \G T-\G ; immediate
 : (  postpone ( ;  immediate  : (  postpone ( ;  immediate
 : include bl word count included ;  : include bl word count included ;
   : included swap >image swap included ;
 : require require ;  : require require ;
   : needs require ;
 : .( [char] ) parse type ;  : .( [char] ) parse type ;
   : ERROR" [char] " parse 
     rot 
     IF cr ." *** " type ."  ***" -1 ABORT" CROSS: Target error, see text above" 
     ELSE 2drop 
     THEN ;
 : ." [char] " parse type ;  : ." [char] " parse type ;
 : cr cr ;  : cr cr ;
   
Line 2615  previous Line 3724  previous
   
 \ cross-compiler words  \ cross-compiler words
   
 : decimal       decimal ;  : decimal       decimal [g'] decimal >exec2 @ ?dup IF EXECUTE THEN ;
 : hex           hex ;  : hex           hex [g'] hex >exec2 @ ?dup IF EXECUTE THEN ;
   
 \ : tudp          X tudp ;  \ : tudp          X tudp ;
 \ : tup           X tup ;  \ : tup           X tup ;
Line 2624  previous Line 3733  previous
 : doc-off       false to-doc ! ;  : doc-off       false to-doc ! ;
 : doc-on        true  to-doc ! ;  : doc-on        true  to-doc ! ;
   
 [IFDEF] dbg : dbg dbg ; [THEN]  : declareunique ( "name" -- )
   \ Sets the unique flag for a ghost. The assembler output
   \ generates labels with the ghostname concatenated with the address
   \ while cross-compiling. The address is concatenated
   \ because we have double occurences of the same name.
   \ If we want to reference the labels from the assembler or C
   \ code we declare them unique, so the address is skipped.
     Ghost >ghost-flags dup @ <unique> or swap ! ;
   
   \ [IFDEF] dbg : dbg dbg ; [THEN]
   
 \ for debugging...  \ for debugging...
 : order         order ;  \ : dbg dbg ;
 : hwords         words ;  : horder         order ;
 : words         also ghosts words previous ;  : hwords        words ;
   \ : words       also ghosts 
   \                words previous ;
 : .s            .s ;  : .s            .s ;
   : depth         depth ;
 : bye           bye ;  : bye           bye ;
   
   \ dummy
   
 \ turnkey direction  \ turnkey direction
 : H forth ; immediate  : H forth ; immediate
 : T minimal ; immediate  : T minimal ; immediate
 : G ghosts ; immediate  : G ghosts ; immediate
   
 : turnkey   
    \GFORTH 0 set-order also ghosts  
    \ANSI [ ' ghosts >wordlist ] Literal 1 set-order  
    also target definitions  
    also Minimal also ;  
   
 \ these ones are pefered:  \ these ones are pefered:
   
 : lock   turnkey ;  
 : unlock previous forth also cross ;  : unlock previous forth also cross ;
   
 \ also minimal  \ also minimal
 : [[ also unlock ;  >cross
 : ]] previous previous also also ;  
   : turnkey 
      ghosts-wordlist 1 set-order
      also target definitions
      also Minimal also ;
   
   >minimal
   
   : [[+++
     turnkey unlock ;
   
 unlock definitions also minimal  unlock definitions also minimal
 : lock   lock ;  
 lock  
   
   : lock   turnkey ;
   
   Defer +++]]-hook
   : +++]] +++]]-hook lock ;
   
   LOCK
 \ load cross compiler extension defined in mach file  \ load cross compiler extension defined in mach file
   
 UNLOCK >CROSS  UNLOCK >CROSS

Removed from v.1.82  
changed lines
  Added in v.1.151


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