Diff for /gforth/see.fs between versions 1.14 and 1.43

version 1.14, 1996/08/26 10:07:21 version 1.43, 2002/12/13 21:20:39
Line 1 Line 1
 \ SEE.FS       highend SEE for ANSforth                16may93jaw  \ SEE.FS       highend SEE for ANSforth                16may93jaw
   
 \ Copyright (C) 1995 Free Software Foundation, Inc.  \ Copyright (C) 1995,2000 Free Software Foundation, Inc.
   
 \ This file is part of Gforth.  \ This file is part of Gforth.
   
Line 16 Line 16
   
 \ 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.
   
   
 \ May be cross-compiled  \ May be cross-compiled
Line 25 Line 25
   
 \ Ideas:        Level should be a stack  \ Ideas:        Level should be a stack
   
   require look.fs
 require termsize.fs  require termsize.fs
   require wordinfo.fs
   [IFUNDEF] .name
   : id. ( nt -- ) \ gforth
       \G Print the name of the word represented by @var{nt}.
       \ this name comes from fig-Forth
       name>string type space ;
   
   ' id. alias .id ( nt -- )
   \G F83 name for @code{id.}.
   
   ' id. alias .name ( nt -- )
   \G Gforth <=0.5.0 name for @code{id.}.
   
   [THEN]
   
 decimal  decimal
   
Line 50  VARIABLE Level Line 65  VARIABLE Level
 : level-        -7 Level +! ;  : level-        -7 Level +! ;
   
 VARIABLE nlflag  VARIABLE nlflag
   VARIABLE uppercase      \ structure words are in uppercase
   
 DEFER nlcount ' noop IS nlcount  DEFER nlcount ' noop IS nlcount
   
 : nl            nlflag on ;  : nl            nlflag on ;
 : (nl)          nlcount  : (nl)          nlcount
                 XPos @ Level @ = ?Exit                  XPos @ Level @ = IF EXIT THEN \ ?Exit
                 C-Formated @ IF                  C-Formated @ IF
                 C-Output @                  C-Output @
                 IF C-Clearline @ IF cols XPos @ - spaces                  IF C-Clearline @ IF cols XPos @ - spaces
Line 68  DEFER nlcount ' noop IS nlcount Line 84  DEFER nlcount ' noop IS nlcount
                 nlflag @ IF (nl) nlflag off THEN                  nlflag @ IF (nl) nlflag off THEN
                 XPos @ over + cols u>= IF (nl) THEN ;                  XPos @ over + cols u>= IF (nl) THEN ;
   
   : c-to-upper ( c1 -- c2 ) \ gforth
       \ nac05feb1999 there is a primitive, toupper, with this function
       dup [char] a >= over [char] z <= and if  bl -  then ;
   
 : ctype         ( adr len -- )  : ctype         ( adr len -- )
                 warp? dup XPos +! C-Output @ IF type ELSE 2drop THEN ;                  warp? dup XPos +! C-Output @ 
                   IF uppercase @ IF bounds ?DO i c@ c-to-upper emit LOOP
                                     uppercase off ELSE type THEN
                   ELSE 2drop THEN ;
   
 : cemit         1 warp?  : cemit         1 warp?
                 over bl = Level @ XPos @ = and                  over bl = Level @ XPos @ = and
                 IF 2drop ELSE XPos +! C-Output @ IF emit ELSE drop THEN                  IF 2drop ELSE XPos +! C-Output @ IF emit ELSE drop THEN
                 THEN ;                  THEN ;
   
 DEFER .string  DEFER .string ( c-addr u n -- )
   
 [IFDEF] Green  [IFDEF] Green
 VARIABLE Colors Colors on  VARIABLE Colors Colors on
Line 98  VARIABLE Colors Colors on Line 121  VARIABLE Colors Colors on
 ' (.string) IS .string  ' (.string) IS .string
   
   
 : .struc        Str# .string ;  : .struc        
           uppercase on Str# .string ;
   
 \ CODES                                                 15may93jaw  \ CODES (Branchtypes)                                    15may93jaw
   
 21 CONSTANT RepeatCode  21 CONSTANT RepeatCode
 22 CONSTANT AgainCode  22 CONSTANT AgainCode
