Annotation of gforth/see.fs, revision 1.47

1.1       anton       1: \ SEE.FS       highend SEE for ANSforth                16may93jaw
                      2: 
1.30      anton       3: \ Copyright (C) 1995,2000 Free Software Foundation, Inc.
1.9       anton       4: 
                      5: \ This file is part of Gforth.
                      6: 
                      7: \ Gforth is free software; you can redistribute it and/or
                      8: \ modify it under the terms of the GNU General Public License
                      9: \ as published by the Free Software Foundation; either version 2
                     10: \ of the License, or (at your option) any later version.
                     11: 
                     12: \ This program is distributed in the hope that it will be useful,
                     13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
                     14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
                     15: \ GNU General Public License for more details.
                     16: 
                     17: \ You should have received a copy of the GNU General Public License
                     18: \ along with this program; if not, write to the Free Software
1.31      anton      19: \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
1.9       anton      20: 
                     21: 
1.1       anton      22: \ May be cross-compiled
                     23: 
                     24: \ I'm sorry. This is really not "forthy" enough.
                     25: 
                     26: \ Ideas:        Level should be a stack
                     27: 
1.18      jwilke     28: require look.fs
1.10      anton      29: require termsize.fs
1.18      jwilke     30: require wordinfo.fs
1.32      anton      31: [IFUNDEF] .name
                     32: : id. ( nt -- ) \ gforth
                     33:     \G Print the name of the word represented by @var{nt}.
                     34:     \ this name comes from fig-Forth
                     35:     name>string type space ;
                     36: 
                     37: ' id. alias .id ( nt -- )
                     38: \G F83 name for @code{id.}.
                     39: 
                     40: ' id. alias .name ( nt -- )
                     41: \G Gforth <=0.5.0 name for @code{id.}.
                     42: 
                     43: [THEN]
1.10      anton      44: 
1.1       anton      45: decimal
                     46: 
                     47: \ Screen format words                                   16may93jaw
                     48: 
                     49: VARIABLE C-Output   1 C-Output  !
                     50: VARIABLE C-Formated 1 C-Formated !
                     51: VARIABLE C-Highlight 0 C-Highlight !
                     52: VARIABLE C-Clearline 0 C-Clearline !
                     53: 
                     54: VARIABLE XPos
                     55: VARIABLE YPos
                     56: VARIABLE Level
                     57: 
                     58: : Format        C-Formated @ C-Output @ and
                     59:                 IF dup spaces XPos +! ELSE drop THEN ;
                     60: 
                     61: : level+        7 Level +!
                     62:                 Level @ XPos @ -
                     63:                 dup 0> IF Format ELSE drop THEN ;
                     64: 
                     65: : level-        -7 Level +! ;
                     66: 
                     67: VARIABLE nlflag
1.15      pazsan     68: VARIABLE uppercase     \ structure words are in uppercase
1.1       anton      69: 
                     70: DEFER nlcount ' noop IS nlcount
                     71: 
                     72: : nl            nlflag on ;
                     73: : (nl)          nlcount
1.18      jwilke     74:                 XPos @ Level @ = IF EXIT THEN \ ?Exit
1.1       anton      75:                 C-Formated @ IF
                     76:                 C-Output @
1.10      anton      77:                 IF C-Clearline @ IF cols XPos @ - spaces
1.1       anton      78:                                  ELSE cr THEN
                     79:                 1 YPos +! 0 XPos !
                     80:                 Level @ spaces
                     81:                 THEN Level @ XPos ! THEN ;
                     82: 
                     83: : warp?         ( len -- len )
                     84:                 nlflag @ IF (nl) nlflag off THEN
1.10      anton      85:                 XPos @ over + cols u>= IF (nl) THEN ;
1.1       anton      86: 
1.22      crook      87: : c-to-upper ( c1 -- c2 ) \ gforth
                     88:     \ nac05feb1999 there is a primitive, toupper, with this function
                     89:     dup [char] a >= over [char] z <= and if  bl -  then ;
1.15      pazsan     90: 
1.1       anton      91: : ctype         ( adr len -- )
1.15      pazsan     92:                 warp? dup XPos +! C-Output @ 
                     93:                IF uppercase @ IF bounds ?DO i c@ c-to-upper emit LOOP
                     94:                                  uppercase off ELSE type THEN
                     95:                ELSE 2drop THEN ;
