MiniDebugger.st
author Claus Gittinger <cg@exept.de>
Mon, 15 Dec 1997 11:34:19 +0100
changeset 3126 e37ccb66f1b0
parent 3009 d74b118b1d70
child 3700 95530aec6e0b
permissions -rw-r--r--
onlz ungrab the main Display (remote display could be inoperable)

"
 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-Debugging-Support'
!

!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.
"
!

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).
    Also, if an interrupt occurs within the debuger, this one is called
    for.

    [author:]
        Claus Gittinger
"
! !

!MiniDebugger class methodsFor:'instance creation'!

enter
    ^ self enterWithMessage:'MiniDebugger'
!

enter:aContext
    ^ self enterWithMessage:'MiniDebugger'
!

enter:aContext withMessage:aString
    ^ self enterWithMessage:aString
!

enterWithMessage:aString
    |active|

    StepInterruptPending := nil.

    Object errorSignal handle:[:ex |
	ex return
    ] do:[
	thisContext isRecursive ifTrue:[
	    "/ 'recursive error in debugger ignored' errorPrintCR.
	    ^ self
	].
        aString printCR.
        Processor notNil ifTrue:[
            active := Processor activeProcess.
            'process: id=' print. active id print. ' name=' print. active name printCR.
        ].
    ].
    self new enter.
    ^ nil

    "Modified: 20.5.1996 / 10:28:31 / cg"
!

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

    "Modified: 20.5.1996 / 10:28:35 / cg"
!

singleStep:aBlock
    |aDebugger|

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

trace:aBlock
    self trace:aBlock with:[:where | where printCR]

    "Modified: 20.5.1996 / 10:27:37 / cg"
!

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 stepInterruptHandler:aDebugger.
    ObjectMemory flushInlineCaches.
    StepInterruptPending := 1.
    InterruptPending := 1.
    aBlock value.
    ObjectMemory stepInterruptHandler:nil.
    StepInterruptPending := nil.
    ^ nil
! !

!MiniDebugger methodsFor:'initialization'!

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

!MiniDebugger methodsFor:'interrupt handling'!

enter
    |leaveCmd stillHere|

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

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

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' errorPrintCR
        ].
        self enter
    ] ifFalse:[
        where notNil ifTrue:[
            traceBlock notNil ifTrue:[
                traceBlock value:where
            ]
        ] ifFalse:[
            'traceInterrupt: no context' errorPrintCR
        ].
        ObjectMemory flushInlineCaches.
        StepInterruptPending := 1.
        InterruptPending := 1
    ]

    "Modified: 20.5.1996 / 10:23:11 / cg"
! !

!MiniDebugger methodsFor:'private'!

findContext:aSelector
    |con|

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

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
!

printBacktraceFrom:aContext
    aContext notNil ifTrue:[
	aContext fullPrintAll
    ] ifFalse:[
	'no context' errorPrintCR
    ]
!

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

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

!MiniDebugger methodsFor:'user commands'!

commandLoop
    |cmd done valid context|

    done := false.
    [done] whileFalse:[
        valid := false.
        cmd := self getCommand.
        cmd isNil ifTrue:[   "/ EOF -> continue
            cmd := $c
        ].
        (cmd == $p) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            self printBacktraceFrom:context
        ].
        (cmd == $b) ifTrue:[
            valid := true.
            Smalltalk printStackBacktrace
        ].
        (cmd == $B) ifTrue:[
            valid := true.
            self printAllBacktraces
        ].
        (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 printCR
            ] ifFalse:[
                'no context - dont know receiver' errorPrintCR
            ]
        ].
        (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' errorPrintCR
            ]
        ].
        (cmd == $i) ifTrue:[
            valid := true.
            context isNil ifTrue: [
                context := self getContext
            ].
            context notNil ifTrue:[
                "remove Debugger stepinterrupt/halt frame"
                MiniInspector openOn:(context sender receiver)
            ] ifFalse:[
                'no context - dont know receiver' errorPrintCR
            ]
        ].
        (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' errorPrintCR.
                self interpreterLoopWith:nil
"/          ]
        ].
        context := nil.
	(cmd == $u) ifTrue:[
            stepping := false.
            tracing := false.
	    Processor activeProcess vmTrace:false.
	].

        (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 terminateActive].
        (cmd == $Q) ifTrue:[valid := true. Processor terminateActiveNoSignal].
        (cmd == $U) ifTrue:[MessageTracer unwrapAllMethods].
        (cmd == $X) ifTrue:[Smalltalk fatalAbort].
        (cmd == $x) ifTrue:[OperatingSystem exit].
        valid ifFalse: [
            'valid commands:
   (c)ontinue
   (s)tep
   (t)race (continue with trace)
   (p)rint context chain
   (b)full backtrace
   (B)backtrace of all other processes
   (r)eceiver printString
   (R)eceiver storeString
   (i)nspect (enter inspector on receiver)
   (I)nterpreter (expression evaluator)
   (a)bort (raise abort signal)
   (P)rocess list
   (T)terminate current process
   (Q)uick terminate current process (no unwinds)
   (U)nwrap all traced/breakpointed methods
   (X)exit (+core)
   (x)exit Smalltalk'  errorPrintCR
        ]
    ].
    context := nil.
    ^ cmd

    "Modified: 24.7.1997 / 10:00:43 / cg"
!

doAbort
    |con sig|

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

    "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' errorPrintCR.
    ].

    'found no context to resume' errorPrintCR.

    "Modified: 20.5.1996 / 10:23:00 / cg"
!

getCommand
    |cmd c|

"/    Display notNil ifTrue:[
"/        Display ungrabPointer.
"/        Display ungrabKeyboard.
"/    ].

"/    Screen notNil ifTrue:[
"/        Screen allScreens do:[:aScreen |
"/            aScreen ungrabPointer.
"/            aScreen ungrabKeyboard.
"/        ].
"/    ].

    Display notNil ifTrue:[
        Display ungrabPointer.
        Display ungrabKeyboard.
    ].

    'MiniDebugger> ' print.

    UserInterruptSignal handle:[:ex |
        ex restart
    ] do:[
        cmd := Character fromUser.
        cmd isNil ifTrue:[
            "
             mhmh end-of-file;
             return a 'c' (for continue); hope thats ok.
            "
            cmd := $c
        ].

        "
         ignore to end-of-line
        "
        c := cmd.
        [c isNil or:[c isEndOfLineCharacter]] whileFalse: [
            c := Character fromUser.
        ].
    ].
    ^ cmd

    "Modified: 11.8.1997 / 16:04:39 / cg"
!

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

    "Modified: 20.5.1996 / 10:27:29 / cg"
!

printAllBacktraces
    Process allInstancesDo:[:p |
	(p ~~ Processor activeProcess
	and:[p isDead not]) ifTrue:[
	    '---------------------------------------------------------' printCR.
	    '  proc id=' print. p id print. 
	    ' name=''' print. p name print.
	    ''' createdBy: ' print. p creatorId print.
	    ' state=' print.  p state print. 
	    ' prio=' print. p priority printCR.
	    '' printCR. '' printCR.

	    self printBacktraceFrom:(p suspendedContext)
	]
    ]
!

showProcesses
    |active|

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

    Process allInstancesDo:[:p |
        'proc id=' print. p id print. 
	' name=''' print. p name print. 
	''' createdBy: ' print. p creatorId print.
	' state=' print.
        p state print. 
	' prio=' print. p priority printCR.
    ]

    "Modified: 20.5.1996 / 10:28:25 / cg"
! !

!MiniDebugger class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.35 1997-12-15 10:34:19 cg Exp $'
! !