Line 110  VARIABLE Colors Colors on Line 134  VARIABLE Colors Colors on
 11 CONSTANT AheadCode  11 CONSTANT AheadCode
 13 CONSTANT WhileCode2  13 CONSTANT WhileCode2
 14 CONSTANT Disable  14 CONSTANT Disable
   15 CONSTANT LeaveCode
   
   
 \ FORMAT WORDS                                          13jun93jaw  \ FORMAT WORDS                                          13jun93jaw
   
 VARIABLE C-Stop  VARIABLE C-Stop
 VARIABLE Branches  VARIABLE Branches
   
 VARIABLE BranchPointer  VARIABLE BranchPointer  \ point to the end of branch table
 VARIABLE SearchPointer  VARIABLE SearchPointer
 CREATE BranchTable 500 allot  
   \ The branchtable consists of three entrys:
   \ address of branch , branch destination , branch type
   
   CREATE BranchTable 128 cells allot
 here 3 cells -  here 3 cells -
 ACONSTANT MaxTable  ACONSTANT MaxTable
   
 : FirstBranch BranchTable cell+ SearchPointer ! ;  : FirstBranch BranchTable cell+ SearchPointer ! ;
   
 : (BranchAddr?) ( a-addr -- a-addr true | false )  : (BranchAddr?) ( a-addr1 -- a-addr2 true | false )
   \ searches a branch with destination a-addr1
   \ a-addr1: branch destination
   \ a-addr2: pointer in branch table
         SearchPointer @          SearchPointer @
         BEGIN   dup BranchPointer @ u<          BEGIN   dup BranchPointer @ u<
         WHILE          WHILE
Line 153  ACONSTANT MaxTable Line 186  ACONSTANT MaxTable
         2drop true          2drop true
         THEN ;          THEN ;
   
   : MyBranch      ( a-addr -- a-addr a-addr2 )
   \ finds branch table entry for branch at a-addr
                   dup @ over +
                   BranchAddr?
                   BEGIN
                   WHILE 1 cells - @
                         over <>
                   WHILE dup @ over +
                         MoreBranchAddr?
                   REPEAT
                   SearchPointer @ 3 cells -
                   ELSE    true ABORT" SEE: Table failure"
                   THEN ;
   
 \  \
 \                 addrw               addrt  \                 addrw               addrt
 \       BEGIN ... WHILE ... AGAIN ... THEN  \       BEGIN ... WHILE ... AGAIN ... THEN