1.1       anton      96: 
                     97: : cemit         1 warp?
                     98:                 over bl = Level @ XPos @ = and
                     99:                 IF 2drop ELSE XPos +! C-Output @ IF emit ELSE drop THEN
                    100:                 THEN ;
                    101: 
1.34      anton     102: DEFER .string ( c-addr u n -- )
1.1       anton     103: 
                    104: [IFDEF] Green
                    105: VARIABLE Colors Colors on
                    106: 
                    107: : (.string)     ( c-addr u n -- )
                    108:                 over warp? drop
                    109:                 Colors @
                    110:                 IF C-Highlight @ ?dup
                    111:                    IF   CT@ swap CT@ or
                    112:                    ELSE CT@
                    113:                    THEN
                    114:                 attr! ELSE drop THEN
                    115:                 ctype  ct @ attr! ;
                    116: [ELSE]
                    117: : (.string)     ( c-addr u n -- )
                    118:                 drop ctype ;
                    119: [THEN]
                    120: 
                    121: ' (.string) IS .string
                    122: 
1.45      anton     123: : c-\type ( c-addr u -- )
                    124:     \ type string in \-escaped form
                    125:     begin
                    126:        dup while
                    127:            2dup newline string-prefix? if
                    128:                '\ cemit 'n cemit
                    129:                newline nip /string
                    130:            else
                    131:                over c@
                    132:                dup '" = over '\ = or if
                    133:                    '\ cemit cemit
                    134:                else
                    135:                    dup bl 127 within if
                    136:                        cemit
                    137:                    else
                    138:                        base @ >r try
                    139:                            8 base ! 0 <<# # # # '\ hold #> ctype #>> 0
                    140:                        recover
                    141:                        endtry
                    142:                        r> base ! throw
                    143:                    endif
                    144:                endif
                    145:                1 /string
                    146:            endif
                    147:     repeat
                    148:     2drop ;
1.1       anton     149: 
1.15      pazsan    150: : .struc        
                    151:        uppercase on Str# .string ;
1.1       anton     152: 
1.17      jwilke    153: \ CODES (Branchtypes)                                    15may93jaw
1.1       anton     154: 
                    155: 21 CONSTANT RepeatCode
                    156: 22 CONSTANT AgainCode
                    157: 23 CONSTANT UntilCode
                    158: \ 09 CONSTANT WhileCode
                    159: 10 CONSTANT ElseCode
                    160: 11 CONSTANT AheadCode
                    161: 13 CONSTANT WhileCode2
                    162: 14 CONSTANT Disable
1.17      jwilke    163: 15 CONSTANT LeaveCode
                    164: 
1.1       anton     165: 
                    166: \ FORMAT WORDS                                          13jun93jaw
                    167: 
                    168: VARIABLE C-Stop
                    169: VARIABLE Branches
                    170: 
1.17      jwilke    171: VARIABLE BranchPointer \ point to the end of branch table
1.1       anton     172: VARIABLE SearchPointer
1.17      jwilke    173: 
                    174: \ The branchtable consists of three entrys:
                    175: \ address of branch , branch destination , branch type
                    176: 
1.25      pazsan    177: CREATE BranchTable 128 cells allot
1.1       anton     178: here 3 cells -
                    179: ACONSTANT MaxTable
                    180: 
                    181: : FirstBranch BranchTable cell+ SearchPointer ! ;
                    182: 
1.17      jwilke    183: : (BranchAddr?) ( a-addr1 -- a-addr2 true | false )
                    184: \ searches a branch with destination a-addr1
                    185: \ a-addr1: branch destination
                    186: \ a-addr2: pointer in branch table
1.1       anton     187:         SearchPointer @
                    188:         BEGIN   dup BranchPointer @ u<
                    189:         WHILE
                    190:                 dup @ 2 pick <>
                    191:         WHILE   3 cells +
                    192:         REPEAT
                    193:         nip dup  3 cells + SearchPointer ! true
                    194:         ELSE
                    195:         2drop false
                    196:         THEN ;
                    197: 
                    198: : BranchAddr?
                    199:         FirstBranch (BranchAddr?) ;
                    200: 
                    201: ' (BranchAddr?) ALIAS MoreBranchAddr?
                    202: 
                    203: : CheckEnd ( a-addr -- true | false )
                    204:         BranchTable cell+
                    205:         BEGIN   dup BranchPointer @ u<
                    206:         WHILE
                    207:                 dup @ 2 pick u<=
                    208:         WHILE   3 cells +
                    209:         REPEAT
                    210:         2drop false
                    211:         ELSE
                    212:         2drop true
                    213:         THEN ;
                    214: 
