MiniDebug.st
author claus
Fri, 05 Aug 1994 02:55:07 +0200
changeset 92 0c73b48551ac
parent 89 7be0b86ef80f
child 93 e31220cb391f
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1988 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Object subclass:#MiniDebugger
       instanceVariableNames:'tracing stepping traceBlock'
       classVariableNames:   'TheOneAndOnlyDebugger'
       poolDictionaries:''
       category:'System-Support'
!

MiniDebugger comment:'
COPYRIGHT (c) 1988 by Claus Gittinger
              All Rights Reserved
'!

!MiniDebugger class methodsFor: 'documentation'!

copyright
"
 COPYRIGHT (c) 1988 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Attic/MiniDebug.st,v 1.7 1994-06-02 17:19:50 claus Exp $
"
!

documentation
"
    a primitive (non graphical) debugger for use on systems without
    graphics or when the real debugger dies (i.e. an error occurs in
    the graphical debugger).
"
! !

!MiniDebugger class methodsFor: 'instance creation'!

new
    TheOneAndOnlyDebugger printNL.
    TheOneAndOnlyDebugger isNil ifTrue:[
        TheOneAndOnlyDebugger := self basicNew initialize
    ].
    ^ TheOneAndOnlyDebugger
!

singleStep:aBlock
    |aDebugger|

    aDebugger := self new stepping.
    ObjectMemory flushInlineCaches.
    ObjectMemory stepInterruptHandler:aDebugger.
    StepInterruptPending := true.
    InterruptPending := true.
    aBlock value.
    StepInterruptPending := nil.
    ObjectMemory stepInterruptHandler:nil
!

trace:aBlock
    self trace:aBlock with:[:where | where printNewline]
!

trace:aBlock on:aStream
    self trace:aBlock with:[:where | where printString printOn:aStream.
                                     aStream cr]
!

trace:aBlock with:aTraceBlock
    |aDebugger|

    aDebugger := self new tracingWith:aTraceBlock.
    ObjectMemory flushInlineCaches.
    ObjectMemory stepInterruptHandler:aDebugger.
    StepInterruptPending := true.
    InterruptPending := true.
    aBlock value.
    ObjectMemory stepInterruptHandler:nil.
    StepInterruptPending := nil.
    ^ nil
!

enterWithMessage:aString
    |aDebugger|

    StepInterruptPending := nil.
    aString printNewline.
    aDebugger := self new.
    aDebugger enter.
    ^ nil
! !

!MiniDebugger methodsFor: 'initialization'!

initialize
    traceBlock := nil.
    tracing := false.
    stepping := false
! !

!MiniDebugger methodsFor: 'private'!

stepping
    traceBlock := nil.
    tracing := false.
    stepping := true
!

tracingWith:aBlockOrNil
    traceBlock := aBlockOrNil.
    stepping := false.
    tracing := true
!

getContext
    |backtrace|
    backtrace := thisContext.
    (backtrace notNil) ifTrue: [
        "remove Context getContext frame"
        backtrace := backtrace sender.
        "remove Debugger showContext frame"
        backtrace := backtrace sender.
        "remove Debugger commandLoop frame"
        backtrace := backtrace sender.
        "remove Debugger enter frame"
        backtrace := backtrace sender
    ].
    ^ backtrace
!

findContext:aSelector
    |con|

    con := thisContext sender.
    [con notNil] whileTrue:[
        (con isBlockContext not and:[con selector == aSelector]) ifTrue:[
            "got it"
            ^ con
        ].
        con := con sender
    ].
    ^ nil
! !

!MiniDebugger methodsFor: 'interrupt handling'!

stepInterrupt
    |where|

    where := thisContext.        "where is stepInterrupt context"
    where notNil ifTrue:[
        where := where sender    "where is now interrupted methods context"
    ].
    stepping ifTrue:[
        where notNil ifTrue:[
            where fullPrint
        ] ifFalse:[
            'stepInterrupt: no context' errorPrintNewline
        ].
        self enter
    ] ifFalse:[
        where notNil ifTrue:[
            traceBlock notNil ifTrue:[
                traceBlock value:where
            ]
        ] ifFalse:[
            'traceInterrupt: no context' errorPrintNewline
        ].
        ObjectMemory flushInlineCaches.
        StepInterruptPending := true.
        InterruptPending := true
    ]
!