Line 201  VARIABLE C-Pass Line 248  VARIABLE C-Pass
 : back? ( n -- flag ) 0< ;  : back? ( n -- flag ) 0< ;
 : ahead? ( n -- flag ) 0> ;  : ahead? ( n -- flag ) 0> ;
   
 : c-(compile)  
     Display?  
     IF  
         s" POSTPONE " Com# .string  
         dup @ look 0= ABORT" SEE: No valid XT"  
         name>string 0 .string bl cemit  
     THEN  
     cell+ ;  
   
 : c-lit  : c-lit
     Display? IF      Display? IF
         dup @ dup abs 0 <# #S rot sign #> 0 .string bl cemit          dup @ dup abs 0 <# #S rot sign #> 0 .string bl cemit
     THEN      THEN
     cell+ ;      cell+ ;
   
 : c-@local#  : .word ( addr xt -- addr )
     Display? IF      look 0= IF
         S" @local" 0 .string          drop dup 1 cells - @ dup body> look
         dup @ dup 1 cells / abs 0 <# #S rot sign #> 0 .string bl cemit          IF
     THEN              nip dup ." <" name>string rot wordinfo .string ." >"
     cell+ ;  
   
 : c-flit  
     Display? IF  
         dup f@ scratch represent 0=  
         IF    2drop  scratch 3 min 0 .string  
         ELSE          ELSE
             IF  '- cemit  THEN  1-              drop ." <" 0 .r ." >"
             scratch over c@ cemit '. cemit 1 /string 0 .string          THEN
             'E cemit      ELSE
             dup abs 0 <# #S rot sign #> 0 .string bl cemit          dup cell+ @ immediate-mask and
         THEN THEN          IF
     float+ ;              bl cemit  ." POSTPONE "
           THEN
 : c-f@local#          dup name>string rot wordinfo .string
     Display? IF      THEN ;
         S" f@local" 0 .string  
         dup @ dup 1 floats / abs 0 <# #S rot sign #> 0 .string bl cemit  : c-call
     THEN      Display? IF  ." call " dup @ body> .word bl cemit  THEN  cell+ ;
     cell+ ;  
   : .name-without ( addr -- addr )
 : c-laddr#  \ prints a name without () e.g. (+LOOP) or (s")
     Display? IF    dup 1 cells - @ look 
         S" laddr# " 0 .string    IF   name>string over c@ '( = IF 1 /string THEN
         dup @ dup abs 0 <# #S rot sign #> 0 .string bl cemit         2dup + 1- c@ ') = IF 1- THEN .struc ELSE drop 
     THEN    THEN ;
     cell+ ;  
   
 : c-lp+!#  
     Display? IF  
         S" lp+!# " 0 .string  
         dup @ dup abs 0 <# #S rot sign #> 0 .string bl cemit  
     THEN  
     cell+ ;  
   
 : c-s"  
         count 2dup + aligned -rot  
         Display?  
         IF      [char] S cemit [char] " cemit bl cemit 0 .string  
                 [char] " cemit bl cemit  
         ELSE    2drop  
         THEN ;  
   
 : c-."  
         count 2dup + aligned -rot  
         Display?  
         IF      [char] . cemit  
                 [char] " cemit bl cemit 0 .string  
                 [char] " cemit bl cemit  
         ELSE    2drop  
         THEN ;  
   
 : c-c"  : c-c"
           Display? IF nl .name-without THEN
         count 2dup + aligned -rot          count 2dup + aligned -rot
         Display?          Display?
         IF      [char] C cemit [char] " cemit bl cemit 0 .string          IF      bl cemit 0 .string
                 [char] " cemit bl cemit                  [char] " cemit bl cemit
         ELSE    2drop          ELSE    2drop
         THEN ;          THEN ;
   
   
 : Forward? ( a-addr true | false -- )  : Forward? ( a-addr true | false -- a-addr true | false )
   \ a-addr1 is pointer into branch table
   \ returns true when jump is a forward jump
         IF      dup dup @ swap 1 cells - @ -          IF      dup dup @ swap 1 cells - @ -
                 Ahead? IF true ELSE drop false THEN                  Ahead? IF true ELSE drop false THEN
                 \ only if forward jump                  \ only if forward jump
         ELSE    false THEN ;          ELSE    false THEN ;
   
 : RepeatCheck  : RepeatCheck ( a-addr1 a-addr2 true | false -- false )
         IF  BEGIN  2dup          IF  BEGIN  2dup
                    1 cells - @ swap dup @ +                     1 cells - @ swap dup @ +
                    u<=                     u<=
Line 327  VARIABLE C-Pass Line 337  VARIABLE C-Pass
                         IF      drop S" REPEAT " .struc nl                          IF      drop S" REPEAT " .struc nl
                         ELSE    S" AGAIN " .struc nl                          ELSE    S" AGAIN " .struc nl
                         THEN                          THEN
                 ELSE    dup cell+ BranchAddr? Forward?                  ELSE    MyBranch cell+ @ LeaveCode =
                         IF      dup cell+ @ WhileCode2 =                          IF      S" LEAVE " .struc
                                 IF nl S" ELSE" .struc level+                          ELSE
                                 ELSE level- nl S" ELSE" .struc level+ THEN                                  dup cell+ BranchAddr? Forward?
                                 cell+ Disable swap !                                  IF      dup cell+ @ WhileCode2 =
                         ELSE    S" AHEAD" .struc level+                                          IF nl S" ELSE" .struc level+
                         THEN                                          ELSE level- nl S" ELSE" .struc level+ THEN
                                           cell+ Disable swap !
                                   ELSE    S" AHEAD" .struc level+
                                   THEN
                           THEN
                 THEN                  THEN
         THEN          THEN
         Debug?          Debug?