1.17      jwilke    215: : MyBranch      ( a-addr -- a-addr a-addr2 )
                    216: \ finds branch table entry for branch at a-addr
1.45      anton     217:                 dup @
1.17      jwilke    218:                 BranchAddr?
                    219:                 BEGIN
                    220:                 WHILE 1 cells - @
                    221:                       over <>
1.45      anton     222:                 WHILE dup @
1.17      jwilke    223:                       MoreBranchAddr?
                    224:                 REPEAT
                    225:                 SearchPointer @ 3 cells -
                    226:                 ELSE    true ABORT" SEE: Table failure"
                    227:                 THEN ;
                    228: 
1.1       anton     229: \
                    230: \                 addrw               addrt
                    231: \       BEGIN ... WHILE ... AGAIN ... THEN
                    232: \         ^         !        !          ^
                    233: \         ----------+--------+          !
                    234: \                   !                   !
                    235: \                   +-------------------+
                    236: \
                    237: \
                    238: 
                    239: : CheckWhile ( a-addrw a-addrt -- true | false )
                    240:         BranchTable
                    241:         BEGIN   dup BranchPointer @ u<
                    242:         WHILE   dup @ 3 pick u>
                    243:                 over @ 3 pick u< and
                    244:                 IF dup cell+ @ 3 pick u<
                    245:                         IF 2drop drop true EXIT THEN
                    246:                 THEN
                    247:                 3 cells +
                    248:         REPEAT
                    249:         2drop drop false ;
                    250: 
                    251: : ,Branch ( a-addr -- )
                    252:         BranchPointer @ dup MaxTable u> ABORT" SEE: Table overflow"
                    253:         !
                    254:         1 cells BranchPointer +! ;
                    255: 
                    256: : Type!   ( u -- )
                    257:         BranchPointer @ 1 cells - ! ;
                    258: 
                    259: : Branch! ( a-addr rel -- a-addr )
1.45      anton     260:     over ,Branch ,Branch 0 ,Branch ;
                    261: \        over + over ,Branch ,Branch 0 ,Branch ;
1.1       anton     262: 
                    263: \ DEFER CheckUntil
                    264: VARIABLE NoOutput
                    265: VARIABLE C-Pass
                    266: 
                    267: 0 CONSTANT ScanMode
                    268: 1 CONSTANT DisplayMode
                    269: 2 CONSTANT DebugMode
                    270: 
                    271: : Scan? ( -- flag ) C-Pass @ 0= ;
                    272: : Display? ( -- flag ) C-Pass @ 1 = ;
                    273: : Debug? ( -- flag ) C-Pass @ 2 = ;
                    274: 
1.45      anton     275: : back? ( addr target -- addr flag )
                    276:     over u< ;
1.1       anton     277: 
1.47    ! anton     278: : .word ( addr x -- addr )
        !           279:     \ print x as a word if possible
        !           280:     dup look 0= IF
        !           281:        drop dup threaded>name 0= if
        !           282:            2drop dup 1 cells - @ dup body> look
        !           283:            IF
        !           284:                nip dup ." <" name>string rot wordinfo .string ." > "
        !           285:            ELSE
        !           286:                drop ." <" 0 .r ." > "
        !           287:            THEN
        !           288:            EXIT
        !           289:        then
        !           290:     THEN
        !           291:     nip dup cell+ @ immediate-mask and
        !           292:     IF
        !           293:        bl cemit  ." POSTPONE "
        !           294:     THEN
        !           295:     dup name>string rot wordinfo .string
        !           296:     ;
1.35      pazsan    297: 
1.44      anton     298: : c-call ( addr1 -- addr2 )
                    299:     Display? IF
                    300:        dup @ body> .word bl cemit
                    301:     THEN
                    302:     cell+ ;
                    303: 
                    304: : c-callxt ( addr1 -- addr2 )
                    305:     Display? IF
                    306:        dup @ .word bl cemit
                    307:     THEN
                    308:     cell+ ;
                    309: 
                    310: \ here docon: , docol: , dovar: , douser: , dodefer: , dofield: ,
                    311: \ here over - 2constant doers
                    312: 
                    313: : c-lit ( addr1 -- addr2 )
                    314:     Display? IF
                    315:        dup @ dup body> dup cfaligned over = swap in-dictionary? and if
                    316:            ( addr1 addr1@ )
                    317:            dup body> @ dovar: = if
                    318:                drop c-call EXIT
                    319:            endif
                    320:        endif
                    321:        \ !! test for cfa here, and print "['] ..."
                    322:        dup abs 0 <# #S rot sign #> 0 .string bl cemit
                    323:     endif
                    324:     cell+ ;
                    325: 
                    326: : c-lit+ ( addr1 -- addr2 )
                    327:     Display? if
                    328:        dup @ dup abs 0 <# #S rot sign #> 0 .string bl cemit
                    329:        s" + " 0 .string
                    330:     endif
                    331:     cell+ ;
