Diff for /gforth/cross.fs between versions 1.25 and 1.51

version 1.25, 1995/07/06 15:57:25 version 1.51, 1997/07/31 16:17:07
Line 1 Line 1
 \ CROSS.FS     The Cross-Compiler                      06oct92py  \ CROSS.FS     The Cross-Compiler                      06oct92py
 \ $Id$  
 \ Idea and implementation: Bernd Paysan (py)  \ Idea and implementation: Bernd Paysan (py)
 \ Copyright 1992-94 by the GNU Forth Development Group  
   \ Copyright (C) 1995 Free Software Foundation, Inc.
   
   \ This file is part of Gforth.
   
   \ Gforth is free software; you can redistribute it and/or
   \ modify it under the terms of the GNU General Public License
   \ as published by the Free Software Foundation; either version 2
   \ of the License, or (at your option) any later version.
   
   \ This program is distributed in the hope that it will be useful,
   \ but WITHOUT ANY WARRANTY; without even the implied warranty of
   \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   \ GNU General Public License for more details.
   
   \ You should have received a copy of the GNU General Public License
   \ along with this program; if not, write to the Free Software
   \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
   
 \ Log:  \ Log:
 \       changed in ; [ to state off           12may93jaw  \       changed in ; [ to state off           12may93jaw
Line 21 Line 37
 \             targets                         09jun93jaw  \             targets                         09jun93jaw
 \       added: 2user and value                11jun93jaw  \       added: 2user and value                11jun93jaw
   
   \       needed? works better now!!!             01mar97jaw
   \       mach file is only loaded into target
   \       cell corrected
   
   
 \ include other.fs       \ ansforth extentions for cross  \ include other.fs       \ ansforth extentions for cross
   
 : string, ( c-addr u -- )  : string, ( c-addr u -- )
Line 75  H Line 96  H
   
 >CROSS  >CROSS
   
 \ Variables                                            06oct92py  \ Parameter for target systems                         06oct92py
   
 -1 Constant NIL  >TARGET
 Variable image  mach-file count included
 Variable tlast    NIL tlast !  \ Last name field  
 Variable tlastcfa \ Last code field  
 Variable tdoes    \ Resolve does> calls  
 Variable bit$  
 Variable tdp  
 : there  tdp @ ;  
   
 \ Parameter for target systems                         06oct92py  [IFUNDEF] has-interpreter true CONSTANT has-interpreter [THEN]
   
   also Forth definitions
   
 included  [IFDEF] asm-include asm-include [THEN]
   
   previous
   hex
   
   >CROSS
   
 \ Create additional parameters                         19jan95py  \ Create additional parameters                         19jan95py
   
 T  T
   NIL                Constant TNIL
 cell               Constant tcell  cell               Constant tcell
 cell<<             Constant tcell<<  cell<<             Constant tcell<<
 cell>bit           Constant tcell>bit  cell>bit           Constant tcell>bit
Line 101  float              Constant tfloat Line 124  float              Constant tfloat
 1 bits/byte lshift Constant maxbyte  1 bits/byte lshift Constant maxbyte
 H  H
   
   \ Variables                                            06oct92py
   
   Variable image
   Variable tlast    TNIL tlast !  \ Last name field
   Variable tlastcfa \ Last code field
   Variable tdoes    \ Resolve does> calls
   Variable bit$
   Variable tdp
   : there  tdp @ ;
   
   
 >TARGET  >TARGET
   
 \ Byte ordering and cell size                          06oct92py  \ Byte ordering and cell size                          06oct92py
Line 108  H Line 142  H
 : cell+         tcell + ;  : cell+         tcell + ;
 : cells         tcell<< lshift ;  : cells         tcell<< lshift ;
 : chars         ;  : chars         ;
   : char+         1 + ;
 : floats        tfloat * ;  : floats        tfloat * ;
           
 >CROSS  >CROSS
 : cell/         tcell<< rshift ;  : cell/         tcell<< rshift ;
 >TARGET  >TARGET
 20 CONSTANT bl  20 CONSTANT bl
 -1 Constant NIL  TNIL Constant NIL
 -2 Constant :docol  
 -3 Constant :docon  
 -4 Constant :dovar  
 -5 Constant :douser  
 -6 Constant :dodefer  
 -7 Constant :dostruc  
 -8 Constant :dodoes  
 -9 Constant :doesjump  
   
 >CROSS  >CROSS
   
Line 157  bigendian Line 184  bigendian
 \ MakeKernal                                           12dec92py  \ MakeKernal                                           12dec92py
   
 >MINIMAL  >MINIMAL
 : makekernal ( targetsize -- targetsize )  : makekernel ( targetsize -- targetsize )
   bit$  over 1- cell>bit rshift 1+ initmem    bit$  over 1- tcell>bit rshift 1+ initmem
   image over initmem tdp off ;    image over initmem tdp off ;
   
 >CROSS  >CROSS
Line 176  CREATE Bittable 80 c, 40 c, 20 c, 10 c, Line 203  CREATE Bittable 80 c, 40 c, 20 c, 10 c,
 \ Target memory access                                 06oct92py  \ Target memory access                                 06oct92py
   
 : align+  ( taddr -- rest )  : align+  ( taddr -- rest )
     cell tuck 1- and - [ cell 1- ] Literal and ;      tcell tuck 1- and - [ tcell 1- ] Literal and ;
 : cfalign+  ( taddr -- rest )  : cfalign+  ( taddr -- rest )
     \ see kernal.fs:cfaligned      \ see kernel.fs:cfaligned
     float tuck 1- and - [ float 1- ] Literal and ;      /maxalign tuck 1- and - [ /maxalign 1- ] Literal and ;
   
 >TARGET  >TARGET
 : aligned ( taddr -- ta-addr )  dup align+ + ;  : aligned ( taddr -- ta-addr )  dup align+ + ;
 \ assumes cell alignment granularity (as GNU C)  \ assumes cell alignment granularity (as GNU C)
   
 : cfaligned ( taddr1 -- taddr2 )  : cfaligned ( taddr1 -- taddr2 )
     \ see kernal.fs      \ see kernel.fs
     dup cfalign+ + ;      dup cfalign+ + ;
   
 >CROSS  >CROSS
Line 204  CREATE Bittable 80 c, 40 c, 20 c, 10 c, Line 231  CREATE Bittable 80 c, 40 c, 20 c, 10 c,
   
 : here  ( -- there )    there ;  : here  ( -- there )    there ;
 : allot ( n -- )        tdp +! ;  : allot ( n -- )        tdp +! ;
 : ,     ( w -- )        T here H cell T allot  ! H ;  : ,     ( w -- )        T here H tcell T allot  ! H ;
 : c,    ( char -- )     T here    1 allot c! H ;  : c,    ( char -- )     T here    1 allot c! H ;
 : align ( -- )          T here H align+ 0 ?DO  bl T c, H LOOP ;  : align ( -- )          T here H align+ 0 ?DO  bl T c, H LOOP ;
 : cfalign ( -- )  : cfalign ( -- )
Line 217  CREATE Bittable 80 c, 40 c, 20 c, 10 c, Line 244  CREATE Bittable 80 c, 40 c, 20 c, 10 c,
   
 \ threading modell                                     13dec92py  \ threading modell                                     13dec92py
   
 \ generic threading modell  
 : docol,  ( -- ) :docol T A, 0 , H ;  
   
 >TARGET  >TARGET
 : >body   ( cfa -- pfa ) T cell+ cell+ H ;  : >body   ( cfa -- pfa ) T cell+ cell+ H ;
 >CROSS  >CROSS
   
 : dodoes, ( -- ) T :doesjump A, 0 , H ;  
   
 \ Ghost Builder                                        06oct92py  \ Ghost Builder                                        06oct92py
   
 \ <T T> new version with temp variable                 10may93jaw  \ <T T> new version with temp variable                 10may93jaw
Line 235  VARIABLE VocTemp Line 257  VARIABLE VocTemp
 : <T  get-current VocTemp ! also Ghosts definitions ;  : <T  get-current VocTemp ! also Ghosts definitions ;
 : T>  previous VocTemp @ set-current ;  : T>  previous VocTemp @ set-current ;
   
   hex
 4711 Constant <fwd>             4712 Constant <res>  4711 Constant <fwd>             4712 Constant <res>
 4713 Constant <imm>  4713 Constant <imm>             4714 Constant <do:>
   
 \ iForth makes only immediate directly after create  \ iForth makes only immediate directly after create
 \ make atonce trick! ?  \ make atonce trick! ?
Line 247  Variable atonce atonce off Line 270  Variable atonce atonce off
   
 : GhostHeader <fwd> , 0 , ['] NoExec , ;  : GhostHeader <fwd> , 0 , ['] NoExec , ;
   
 : >magic ; : >link cell+ ; : >exec cell+ cell+ ;  : >magic ;
   : >link cell+ ;
   : >exec cell+ cell+ ;
 : >end 3 cells + ;  : >end 3 cells + ;
   
 Variable last-ghost  Variable last-ghost
Line 257  Variable last-ghost Line 282  Variable last-ghost
   here tuck swap ! ghostheader T>    here tuck swap ! ghostheader T>
   DOES> dup last-ghost ! >exec @ execute ;    DOES> dup last-ghost ! >exec @ execute ;
   
   variable cfalist 0 cfalist !
   
   : markcfa
     cfalist here over @ , swap ! , ;
   
 \ ghost words                                          14oct92py  \ ghost words                                          14oct92py
 \                                          changed:    10may93py/jaw  \                                          changed:    10may93py/jaw
   
 : gfind   ( string -- ghost true/1 / string false )  : gfind   ( string -- ghost true/1 / string false )
 \ searches for string in word-list ghosts  \ searches for string in word-list ghosts
 \ !! wouldn't it be simpler to just use search-wordlist ? ae  
   dup count [ ' ghosts >body ] ALiteral search-wordlist    dup count [ ' ghosts >body ] ALiteral search-wordlist
   dup IF  >r >body nip r>  THEN ;    dup IF >r >body nip r>  THEN ;
   
 VARIABLE Already  VARIABLE Already
   
Line 327  variable ResolveFlag Line 356  variable ResolveFlag
   WHILE dup ?resolved    WHILE dup ?resolved
   REPEAT drop ResolveFlag @    REPEAT drop ResolveFlag @
   IF    IF
       abort" Unresolved words!"        -1 abort" Unresolved words!"
   ELSE    ELSE
       ." Nothing!"        ." Nothing!"
   THEN    THEN
Line 341  variable ResolveFlag Line 370  variable ResolveFlag
 VARIABLE ^imm  VARIABLE ^imm
   
 >TARGET  >TARGET
 : immediate     20 flag!  : immediate     40 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      40 flag! ;  : restrict      20 flag! ;
 >CROSS  >CROSS
   
 \ ALIAS2 ansforth conform alias                          9may93jaw  \ ALIAS2 ansforth conform alias                          9may93jaw
Line 357  VARIABLE ^imm Line 386  VARIABLE ^imm
 \ Target Header Creation                               01nov92py  \ Target Header Creation                               01nov92py
   
 : string,  ( addr count -- )  : string,  ( addr count -- )
   dup T c, H bounds  DO  I c@ T c, H  LOOP ;     dup T c, H bounds  ?DO  I c@ T c, H  LOOP ; 
 : name,  ( "name" -- )  bl word count string, T cfalign H ;  : name,  ( "name" -- )  bl word count string, T cfalign H ;
 : view,   ( -- ) ( dummy ) ;  : view,   ( -- ) ( dummy ) ;
   
 \ Target Document Creation (goes to crossdoc.fd)       05jul95py  \ Target Document Creation (goes to crossdoc.fd)       05jul95py
   
 s" crossdoc.fd" r/w create-file throw value doc-file-id  s" doc/crossdoc.fd" r/w create-file throw value doc-file-id
 \ contains the file-id of the documentation file  \ contains the file-id of the documentation file
   
 : \G ( -- )  : T-\G ( -- )
     source >in @ /string doc-file-id write-line throw      source >in @ /string doc-file-id write-line throw
     source >in ! drop ; immediate      postpone \ ;
   
 Variable to-doc  Variable to-doc  to-doc on
   
 : cross-doc-entry  ( -- )  : cross-doc-entry  ( -- )
     to-doc @ tlast @ 0<> and    \ not an anonymous (i.e. noname) header      to-doc @ tlast @ 0<> and    \ not an anonymous (i.e. noname) header
Line 383  Variable to-doc Line 412  Variable to-doc
         [char] ) parse doc-file-id write-file throw          [char] ) parse doc-file-id write-file throw
         s"  )" doc-file-id write-file throw          s"  )" doc-file-id write-file throw
         [char] \ parse 2drop                                              [char] \ parse 2drop                                    
         POSTPONE \g          T-\G
         >in !          >in !
     THEN  to-doc on ;      THEN ;
   
   \ Target TAGS creation
   
   s" kernel.TAGS" r/w create-file throw value tag-file-id
   \ contains the file-id of the tags file
   
   Create tag-beg 2 c,  7F c, bl c,
   Create tag-end 2 c,  bl c, 01 c,
   Create tag-bof 1 c,  0C c,
   
   2variable last-loadfilename 0 0 last-loadfilename 2!
               
   : put-load-file-name ( -- )
       loadfilename 2@ last-loadfilename 2@ d<>
       IF
           tag-bof count tag-file-id write-line throw
           sourcefilename 2dup
           tag-file-id write-file throw
           last-loadfilename 2!
           s" ,0" tag-file-id write-line throw
       THEN ;
   
   : cross-tag-entry  ( -- )
       tlast @ 0<> \ not an anonymous (i.e. noname) header
       IF
           put-load-file-name
           source >in @ min 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
           tag-end count 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
           s" ,0" tag-file-id write-line throw
           base !
       THEN ;
   
   \ Check for words
   
   Defer skip? ' false IS skip?
   
   : defined? ( -- flag ) \ name
       ghost >magic @ <fwd> <> ;
   
   : needed? ( -- flag ) \ name
   \G returns a false flag when
   \G a word is not defined
   \G a forward reference exists
   \G so the definition is not skipped!
       bl word gfind
       IF dup >magic @ <fwd> = 
           \ swap >link @ 0<> and 
           nip
           0=
       ELSE  drop true  THEN ;
   
   : doer? ( -- flag ) \ name
       ghost >magic @ <do:> = ;
   
   : skip-defs ( -- )
       BEGIN  refill  WHILE  source -trailing nip 0= UNTIL  THEN ;
   
   \ Target header creation
   
 VARIABLE CreateFlag CreateFlag off  VARIABLE CreateFlag CreateFlag off
   
 : (Theader ( "name" -- ghost ) T align H view,  : (Theader ( "name" -- ghost )
   \  >in @ bl word count type 2 spaces >in !
     T align H view,
   tlast @ dup 0> IF  T 1 cells - THEN  A, H  there tlast !    tlast @ dup 0> IF  T 1 cells - THEN  A, H  there tlast !
   >in @ name, >in ! T here H tlastcfa !    >in @ name, >in ! T here H tlastcfa !
   CreateFlag @ IF    CreateFlag @ IF
Line 402  VARIABLE CreateFlag CreateFlag off Line 495  VARIABLE CreateFlag CreateFlag off
   Already @ IF  dup >end tdoes !    Already @ IF  dup >end tdoes !
   ELSE 0 tdoes ! THEN    ELSE 0 tdoes ! THEN
   80 flag!    80 flag!
   cross-doc-entry ;    cross-doc-entry cross-tag-entry ;
   
 VARIABLE ;Resolve 1 cells allot  VARIABLE ;Resolve 1 cells allot
   
Line 411  VARIABLE ;Resolve 1 cells allot Line 504  VARIABLE ;Resolve 1 cells allot
   
 >TARGET  >TARGET
 : Alias    ( cfa -- ) \ name  : Alias    ( cfa -- ) \ name
   dup 0< IF  to-doc off  THEN      >in @ skip? IF  2drop  EXIT  THEN  >in !
   (THeader over resolve T A, H 80 flag! ;      dup 0< has-prims 0= and
       IF
           ." needs prim: " >in @ bl word count type >in ! cr
       THEN
       (THeader over resolve T A, H 80 flag! ;
   : Alias:   ( cfa -- ) \ name
       >in @ skip? IF  2drop  EXIT  THEN  >in !
       dup 0< has-prims 0= and
       IF
           ." needs doer: " >in @ bl word count type >in ! cr
       THEN
       ghost tuck swap resolve <do:> swap >magic ! ;
 >CROSS  >CROSS
   
 \ Conditionals and Comments                            11may93jaw  \ Conditionals and Comments                            11may93jaw
Line 446  ghost (loop)    ghost (+loop) Line 550  ghost (loop)    ghost (+loop)
 ghost (next)                                    drop  ghost (next)                                    drop
 ghost unloop    ghost ;S                        2drop  ghost unloop    ghost ;S                        2drop
 ghost lit       ghost (compile) ghost !         2drop drop  ghost lit       ghost (compile) ghost !         2drop drop
 ghost (;code)   ghost noop                      2drop  ghost (does>)   ghost noop                      2drop
 ghost (.")      ghost (S")      ghost (ABORT")  2drop drop  ghost (.")      ghost (S")      ghost (ABORT")  2drop drop
 ghost '  ghost '                                         drop
   ghost :docol    ghost :doesjump ghost :dodoes   2drop drop
   ghost over      ghost =         ghost drop      2drop drop
   
 \ compile                                              10may93jaw  \ compile                                              10may93jaw
   
Line 460  ghost ' Line 566  ghost '
   ELSE  postpone literal postpone gexecute  THEN ;    ELSE  postpone literal postpone gexecute  THEN ;
                                         immediate                                          immediate
   
   \ generic threading modell
   : docol,  ( -- ) compile :docol T 0 , H ;
   
   : dodoes, ( -- ) T cfalign H compile :doesjump T 0 , H ;
   
   [IFUNDEF] (code) 
   Defer (code)
   Defer (end-code)
   [THEN]
   
   [IFUNDEF] ca>native
   defer ca>native
   [THEN]
   
 >TARGET  >TARGET
   : Code
     (THeader there resolve
     [ has-prims 0= [IF] ITC [ELSE] true [THEN] ] [IF]
     there 2 T cells H + ca>native T a, 0 , H
     [THEN]
     depth (code) ;
   
   : Code:
       ghost dup there ca>native resolve  <do:> swap >magic !
       depth (code) ;
   
   : end-code
       depth ?dup IF   1- <> ABORT" CROSS: Stack changed"
       ELSE true ABORT" CROSS: Stack empty" THEN
       (end-code) ;
                  
 : '  ( -- cfa ) bl word gfind 0= ABORT" CROSS: undefined "  : '  ( -- cfa ) bl word gfind 0= ABORT" CROSS: undefined "
   dup >magic @ <fwd> = ABORT" CROSS: forward " >link @ ;    dup >magic @ <fwd> = ABORT" CROSS: forward " >link @ ;
   
Line 475  Cond: chars ;Cond Line 611  Cond: chars ;Cond
 : alit, ( n -- )  compile lit T A,  H ;  : alit, ( n -- )  compile lit T A,  H ;
   
 >TARGET  >TARGET
   Cond: \G  T-\G ;Cond
   
 Cond:  Literal ( n -- )   restrict? lit, ;Cond  Cond:  Literal ( n -- )   restrict? lit, ;Cond
 Cond: ALiteral ( n -- )   restrict? alit, ;Cond  Cond: ALiteral ( n -- )   restrict? alit, ;Cond
   
 : Char ( "<char>" -- )  bl word char+ c@ ;  : Char ( "<char>" -- )  bl word char+ c@ ;
 Cond: [Char]   ( "<char>" -- )  restrict? Char  lit, ;Cond  Cond: [Char]   ( "<char>" -- )  restrict? Char  lit, ;Cond
   
   \ some special literals                                 27jan97jaw
   
   Cond: MAXU
    restrict? compile lit 
    tcell 0 ?DO FF T c, H LOOP ;Cond
   
   Cond: MINI
    restrict? 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
    ;Cond
    
   Cond: MAXI
    restrict? compile lit
    bigendian 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
    ;Cond
   
 >CROSS  >CROSS
 \ Target compiling loop                                12dec92py  \ Target compiling loop                                12dec92py
 \ ">tib trick thrown out                               10may93jaw  \ ">tib trick thrown out                               10may93jaw
Line 513  Cond: [Char]   ( "<char>" -- )  restrict Line 675  Cond: [Char]   ( "<char>" -- )  restrict
 \             is not allowed if a system should be ans conform  \             is not allowed if a system should be ans conform
   
 : : ( -- colon-sys ) \ Name  : : ( -- colon-sys ) \ Name
     >in @ skip? IF  drop skip-defs  EXIT  THEN  >in !
   (THeader ;Resolve ! there ;Resolve cell+ !    (THeader ;Resolve ! there ;Resolve cell+ !
   docol, depth T ] H ;    docol, depth T ] H ;
   
   : :noname ( -- colon-sys )
     T cfalign H there docol, depth T ] H ;
   
 Cond: EXIT ( -- )  restrict?  compile ;S  ;Cond  Cond: EXIT ( -- )  restrict?  compile ;S  ;Cond
   
 Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond  Cond: ?EXIT ( -- ) 1 abort" CROSS: using ?exit" ;Cond
Line 530  Cond: ; ( -- ) restrict? Line 696  Cond: ; ( -- ) restrict?
 Cond: [  restrict? state off ;Cond  Cond: [  restrict? state off ;Cond
   
 >CROSS  >CROSS
 : !does  :dodoes tlastcfa @ tuck T ! cell+ ! H ;  : !does
       tlastcfa @ dup there >r tdp ! compile :dodoes r> tdp ! T cell+ ! H ;
   
 >TARGET  >TARGET
 Cond: DOES> restrict?  Cond: DOES> restrict?
         compile (;code) dodoes, tdoes @ ?dup IF  @ T here H resolve THEN          compile (does>) dodoes, tdoes @ ?dup IF  @ T here H resolve THEN
         ;Cond          ;Cond
 : DOES> dodoes, T here H !does depth T ] H ;  : DOES> dodoes, T here H !does depth T ] H ;
   
Line 551  Cond: DOES> restrict? Line 718  Cond: DOES> restrict?
 \  DOES>  dup >exec @ execute ;  \  DOES>  dup >exec @ execute ;
   
 : gdoes,  ( ghost -- )  >end @ dup >magic @ <fwd> <>  : gdoes,  ( ghost -- )  >end @ dup >magic @ <fwd> <>
   IF dup >link @ dup 0< IF T A, 0 , H drop EXIT THEN drop THEN      IF
   :dodoes T A, H gexecute T here H cell - reloff ;          dup >magic @ <do:> =
           IF  gexecute T 0 , H  EXIT THEN
       THEN
       compile :dodoes gexecute T here H tcell - reloff ;
   
 : TCreate ( -- )  : TCreate ( -- )
   last-ghost @    last-ghost @
Line 575  Cond: DOES> restrict? Line 745  Cond: DOES> restrict?
   here ghostheader    here ghostheader
   :noname postpone gdoes> postpone ?EXIT ;    :noname postpone gdoes> postpone ?EXIT ;
   
   : by:     ( -- addr [xt] [colon-sys] ) \ name
     ghost
     :noname postpone gdoes> postpone ?EXIT ;
   
 : ;DO ( addr [xt] [colon-sys] -- )  : ;DO ( addr [xt] [colon-sys] -- )
   postpone ;    ( S addr xt )    postpone ;    ( S addr xt )
   over >exec ! ; immediate    over >exec ! ; immediate
Line 586  Cond: DOES> restrict? Line 760  Cond: DOES> restrict?
 \ Variables and Constants                              05dec92py  \ Variables and Constants                              05dec92py
   
 Build:  ;  Build:  ;
 DO: ( ghost -- addr ) ;DO  by: :dovar ( ghost -- addr ) ;DO
 Builder Create  Builder Create
 by Create :dovar resolve  
   
 Build: T 0 , H ;  Build: T 0 , H ;
 by Create  by Create
Line 612  Variable tudp 0 tudp ! Line 785  Variable tudp 0 tudp !
 >TARGET  >TARGET
   
 Build: T 0 u, , H ;  Build: T 0 u, , H ;
 DO: ( ghost -- up-addr )  T @ H tup @ + ;DO  by: :douser ( ghost -- up-addr )  T @ H tup @ + ;DO
 Builder User  Builder User
 by User :douser resolve  
   
 Build: T 0 u, , 0 u, drop H ;  Build: T 0 u, , 0 u, drop H ;
 by User  by User
Line 624  Build: T 0 au, , H ; Line 796  Build: T 0 au, , H ;
 by User  by User
 Builder AUser  Builder AUser
   
   Build:  ( n -- ) ;
   by: :docon ( ghost -- n ) T @ H ;DO
   Builder (Constant)
   
 Build:  ( n -- ) T , H ;  Build:  ( n -- ) T , H ;
 DO: ( ghost -- n ) T @ H ;DO  by (Constant)
 Builder Constant  Builder Constant
 by Constant :docon resolve  
   
 Build:  ( n -- ) T A, H ;  Build:  ( n -- ) T A, H ;
 by Constant  by (Constant)
 Builder AConstant  Builder AConstant
   
 Build:  ( d -- ) T , , H ;  Build:  ( d -- ) T , , H ;
 DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO  DO: ( ghost -- d ) T dup cell+ @ swap @ H ;DO
 Builder 2Constant  Builder 2Constant
   
 Build: T 0 , H ;  Build: T , H ;
 by Constant  by (Constant)
 Builder Value  Builder Value
   
   Build: T A, H ;
   by (Constant)
   Builder AValue
   
 Build:  ( -- ) compile noop ;  Build:  ( -- ) compile noop ;
 DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO  by: :dodefer ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
 Builder Defer  Builder Defer
 by Defer :dodefer resolve  
   Build:  ( inter comp -- ) swap T immediate A, A, H ;
   DO: ( ghost -- ) ABORT" CROSS: Don't execute" ;DO
   Builder interpret/compile:
   
 \ Sturctures                                           23feb95py  \ Sturctures                                           23feb95py
   
Line 654  by Defer :dodefer resolve Line 836  by Defer :dodefer resolve
  1- tuck +  swap invert and ;   1- tuck +  swap invert and ;
 >TARGET  >TARGET
   
 Build:  >r rot r@ nalign  dup T , H  ( align1 size offset )  Build: ;
         + swap r> nalign ;  by: :dofield T @ H + ;DO
 DO: T @ H + ;DO  Builder (Field)
   
   Build: ( align1 offset1 align size "name" --  align2 offset2 )
       rot dup T , H ( align1 align size offset1 )
       + >r nalign r> ;
   by (Field)
 Builder Field  Builder Field
 by Field :dostruc resolve  
   
 : struct  T 0 1 chars H ;  : struct  T 1 chars 0 H ;
 : end-struct  T 2Constant H ;  : end-struct  T 2Constant H ;
   
 : cells: ( n -- size align )  : cell% ( -- align size )
     T cells 1 cells H ;      T 1 cells H dup ;
   
 \ ' 2Constant Alias2 end-struct  \ ' 2Constant Alias2 end-struct
 \ 0 1 T Chars H 2Constant struct  \ 0 1 T Chars H 2Constant struct
Line 712  Cond: AGAIN     restrict? sys? compile b Line 898  Cond: AGAIN     restrict? sys? compile b
 Cond: UNTIL     restrict? sys? compile ?branch <resolve ;Cond  Cond: UNTIL     restrict? sys? compile ?branch <resolve ;Cond
 Cond: REPEAT    restrict? over 0= ?struc compile AGAIN compile THEN ;Cond  Cond: REPEAT    restrict? over 0= ?struc compile AGAIN compile THEN ;Cond
   
   Cond: CASE      restrict? 0 ;Cond
   Cond: OF        restrict? 1+ >r compile over compile = compile IF compile drop
                   r> ;Cond
   Cond: ENDOF     restrict? >r compile ELSE r> ;Cond
   Cond: ENDCASE   restrict? compile drop 0 ?DO  compile THEN  LOOP ;Cond
   
 \ Structural Conditionals                              12dec92py  \ Structural Conditionals                              12dec92py
   
 Cond: DO        restrict? compile (do)   T here H ;Cond  Cond: DO        restrict? compile (do)   T here H ;Cond
 Cond: ?DO       restrict? compile (?do)  (leave T here H ;Cond  Cond: ?DO       restrict? compile (?do)  T (leave here H ;Cond
 Cond: FOR       restrict? compile (for)  T here H ;Cond  Cond: FOR       restrict? compile (for)  T here H ;Cond
   
 >CROSS  >CROSS
 : loop]   dup <resolve cell - compile DONE compile unloop ;  : loop]   dup <resolve tcell - compile DONE compile unloop ;
 >TARGET  >TARGET
   
 Cond: LOOP      restrict? sys? compile (loop)  loop] ;Cond  Cond: LOOP      restrict? sys? compile (loop)  loop] ;Cond
Line 778  also minimal Line 970  also minimal
   
 \ define new [IFDEF] and [IFUNDEF]                      20may93jaw  \ define new [IFDEF] and [IFUNDEF]                      20may93jaw
   
 : there? bl word gfind IF >magic @ <fwd> <> ELSE drop false THEN ;  : defined? defined? ;
   : needed? needed? ;
   : doer? doer? ;
   
 : [IFDEF] there? postpone [IF] ;  : [IFDEF] defined? postpone [IF] ;
 : [IFUNDEF] there? 0= postpone [IF] ;  : [IFUNDEF] defined? 0= postpone [IF] ;
   
 \ C: \- \+ Conditional Compiling                         09jun93jaw  \ C: \- \+ Conditional Compiling                         09jun93jaw
   
 : C: >in @ there? 0=  : C: >in @ defined? 0=
      IF    >in ! T : H       IF    >in ! T : H
      ELSE drop       ELSE drop
         BEGIN bl word dup c@          BEGIN bl word dup c@
Line 797  also minimal Line 991  also minimal
   
 also minimal  also minimal
   
 : \- there? IF postpone \ THEN ;  \G interprets the line if word is not defined
 : \+ there? 0= IF postpone \ THEN ;  : \- defined? IF postpone \ THEN ;
   
   \G interprets the line if word is defined
   : \+ defined? 0= IF postpone \ THEN ;
   
   Cond: \- \- ;Cond
   Cond: \+ \+ ;Cond
   
   : ?? bl word find IF execute ELSE drop 0 THEN ;
   
   : needed:
   \G defines ghost for words that we want to be compiled
     BEGIN >in @ bl word c@ WHILE >in ! ghost drop REPEAT drop ;
   
 : [IF]   postpone [IF] ;  : [IF]   postpone [IF] ;
 : [THEN] postpone [THEN] ;  : [THEN] postpone [THEN] ;
Line 810  Cond: [IFUNDEF] [IFUNDEF] ;Cond Line 1016  Cond: [IFUNDEF] [IFUNDEF] ;Cond
 Cond: [THEN]    [THEN] ;Cond  Cond: [THEN]    [THEN] ;Cond
 Cond: [ELSE]    [ELSE] ;Cond  Cond: [ELSE]    [ELSE] ;Cond
   
   previous
   
 \ save-cross                                           17mar93py  \ save-cross                                           17mar93py
   
 \ i'm not interested in bigforth features this time    10may93jaw  >CROSS
 \ [IFDEF] file  Create magic  s" Gforth10" here over allot swap move
 \ also file  
 \ [THEN]  
 \ included throw after create-file                     11may93jaw  
   
 bigendian Constant bigendian  char 1 bigendian + tcell + magic 7 + c!
   
 : save-cross ( "name" -- )  : save-cross ( "image-name" "binary-name" -- )
   bl parse ." Saving to " 2dup type    bl parse ." Saving to " 2dup type cr
   w/o bin create-file throw >r    w/o bin create-file throw >r
   s" gforth00"  r@ write-file throw \ write magic    TNIL IF
         s" #! "   r@ write-file throw
         bl parse  r@ write-file throw
         s"  -i"   r@ write-file throw
         #lf       r@ emit-file throw
         r@ dup file-position throw drop 8 mod 8 swap ( file-id limit index )
         ?do
             bl over emit-file throw
         loop
         drop
         magic 8       r@ write-file throw \ write magic
     ELSE
         bl parse 2drop
     THEN
   image @ there r@ write-file throw \ write image    image @ there r@ write-file throw \ write image
   bit$  @ there 1- cell>bit rshift 1+    TNIL IF
         bit$  @ there 1- tcell>bit rshift 1+
                 r@ write-file throw \ write tags                  r@ write-file throw \ write tags
     THEN
   r> close-file throw ;    r> close-file throw ;
   
 \ words that should be in minimal  \ words that should be in minimal
   >MINIMAL
   also minimal
   
 : + + ;         : 1- 1- ;  bigendian Constant bigendian
 : - - ;         : 2* 2* ;  : save-cross save-cross ;
 : * * ;         : / / ;  : here there ;
 : dup dup ;     : over over ;  also forth 
 : swap swap ;   : rot rot ;  [IFDEF] Label : Label Label ; [THEN] 
 : drop drop ;   : =   = ;  [IFDEF] start-macros : start-macros start-macros ; [THEN]
 : lshift lshift ; : 2/ 2/ ;  previous
   
   : + + ;
   : or or ;
   : 1- 1- ;
   : - - ;
   : 2* 2* ;
   : * * ;
   : / / ;
   : dup dup ;
   : over over ;
   : swap swap ;
   : rot rot ;
   : drop drop ;
   : =   = ;
   : 0=   0= ;
   : lshift lshift ;
   : 2/ 2/ ;
 : . . ;  : . . ;
 cell constant cell  : const ;
   
   \ mach-file count included
   
 \ include bug5.fs  : all-words    ['] false    IS skip? ;
 \ only forth also minimal definitions  : needed-words ['] needed?  IS skip? ;
   : undef-words  ['] defined? IS skip? ;
   
 : \  postpone \ ;  : \  postpone \ ;  immediate
 : \G postpone \G ;  : \G T-\G ; immediate
 : (  postpone ( ;  : (  postpone ( ;  immediate
 : include bl word count included ;  : include bl word count included ;
 : .( [char] ) parse type ;  : .( [char] ) parse type ;
 : cr cr ;  : cr cr ;
Line 860  only forth also minimal definitions Line 1102  only forth also minimal definitions
 : hex           hex ;  : hex           hex ;
   
 : tudp          T tudp H ;  : tudp          T tudp H ;
 : tup           T tup H ;  minimal  : tup           T tup H ;
   
   : doc-off       false T to-doc H ! ;
   : doc-on        true  T to-doc H ! ;
   
   minimal
   
 \ for debugging...  \ for debugging...
 : order         order ;  : order         order ;

Removed from v.1.25  
changed lines
  Added in v.1.51


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