Line 341  VARIABLE C-Pass Line 355  VARIABLE C-Pass
         ELSE    cell+          ELSE    cell+
         THEN ;          THEN ;
   
 : MyBranch      ( a-addr -- a-addr a-addr2 )  
                 dup @ over +  
                 BranchAddr?  
                 BEGIN  
                 WHILE 1 cells - @  
                       over <>  
                 WHILE dup @ over +  
                       MoreBranchAddr?  
                 REPEAT  
                 SearchPointer @ 3 cells -  
                 ELSE    true ABORT" SEE: Table failure"  
                 THEN ;  
   
 : DebugBranch  : DebugBranch
         Debug?          Debug?
         IF      dup @ over + swap THEN ; \ return 2 different addresses          IF      dup @ over + swap THEN ; \ return 2 different addresses
Line 376  VARIABLE C-Pass Line 377  VARIABLE C-Pass
                                 level- nl                                  level- nl
                                 S" WHILE " .struc                                  S" WHILE " .struc
                                 level+                                  level+
                         ELSE    nl S" IF " .struc level+                          ELSE    MyBranch cell+ @ LeaveCode =
                                   IF   s" 0= ?LEAVE " .struc
                                   ELSE nl S" IF " .struc level+
                                   THEN
                         THEN                          THEN
                 THEN                  THEN
         THEN          THEN
         DebugBranch          DebugBranch
         cell+ ;          cell+ ;
   
 : c-?branch-lp+!#  c-?branch cell+ ;  : c-for
 : c-branch-lp+!#   c-branch  cell+ ;          Display? IF nl S" FOR" .struc level+ THEN ;
   
   : c-loop
           Display? IF level- nl .name-without bl cemit nl THEN
           DebugBranch cell+ 
           Scan? 
           IF      dup BranchAddr? 
                   BEGIN   WHILE cell+ LeaveCode swap !
                           dup MoreBranchAddr?
                   REPEAT
           THEN
           cell+ ;
   
 : c-do  : c-do
         Display? IF nl S" DO" .struc level+ THEN ;          Display? IF nl .name-without level+ THEN ;
   
 : c-?do  : c-?do
         Display? IF nl S" ?DO" .struc level+ THEN          Display? IF nl S" ?DO" .struc level+ THEN
         DebugBranch cell+ ;          DebugBranch cell+ ;
   
 : c-for  
         Display? IF nl S" FOR" .struc level+ THEN ;  
   
 : c-next  
         Display? IF level- nl S" NEXT " .struc nl THEN  
         DebugBranch cell+ cell+ ;  
   
 : c-loop  
         Display? IF level- nl S" LOOP " .struc nl THEN  
         DebugBranch cell+ cell+ ;  
   
 : c-+loop  
         Display? IF level- nl S" +LOOP " .struc nl THEN  
         DebugBranch cell+ cell+ ;  
   
 : c-s+loop  
         Display? IF level- nl S" S+LOOP " .struc nl THEN  
         DebugBranch cell+ cell+ ;  
   
 : c--loop  
         Display? IF level- nl S" -LOOP " .struc nl THEN  
         DebugBranch cell+ cell+ ;  
   
 : c-next-lp+!#  c-next cell+ ;  
 : c-loop-lp+!#  c-loop cell+ ;  
 : c-+loop-lp+!#  c-+loop cell+ ;  
 : c-s+loop-lp+!#  c-s+loop cell+ ;  
 : c--loop-lp+!#  c--loop cell+ ;  
   
 : c-leave  
         Display? IF S" LEAVE " .struc THEN  
         Debug? IF dup @ + THEN cell+ ;  
   
 : c-?leave  
         Display? IF S" ?LEAVE " .struc THEN  
         cell+ DebugBranch swap cell+ swap cell+ ;  
   
 : c-exit  dup 1 cells -  : c-exit  dup 1 cells -
         CheckEnd          CheckEnd
         IF      Display? IF nlflag off S" ;" Com# .string THEN          IF      Display? IF nlflag off S" ;" Com# .string THEN
Line 438  VARIABLE C-Pass Line 416  VARIABLE C-Pass
         THEN          THEN
         Debug? IF drop THEN ;          Debug? IF drop THEN ;
   
 : c-does>               \ end of create part  
         Display? IF S" DOES> " Com# .string THEN  
         Cell+ cell+ ;  
   
 : c-abort"  : c-abort"
         count 2dup + aligned -rot          count 2dup + aligned -rot
         Display?          Display?