enter
    |cmd stillHere|

    stillHere := true.
    [stillHere] whileTrue:[
        cmd := self commandLoop.

        (cmd == $s) ifTrue: [
            self stepping.
            ObjectMemory flushInlineCaches.
            ObjectMemory stepInterruptHandler:self.
            stillHere := false.
            StepInterruptPending := true.
            InterruptPending := true
        ].
        (cmd == $t) ifTrue: [
            traceBlock := [:where | where fullPrint].
            ObjectMemory flushInlineCaches.
            ObjectMemory stepInterruptHandler:self.
            stillHere := false.
            StepInterruptPending := true.
            InterruptPending := true
        ].
        (cmd == $c) ifTrue: [
            stillHere := false.
            stepping := false.
            tracing := false.
            StepInterruptPending := nil.
            InterruptPending := nil
        ].
        (cmd == $a) ifTrue: [
            "abort"
            stepping := false.
            tracing := false.
            StepInterruptPending := nil.
            InterruptPending := nil.
            self doAbort.
            stillHere := true.
            "failed abort"
        ].
    ].
    ^ nil
! !

!MiniDebugger methodsFor: 'user commands'!

doAbort
    |con sig|

    (sig := Object abortSignal) isHandled ifTrue:[
        sig raise.
        'abort raise failed' errorPrintNewline.
    ].

    "TEMPORARY kludge - find event handler context
     this will be removed, once real debugging is possible
    "
    con := self findContext:#processEvent.
    con isNil ifTrue:[
        con := self findContext:#dispatch.
    ].
    con notNil ifTrue:[
        "got it"
        con return.
        'return failed' errorPrintNewline.
    ].

    'found no context to resume' errorPrintNewline.
!

showProcesses
    |active|

    active := Processor activeProcess.
    'current id=' print. active id print. ' name=' print. active name printNewline.

    Process allInstancesDo:[:p |
        'proc id=' print. p id print. ' name=' print. p name print. ' state=' print.
                          p state printNewline.
    ]
!

commandLoop
    |cmd done valid context|

    done := false.
    [done] whileFalse:[
        valid := false.
        cmd := self getCommand.
        (cmd == $p) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                context fullPrintAll
            ] ifFalse:[
                'no context' errorPrintNewline
            ]
        ].
        (cmd == $P) ifTrue:[
            valid := true.
            self showProcesses.
        ].
        (cmd == $r) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                "remove Debugger stepinterrupt/halt frame"
                context sender receiver printNewline
            ] ifFalse:[
                'no context - dont know receiver' errorPrintNewline
            ]
        ].
        (cmd == $R) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                "remove Debugger stepinterrupt/halt frame"
                context sender receiver storeOn:Stdout
            ] ifFalse:[
                'no context - dont know receiver' errorPrintNewline
            ]
        ].
        (cmd == $i) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                "remove Debugger stepinterrupt/halt frame"
                context sender receiver inspect
            ] ifFalse:[
                'no context - dont know receiver' errorPrintNewline
            ]
        ].
        (cmd == $I) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                "remove Debugger stepinterrupt/halt frame"
                self interpreterLoopWith:(context sender receiver)
            ] ifFalse:[
                'no context - dont know receiver' errorPrintNewline.
                self interpreterLoopWith:nil
            ]
        ].
        context := nil.
        (cmd == $c) ifTrue:[valid := true. done := true].
        (cmd == $s) ifTrue:[valid := true. done := true].
        (cmd == $t) ifTrue:[valid := true. done := true].
        (cmd == $a) ifTrue:[valid := true. done := true].
        (cmd == $T) ifTrue:[valid := true. Processor activeProcess terminate].
        (cmd == $X) ifTrue:[Smalltalk fatalAbort].
        (cmd == $x) ifTrue:[Smalltalk exit].
        valid ifFalse: [
            'valid commands:
   (c)ontinue
   (s)tep
   (t)race
   (p)rintContext
   (r)eceiver
   (R)eceiver
   (i)nspect
   (I)nterpreter
   (a)bort
   (P)rocesses
   (T)terminate process
   (X)exit (+core)
   (x)exit Smalltalk'  errorPrintNewline
        ]
    ].
    ^ cmd
!

getCommand
    |cmd c|
    'MiniDebugger> ' print.
    cmd := Character fromUser.
    c := cmd.
    [ c isEndOfLineCharacter ] whileFalse: [
        c := Character fromUser
    ].
    ^ cmd
!

interpreterLoopWith:anObject
    |line done|
    'read-eval-print loop; exit with empty line' printNewline.
    done := false.
    [done] whileFalse:[
        line := Stdin nextLine.
        (line size == 0) ifTrue:[
            done := true
        ] ifFalse:[
            (Compiler evaluate:line 
                      receiver:anObject
                     notifying:nil) printNewline
        ]
    ]
! !