1.35      pazsan    332: 
1.18      jwilke    333: : .name-without ( addr -- addr )
1.45      anton     334: \ prints a name without a() e.g. a(+LOOP) or (s")
1.47    ! anton     335:     dup 1 cells - @ threaded>name IF
1.45      anton     336:        name>string over c@ 'a = IF
                    337:            1 /string
                    338:        THEN
                    339:         over c@ '( = IF
                    340:            1 /string
                    341:        THEN
                    342:        2dup + 1- c@ ') = IF 1- THEN .struc ELSE drop 
                    343:     THEN ;
1.1       anton     344: 
1.45      anton     345: [ifdef] (s")
1.1       anton     346: : c-c"
1.18      jwilke    347:        Display? IF nl .name-without THEN
1.1       anton     348:         count 2dup + aligned -rot
                    349:         Display?
1.18      jwilke    350:         IF      bl cemit 0 .string
1.1       anton     351:                 [char] " cemit bl cemit
                    352:         ELSE    2drop
                    353:         THEN ;
1.45      anton     354: [endif]
1.1       anton     355: 
1.45      anton     356: : c-string? ( addr1 -- addr2 f )
                    357:     \ f is true if a string was found and decompiled.
                    358:     \ if f is false, addr2=addr1
                    359:     \ recognizes the following patterns:
                    360:     \ c":     ahead X: len string then lit X
                    361:     \ s\":    ahead X: string then lit X lit len
                    362:     \ .\":    ahead X: string then lit X lit len type
                    363:     \ !! not recognized anywhere:
                    364:     \ abort": if ahead X: len string then lit X c(abort") then
                    365:     dup @ back? if false exit endif
                    366:     dup @ >r
                    367:     r@ @ decompile-prim ['] lit xt>threaded <> if rdrop false exit endif
                    368:     r@ cell+ @ over cell+ <> if rdrop false exit endif
                    369:     \ we have at least C"
                    370:     r@ 2 cells + @ decompile-prim ['] lit xt>threaded = if
                    371:        r@ 3 cells + @ over cell+ + aligned r@ = if
                    372:            \ we have at least s"
                    373:            r@ 4 cells + @ decompile-prim ['] lit-perform xt>threaded =
                    374:            r@ 5 cells + @ ['] type >body = and if
                    375:                6 s\" .\\\" "
                    376:            else
                    377:                4 s\" s\\\" "
                    378:            endif
                    379:            \ !! make newline if string too long?
                    380:            display? if
                    381:                0 .string r@ cell+ @ r@ 3 cells + @ c-\type '" cemit bl cemit
                    382:            else
                    383:                2drop
                    384:            endif
                    385:            nip cells r> + true exit
                    386:        endif
                    387:     endif
                    388:     \ !! check if count matches space?
                    389:     display? if
                    390:        s\" c\" " 0 .string r@ cell+ @ count 0 .string '" cemit bl cemit
                    391:     endif
                    392:     drop r> 2 cells + true ;
1.1       anton     393: 
1.17      jwilke    394: : Forward? ( a-addr true | false -- a-addr true | false )
1.45      anton     395:     \ a-addr is pointer into branch table
                    396:     \ returns true when jump is a forward jump
                    397:     IF
                    398:        dup dup @ swap 1 cells - @ u> IF
                    399:            true
                    400:        ELSE
                    401:            drop false
                    402:        THEN
                    403:        \ only if forward jump
                    404:     ELSE
                    405:        false
                    406:     THEN ;
1.1       anton     407: 
1.17      jwilke    408: : RepeatCheck ( a-addr1 a-addr2 true | false -- false )
1.1       anton     409:         IF  BEGIN  2dup
1.45      anton     410:                    1 cells - @ swap @
1.1       anton     411:                    u<=
                    412:             WHILE  drop dup cell+
                    413:                    MoreBranchAddr? 0=
                    414:             UNTIL  false
                    415:             ELSE   true
                    416:             THEN
                    417:         ELSE false
                    418:         THEN ;
                    419: 
1.45      anton     420: : c-branch ( addr1 -- addr2 )
                    421:     c-string? ?exit
1.1       anton     422:         Scan?
                    423:         IF      dup @ Branch!
                    424:                 dup @ back?
                    425:                 IF                      \ might be: AGAIN, REPEAT
                    426:                         dup cell+ BranchAddr? Forward?
                    427:                         RepeatCheck
                    428:                         IF      RepeatCode Type!
                    429:                                 cell+ Disable swap !
                    430:                         ELSE    AgainCode Type!
                    431:                         THEN
                    432:                 ELSE    dup cell+ BranchAddr? Forward?
                    433:                         IF      ElseCode Type! drop
                    434:                         ELSE    AheadCode Type!
                    435:                         THEN
                    436:                 THEN
                    437:         THEN
                    438:         Display?
                    439:         IF
                    440:                 dup @ back?
                    441:                 IF                      \ might be: AGAIN, REPEAT
                    442:                         level- nl
                    443:                         dup cell+ BranchAddr? Forward?
                    444:                         RepeatCheck
                    445:                         IF      drop S" REPEAT " .struc nl
                    446:                         ELSE    S" AGAIN " .struc nl
                    447:                         THEN
1.17      jwilke    448:                 ELSE    MyBranch cell+ @ LeaveCode =
                    449:                        IF      S" LEAVE " .struc
                    450:                        ELSE
                    451:                                dup cell+ BranchAddr? Forward?
                    452:                                        IF      dup cell+ @ WhileCode2 =
                    453:                                                IF nl S" ELSE" .struc level+
                    454:                                        ELSE level- nl S" ELSE" .struc level+ THEN
                    455:                                        cell+ Disable swap !
                    456:                                ELSE    S" AHEAD" .struc level+
                    457:                                THEN
                    458:                        THEN
1.1       anton     459:                 THEN
                    460:         THEN
                    461:         Debug?
                    462:         IF      dup @ +
                    463:         ELSE    cell+
                    464:         THEN ;
                    465: 
                    466: : DebugBranch
                    467:         Debug?
                    468:         IF      dup @ over + swap THEN ; \ return 2 different addresses
                    469: 
                    470: : c-?branch
                    471:         Scan?
                    472:         IF      dup @ Branch!
                    473:                 dup @ Back?
                    474:                 IF      UntilCode Type! THEN
                    475:         THEN
                    476:         Display?
                    477:         IF      dup @ Back?
                    478:                 IF      level- nl S" UNTIL " .struc nl
                    479:                 ELSE    dup    dup @ over +
                    480:                         CheckWhile
                    481:                         IF      MyBranch
                    482:                                 cell+ dup @ 0=
                    483:                                          IF WhileCode2 swap !
                    484:                                          ELSE drop THEN
                    485:                                 level- nl
1.8       pazsan    486:                                 S" WHILE " .struc
1.1       anton     487:                                 level+
1.17      jwilke    488:                         ELSE    MyBranch cell+ @ LeaveCode =
                    489:                                IF   s" 0= ?LEAVE " .struc
                    490:                                ELSE nl S" IF " .struc level+
                    491:                                THEN
1.1       anton     492:                         THEN
                    493:                 THEN
                    494:         THEN
                    495:         DebugBranch
                    496:         cell+ ;
                    497: 
                    498: : c-for
                    499:         Display? IF nl S" FOR" .struc level+ THEN ;
                    500: 
                    501: : c-loop
1.15      pazsan    502:         Display? IF level- nl .name-without bl cemit nl THEN
1.17      jwilke    503:         DebugBranch cell+ 
                    504:        Scan? 
                    505:        IF      dup BranchAddr? 
                    506:                BEGIN   WHILE cell+ LeaveCode swap !
                    507:                        dup MoreBranchAddr?
                    508:                REPEAT
                    509:        THEN
                    510:        cell+ ;
1.1       anton     511: 
1.15      pazsan    512: : c-do
                    513:         Display? IF nl .name-without level+ THEN ;
1.1       anton     514: 
1.45      anton     515: : c-?do ( addr1 -- addr2 )
                    516:     Display? IF
                    517:        nl .name-without level+
                    518:     THEN
                    519:     DebugBranch cell+ ;
1.8       pazsan    520: 
1.1       anton     521: : c-exit  dup 1 cells -
                    522:         CheckEnd
                    523:         IF      Display? IF nlflag off S" ;" Com# .string THEN
                    524:                 C-Stop on
                    525:         ELSE    Display? IF S" EXIT " .struc THEN
                    526:         THEN
                    527:         Debug? IF drop THEN ;
                    528: 
                    529: : c-abort"
                    530:         count 2dup + aligned -rot
                    531:         Display?
                    532:         IF      S" ABORT" .struc
                    533:                 [char] " cemit bl cemit 0 .string
                    534:                 [char] " cemit bl cemit
                    535:         ELSE    2drop
                    536:         THEN ;
                    537: 
1.23      jwilke    538: [IFDEF] (does>)
                    539: : c-does>               \ end of create part
                    540:         Display? IF S" DOES> " Com# .string THEN
                    541:        maxaligned /does-handler + ;
                    542: [THEN]
                    543: 
                    544: [IFDEF] (compile)
                    545: : c-(compile)
                    546:     Display?
                    547:     IF
                    548:        s" POSTPONE " Com# .string
                    549:        dup @ look 0= ABORT" SEE: No valid XT"
                    550:        name>string 0 .string bl cemit
                    551:     THEN
                    552:     cell+ ;
                    553: [THEN]
1.1       anton     554: 
                    555: CREATE C-Table
1.18      jwilke    556:                ' lit A,            ' c-lit A,
1.44      anton     557:                ' does-exec A,      ' c-callxt A,
                    558:                ' lit@ A,           ' c-call A,
1.37      pazsan    559: [IFDEF] call   ' call A,           ' c-call A, [THEN]
1.44      anton     560: \              ' useraddr A,       ....
                    561:                ' lit-perform A,    ' c-call A,
                    562:                ' lit+ A,           ' c-lit+ A,
1.42      anton     563: [IFDEF] (s")   ' (s") A,           ' c-c" A, [THEN]
                    564: [IFDEF] (.")   ' (.") A,           ' c-c" A, [THEN]
                    565: [IFDEF] "lit    ' "lit A,           ' c-c" A, [THEN]
1.18      jwilke    566: [IFDEF] (c")   ' (c") A,           ' c-c" A, [THEN]
                    567:                ' (do) A,           ' c-do A,
1.46      pazsan    568: [IFDEF] (+do)  ' (+do) A,          ' c-?do A, [THEN]
                    569: [IFDEF] (u+do) ' (u+do) A,         ' c-?do A, [THEN]
                    570: [IFDEF] (-do)  ' (-do) A,          ' c-?do A, [THEN]
                    571: [IFDEF] (u-do) ' (u-do) A,         ' c-?do A, [THEN]
                    572:                ' (?do) A,          ' c-?do A,
1.18      jwilke    573:                ' (for) A,          ' c-for A,
1.46      pazsan    574:                ' ?branch A,        ' c-?branch A,
                    575:                ' branch A,         ' c-branch A,
                    576:                ' (loop) A,         ' c-loop A,
                    577:                ' (+loop) A,        ' c-loop A,
                    578: [IFDEF] (s+loop) ' (s+loop) A,      ' c-loop A, [THEN]
                    579: [IFDEF] (-loop) ' (-loop) A,        ' c-loop A, [THEN]
                    580:                ' (next) A,         ' c-loop A,
1.18      jwilke    581:                ' ;s A,             ' c-exit A,
1.42      anton     582: [IFDEF] (abort") ' (abort") A,      ' c-abort" A, [THEN]
1.23      jwilke    583: \ only defined if compiler is loaded
                    584: [IFDEF] (compile) ' (compile) A,      ' c-(compile) A, [THEN]
                    585: [IFDEF] (does>) ' (does>) A,        ' c-does> A, [THEN]
1.18      jwilke    586:                0 ,             here 0 ,
1.15      pazsan    587: 
                    588: avariable c-extender
                    589: c-extender !
1.1       anton     590: 
                    591: \ DOTABLE                                               15may93jaw
                    592: 
1.44      anton     593: : DoTable ( ca/cfa -- flag )
                    594:     decompile-prim C-Table BEGIN ( cfa table-entry )
                    595:        dup @ dup 0=  IF
                    596:            drop cell+ @ dup IF ( next table!)
                    597:                dup @
                    598:            ELSE ( end!)
                    599:                2drop false EXIT
                    600:            THEN 
                    601:        THEN
                    602:        \ jump over to extender, if any 26jan97jaw
                    603:        xt>threaded 2 pick <>
                    604:     WHILE
                    605:            2 cells +
                    606:     REPEAT
                    607:     nip cell+ perform
                    608:     true
                    609: ;
1.1       anton     610: 
                    611: : BranchTo? ( a-addr -- a-addr )
1.17      jwilke    612:         Display?  IF    dup BranchAddr?
1.15      pazsan    613:                         IF
                    614:                                BEGIN cell+ @ dup 20 u>
1.1       anton     615:                                 IF drop nl S" BEGIN " .struc level+
                    616:                                 ELSE
1.17      jwilke    617:                                   dup Disable <> over LeaveCode <> and
1.1       anton     618:                                   IF   WhileCode2 =
                    619:                                        IF nl S" THEN " .struc nl ELSE
                    620:                                        level- nl S" THEN " .struc nl THEN
                    621:                                   ELSE drop THEN
                    622:                                 THEN
                    623:                                   dup MoreBranchAddr? 0=
                    624:                            UNTIL
                    625:                         THEN
                    626:                   THEN ;
                    627: 
                    628: : analyse ( a-addr1 -- a-addr2 )
1.34      anton     629:     Branches @ IF BranchTo? THEN
                    630:     dup cell+ swap @
                    631:     dup >r DoTable r> swap IF drop EXIT THEN
                    632:     Display?
                    633:     IF
1.35      pazsan    634:        .word bl cemit
1.34      anton     635:     ELSE
                    636:        drop
                    637:     THEN ;
1.1       anton     638: 
                    639: : c-init
                    640:         0 YPos ! 0 XPos !
                    641:         0 Level ! nlflag off
                    642:         BranchTable BranchPointer !
                    643:         c-stop off
                    644:         Branches on ;
                    645: 
                    646: : makepass ( a-addr -- )
1.14      anton     647:     c-stop off
                    648:     BEGIN
                    649:        analyse
                    650:        c-stop @
                    651:     UNTIL drop ;
                    652: 
                    653: Defer xt-see-xt ( xt -- )
                    654: \ this one is just a forward declaration for indirect recursion
                    655: 
                    656: : .defname ( xt c-addr u -- )
                    657:     rot look
                    658:     if ( c-addr u nfa )
                    659:        -rot type space .name
                    660:     else
                    661:        drop ." noname " type
                    662:     then
                    663:     space ;
                    664: 
1.28      anton     665: Defer discode ( addr u -- ) \ gforth
                    666: \G hook for the disassembler: disassemble code at addr of length u
1.27      anton     667: ' dump IS discode
                    668: 
                    669: : next-head ( addr1 -- addr2 ) \ gforth
                    670:     \G find the next header starting after addr1, up to here (unreliable).
                    671:     here swap u+do
1.43      anton     672:        i head? -2 and if
1.27      anton     673:            i unloop exit
                    674:        then
                    675:     cell +loop
                    676:     here ;
                    677: 
                    678: : umin ( u1 u2 -- u )
                    679:     2dup u>
                    680:     if
                    681:        swap
                    682:     then
                    683:     drop ;
                    684:        
1.28      anton     685: : next-prim ( addr1 -- addr2 ) \ gforth
                    686:     \G find the next primitive after addr1 (unreliable)
1.27      anton     687:     1+ >r -1 primstart
                    688:     begin ( umin head R: boundary )
                    689:        @ dup
                    690:     while
1.28      anton     691:        tuck name>int >code-address ( head1 umin ca R: boundary )
1.27      anton     692:        r@ - umin
                    693:        swap
                    694:     repeat
1.28      anton     695:     drop dup r@ negate u>=
                    696:     \ "umin+boundary within [0,boundary)" = "umin within [-boundary,0)"
                    697:     if ( umin R: boundary ) \ no primitive found behind -> use a default length
                    698:        drop 31
                    699:     then
                    700:     r> + ;
1.14      anton     701: 
                    702: : seecode ( xt -- )
                    703:     dup s" Code" .defname
1.39      anton     704:     >code-address
1.27      anton     705:     dup in-dictionary? \ user-defined code word?
                    706:     if
                    707:        dup next-head
                    708:     else
                    709:        dup next-prim
                    710:     then
                    711:     over - discode
                    712:     ." end-code" cr ;
1.14      anton     713: : seevar ( xt -- )
                    714:     s" Variable" .defname cr ;
                    715: : seeuser ( xt -- )
                    716:     s" User" .defname cr ;
                    717: : seecon ( xt -- )
                    718:     dup >body ?
                    719:     s" Constant" .defname cr ;
                    720: : seevalue ( xt -- )
                    721:     dup >body ?
                    722:     s" Value" .defname cr ;
                    723: : seedefer ( xt -- )
                    724:     dup >body @ xt-see-xt cr
                    725:     dup s" Defer" .defname cr
1.26      anton     726:     >name ?dup-if
                    727:        ." IS " .name cr
1.14      anton     728:     else
1.26      anton     729:        ." lastxt >body !"
1.14      anton     730:     then ;
                    731: : see-threaded ( addr -- )
                    732:     C-Pass @ DebugMode = IF
                    733:        ScanMode c-pass !
                    734:        EXIT
1.10      anton     735:     THEN
                    736:     ScanMode c-pass ! dup makepass
                    737:     DisplayMode c-pass ! makepass ;
1.14      anton     738: : seedoes ( xt -- )
                    739:     dup s" create" .defname cr
                    740:     S" DOES> " Com# .string XPos @ Level !
                    741:     >does-code see-threaded ;
                    742: : seecol ( xt -- )
1.15      pazsan    743:     dup s" :" .defname nl
1.14      anton     744:     2 Level !
                    745:     >body see-threaded ;
                    746: : seefield ( xt -- )
                    747:     dup >body ." 0 " ? ." 0 0 "
                    748:     s" Field" .defname cr ;
                    749: 
1.29      anton     750: : xt-see ( xt -- ) \ gforth
                    751:     \G Decompile the definition represented by @i{xt}.
1.14      anton     752:     cr c-init
                    753:     dup >does-code
                    754:     if
                    755:        seedoes EXIT
                    756:     then
1.18      jwilke    757:     dup xtprim?
1.14      anton     758:     if
                    759:        seecode EXIT
                    760:     then
                    761:     dup >code-address
                    762:     CASE
                    763:        docon: of seecon endof
                    764:        docol: of seecol endof
                    765:        dovar: of seevar endof
1.18      jwilke    766: [ [IFDEF] douser: ]
1.14      anton     767:        douser: of seeuser endof
1.18      jwilke    768: [ [THEN] ]
                    769: [ [IFDEF] dodefer: ]
1.14      anton     770:        dodefer: of seedefer endof
1.18      jwilke    771: [ [THEN] ]
                    772: [ [IFDEF] dofield: ]
1.14      anton     773:        dofield: of seefield endof
1.18      jwilke    774: [ [THEN] ]
1.27      anton     775:        over       of seecode endof \ direct threaded code words
                    776:        over >body of seecode endof \ indirect threaded code words
1.14      anton     777:        2drop abort" unknown word type"
                    778:     ENDCASE ;
                    779: 
                    780: : (xt-see-xt) ( xt -- )
                    781:     xt-see cr ." lastxt" ;
                    782: ' (xt-see-xt) is xt-see-xt
                    783: 
                    784: : (.immediate) ( xt -- )
                    785:     ['] execute = if
                    786:        ."  immediate"
                    787:     then ;
                    788: 
                    789: : name-see ( nfa -- )
                    790:     dup name>int >r
                    791:     dup name>comp 
                    792:     over r@ =
                    793:     if \ normal or immediate word
                    794:        swap xt-see (.immediate)
                    795:     else
1.40      anton     796:        r@ ['] ticking-compile-only-error =
1.14      anton     797:        if \ compile-only word
                    798:            swap xt-see (.immediate) ."  compile-only"
                    799:        else \ interpret/compile word
                    800:            r@ xt-see-xt cr
                    801:            swap xt-see-xt cr
                    802:            ." interpret/compile " over .name (.immediate)
                    803:        then
                    804:     then
                    805:     rdrop drop ;
1.3       pazsan    806: 
1.21      crook     807: : see ( "<spaces>name" -- ) \ tools
                    808:     \G Locate @var{name} using the current search order. Display the
                    809:     \G definition of @var{name}. Since this is achieved by decompiling
                    810:     \G the definition, the formatting is mechanised and some source
                    811:     \G information (comments, interpreted sequences within definitions
                    812:     \G etc.) is lost.
1.13      anton     813:     name find-name dup 0=
                    814:     IF
1.24      anton     815:        drop -&13 throw
1.13      anton     816:     THEN
1.14      anton     817:     name-see ;
1.1       anton     818: 
                    819: 

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