Line 451  VARIABLE C-Pass Line 425  VARIABLE C-Pass
         ELSE    2drop          ELSE    2drop
         THEN ;          THEN ;
   
   [IFDEF] (does>)
   : c-does>               \ end of create part
           Display? IF S" DOES> " Com# .string THEN
           maxaligned /does-handler + ;
   [THEN]
   
   [IFDEF] (compile)
   : c-(compile)
       Display?
       IF
           s" POSTPONE " Com# .string
           dup @ look 0= ABORT" SEE: No valid XT"
           name>string 0 .string bl cemit
       THEN
       cell+ ;
   [THEN]
   
 CREATE C-Table  CREATE C-Table
         ' lit A,            ' c-lit A,                  ' lit A,            ' c-lit A,
         ' @local# A,        ' c-@local# A,  [IFDEF] call    ' call A,           ' c-call A, [THEN]
         ' flit A,           ' c-flit A,  [IFDEF] (s")    ' (s") A,           ' c-c" A, [THEN]
         ' f@local# A,       ' c-f@local# A,  [IFDEF] (.")    ' (.") A,           ' c-c" A, [THEN]
         ' laddr# A,         ' c-laddr# A,  [IFDEF] "lit    ' "lit A,           ' c-c" A, [THEN]
         ' lp+!# A,          ' c-lp+!# A,  [IFDEF] (c")    ' (c") A,           ' c-c" A, [THEN]
         ' (s") A,           ' c-s" A,                  ' (do) A,           ' c-do A,
         ' (.") A,           ' c-." A,  [IFDEF] (+do)   ' (+do) A,          ' c-do A, [THEN]
         ' "lit A,           ' c-c" A,  [IFDEF] (u+do)  ' (u+do) A,         ' c-do A, [THEN]
         comp' leave drop A, ' c-leave A,  [IFDEF] (-do)   ' (-do) A,          ' c-do A, [THEN]
         comp' ?leave drop A, ' c-?leave A,  [IFDEF] (u-do)  ' (u-do) A,         ' c-do A, [THEN]
         ' (do) A,           ' c-do A,                  ' (?do) A,          ' c-?do A,
         ' (?do) A,          ' c-?do A,                  ' (for) A,          ' c-for A,
         ' (for) A,          ' c-for A,                  ' ?branch A,        ' c-?branch A,
         ' ?branch A,        ' c-?branch A,                  ' branch A,         ' c-branch A,
         ' branch A,         ' c-branch A,                  ' (loop) A,         ' c-loop A,
         ' (loop) A,         ' c-loop A,                  ' (+loop) A,        ' c-loop A,
         ' (+loop) A,        ' c-+loop A,  [IFDEF] (s+loop) ' (s+loop) A,       ' c-loop A, [THEN]
         ' (s+loop) A,       ' c-s+loop A,  [IFDEF] (-loop) ' (-loop) A,        ' c-loop A, [THEN]
         ' (-loop) A,        ' c--loop A,                  ' (next) A,         ' c-loop A,
         ' (next) A,         ' c-next A,                  ' ;s A,             ' c-exit A,
         ' ?branch-lp+!# A,  ' c-?branch-lp+!# A,  [IFDEF] (abort") ' (abort") A,      ' c-abort" A, [THEN]
         ' branch-lp+!# A,   ' c-branch-lp+!# A,  \ only defined if compiler is loaded
         ' (loop)-lp+!# A,   ' c-loop-lp+!# A,  [IFDEF] (compile) ' (compile) A,      ' c-(compile) A, [THEN]
         ' (+loop)-lp+!# A,  ' c-+loop-lp+!# A,  [IFDEF] (does>) ' (does>) A,        ' c-does> A, [THEN]
         ' (s+loop)-lp+!# A, ' c-s+loop-lp+!# A,                  0 ,             here 0 ,
         ' (-loop)-lp+!# A,  ' c--loop-lp+!# A,  
         ' (next)-lp+!# A,   ' c-next-lp+!# A,  avariable c-extender
         ' ;s A,             ' c-exit A,  c-extender !
         ' (does>) A,        ' c-does> A,  
         ' (abort") A,       ' c-abort" A,  
         ' (compile) A,      ' c-(compile) A,  
         0 ,  
   
 \ DOTABLE                                               15may93jaw  \ DOTABLE                                               15may93jaw
   
 : DoTable ( cfa -- flag )  : DoTable ( cfa -- flag )
         C-Table          C-Table
         BEGIN   dup @ dup          BEGIN   dup @ dup 0= 
         WHILE   2 pick <>                  IF drop cell+ @ dup 
                     IF ( next table!) dup @ ELSE 
                           ( end!) 2drop false EXIT THEN 
                   THEN
                   \ jump over to extender, if any 26jan97jaw
                   xt>threaded 2 pick <>
         WHILE   2 cells +          WHILE   2 cells +
         REPEAT          REPEAT
         nip cell+ perform          nip cell+ perform
         true          true
         ELSE          ;
         2drop drop false  
         THEN ;  
   
 : BranchTo? ( a-addr -- a-addr )  : BranchTo? ( a-addr -- a-addr )
         Display?  IF     dup BranchAddr?          Display?  IF    dup BranchAddr?
                         IF BEGIN cell+ @ dup 20 u>                          IF
                                   BEGIN cell+ @ dup 20 u>
                                 IF drop nl S" BEGIN " .struc level+                                  IF drop nl S" BEGIN " .struc level+
                                 ELSE                                  ELSE
                                   dup Disable <>                                    dup Disable <> over LeaveCode <> and
                                   IF   WhileCode2 =                                    IF   WhileCode2 =
                                        IF nl S" THEN " .struc nl ELSE                                         IF nl S" THEN " .struc nl ELSE
                                        level- nl S" THEN " .struc nl THEN                                         level- nl S" THEN " .struc nl THEN
Line 518  CREATE C-Table Line 508  CREATE C-Table
                   THEN ;                    THEN ;
   
 : analyse ( a-addr1 -- a-addr2 )  : analyse ( a-addr1 -- a-addr2 )
         Branches @ IF BranchTo? THEN      Branches @ IF BranchTo? THEN
         dup cell+ swap @      dup cell+ swap @
         dup >r DoTable r> swap IF drop EXIT THEN      dup >r DoTable r> swap IF drop EXIT THEN
         Display?      Display?
         IF look 0= IF  drop dup 1 cells - @ .  \ ABORT" SEE: Bua!"      IF
            ELSE  dup cell+ count 31 and rot wordinfo .string  THEN  bl cemit          .word bl cemit
         ELSE drop      ELSE
         THEN ;          drop
       THEN ;
   
 : c-init  : c-init
         0 YPos ! 0 XPos !          0 YPos ! 0 XPos !
Line 553  Defer xt-see-xt ( xt -- ) Line 544  Defer xt-see-xt ( xt -- )
     then      then
     space ;      space ;
   
 Defer discode ( addr -- )  Defer discode ( addr u -- ) \ gforth
 \  hook for the disassembler: disassemble code at addr (as far as the  \G hook for the disassembler: disassemble code at addr of length u
 \  disassembler thinks is sensible)  ' dump IS discode
 :noname ( addr -- )  
     drop ." ..." ;  : next-head ( addr1 -- addr2 ) \ gforth
 IS discode      \G find the next header starting after addr1, up to here (unreliable).
       here swap u+do
           i head? -2 and if
               i unloop exit
           then
       cell +loop
       here ;
   
   : umin ( u1 u2 -- u )
       2dup u>
       if
           swap
       then
       drop ;
           
   : next-prim ( addr1 -- addr2 ) \ gforth
       \G find the next primitive after addr1 (unreliable)
       1+ >r -1 primstart
       begin ( umin head R: boundary )
           @ dup
       while
           tuck name>int >code-address ( head1 umin ca R: boundary )
           r@ - umin
           swap
       repeat
       drop dup r@ negate u>=
       \ "umin+boundary within [0,boundary)" = "umin within [-boundary,0)"
       if ( umin R: boundary ) \ no primitive found behind -> use a default length
           drop 31
       then
       r> + ;
   
 : seecode ( xt -- )  : seecode ( xt -- )
     dup s" Code" .defname      dup s" Code" .defname
     >body discode      >code-address
     ."  end-code" cr ;      dup in-dictionary? \ user-defined code word?
       if
           dup next-head
       else
           dup next-prim
       then
       over - discode
       ." end-code" cr ;
 : seevar ( xt -- )  : seevar ( xt -- )
     s" Variable" .defname cr ;      s" Variable" .defname cr ;
 : seeuser ( xt -- )  : seeuser ( xt -- )
Line 577  IS discode Line 605  IS discode
 : seedefer ( xt -- )  : seedefer ( xt -- )
     dup >body @ xt-see-xt cr      dup >body @ xt-see-xt cr
     dup s" Defer" .defname cr      dup s" Defer" .defname cr
     >name dup ??? = if      >name ?dup-if
         drop ." lastxt >body !"  
     else  
         ." IS " .name cr          ." IS " .name cr
       else
           ." lastxt >body !"
     then ;      then ;
 : see-threaded ( addr -- )  : see-threaded ( addr -- )
     C-Pass @ DebugMode = IF      C-Pass @ DebugMode = IF
Line 594  IS discode Line 622  IS discode
     S" DOES> " Com# .string XPos @ Level !      S" DOES> " Com# .string XPos @ Level !
     >does-code see-threaded ;      >does-code see-threaded ;
 : seecol ( xt -- )  : seecol ( xt -- )
     dup s" :" .defname cr      dup s" :" .defname nl
     2 Level !      2 Level !
     >body see-threaded ;      >body see-threaded ;
 : seefield ( xt -- )  : seefield ( xt -- )
     dup >body ." 0 " ? ." 0 0 "      dup >body ." 0 " ? ." 0 0 "
     s" Field" .defname cr ;      s" Field" .defname cr ;
   
 : xt-see ( xt -- )  : xt-see ( xt -- ) \ gforth
       \G Decompile the definition represented by @i{xt}.
     cr c-init      cr c-init
     dup >does-code      dup >does-code
     if      if
         seedoes EXIT          seedoes EXIT
     then      then
     dup forthstart u<      dup xtprim?
     if      if
         seecode EXIT          seecode EXIT
     then      then
Line 616  IS discode Line 645  IS discode
         docon: of seecon endof          docon: of seecon endof
         docol: of seecol endof          docol: of seecol endof
         dovar: of seevar endof          dovar: of seevar endof
   [ [IFDEF] douser: ]
         douser: of seeuser endof          douser: of seeuser endof
   [ [THEN] ]
   [ [IFDEF] dodefer: ]
         dodefer: of seedefer endof          dodefer: of seedefer endof
   [ [THEN] ]
   [ [IFDEF] dofield: ]
         dofield: of seefield endof          dofield: of seefield endof
         over >body of seecode endof  [ [THEN] ]
           over       of seecode endof \ direct threaded code words
           over >body of seecode endof \ indirect threaded code words
         2drop abort" unknown word type"          2drop abort" unknown word type"
     ENDCASE ;      ENDCASE ;
   
Line 639  IS discode Line 675  IS discode
     if \ normal or immediate word      if \ normal or immediate word
         swap xt-see (.immediate)          swap xt-see (.immediate)
     else      else
         r@ ['] compile-only-error =          r@ ['] ticking-compile-only-error =
         if \ compile-only word          if \ compile-only word
             swap xt-see (.immediate) ."  compile-only"              swap xt-see (.immediate) ."  compile-only"
         else \ interpret/compile word          else \ interpret/compile word
Line 650  IS discode Line 686  IS discode
     then      then
     rdrop drop ;      rdrop drop ;
   
 : see ( "name" -- ) \ tools  : see ( "<spaces>name" -- ) \ tools
       \G Locate @var{name} using the current search order. Display the
       \G definition of @var{name}. Since this is achieved by decompiling
       \G the definition, the formatting is mechanised and some source
       \G information (comments, interpreted sequences within definitions
       \G etc.) is lost.
     name find-name dup 0=      name find-name dup 0=
     IF      IF
         drop -&13 bounce          drop -&13 throw
     THEN      THEN
     name-see ;      name-see ;
   

Removed from v.1.14  
changed lines
  Added in v.1.43


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