MiniDebugger.st
author Claus Gittinger <cg@exept.de>
Mon, 07 Jul 2003 12:07:26 +0200
changeset 7476 2e646cca131e
parent 7093 60bad14d38fc
child 7477 b190b8548cef
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.
"

"{ Package: 'stx:libbasic' }"

Object subclass:#MiniDebugger
	instanceVariableNames:'tracing stepping traceBlock command commandArg commandCount
		enteringContext dot nesting'
	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:aContext withMessage:aString mayProceed:mayProceed
    "enter a miniDebugger"

    |active con|

    StepInterruptPending := nil.

    Error 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.

            'context: ' print. aContext printString printCR.
            (con := aContext) notNil ifTrue:[
                con := con sender.
                ' ......: ' print. con printString printCR.
                [con notNil] whileTrue:[
                    con := con sender.
                    ' ......: ' print. con printString printCR.
                ]
            ]
        ].
    ].

    OperatingSystem hasConsole ifFalse:[
        Error handle:[:ex |
            ex return
        ] do:[
            self warn:('Unexpected error:\' , aString , '\\No MiniDebugger functionality available') withCRs .
        ].

        Error handle:[:ex |
            'cannot raise AbortSignal - exiting ...' errorPrintCR.
            Smalltalk exit.
        ] do:[
            AbortSignal raise.
        ]
    ] ifTrue:[
        self new enter:aContext mayProceed:mayProceed.
    ].
    mayProceed ifFalse:[
        AbortSignal raise
    ].
    ^ nil

    "Modified: / 19.5.1999 / 18:14:33 / cg"
!

enterWithMessage:aString mayProceed:mayProceed
    "enter a miniDebugger"

    self enter:thisContext sender withMessage:aString mayProceed:mayProceed

    "Modified: / 19.5.1999 / 18:14:33 / cg"
!

new
    "redefined to make certain that there is only one miniDebugger
     in the system"

    ^ self basicNew initialize.

"/    TheOneAndOnlyDebugger isNil ifTrue:[
"/        TheOneAndOnlyDebugger := self basicNew initialize
"/    ].
"/    ^ TheOneAndOnlyDebugger

    "
     TheOneAndOnlyDebugger := nil
    "

    "Modified: / 31.7.1998 / 17:08:07 / cg"
!

openOn:aProcess
    "enter a miniDebugger"

    self 
        enter:thisContext sender 
        withMessage:'MiniDebugger [info]: Attention - process debugging not possible.' 
        mayProceed:true

    "Modified: / 19.5.1999 / 18:14:33 / 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:aContext mayProceed:mayProceed
    |c leaveCmd stillHere yesNo|

    enteringContext := dot := aContext.
    nesting := 0.
    c := aContext.
    [c notNil] whileTrue:[
        c selector == #enter:mayProceed: ifTrue:[
            nesting := nesting + 1.
        ].
        c := c sender.
    ].

    stillHere := true.
    [stillHere] whileTrue:[
        AbortSignal handle:[:ex |
            '** Abort Signal cought - back in previous debugLevel' printCR.
        ] do:[
            Error handle:[:ex |
                'Error while executing command: ' print.
                ex description printCR.
                yesNo := self getCommand:'- (i)gnore / (p)roceed / (d)ebug ? '.
                yesNo == $d ifTrue:[
                    ex reject
                ].
                yesNo == $p ifTrue:[
                    ex proceed
                ].
            ] do:[
                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: [
            traceBlock := nil.
            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"
        ].
    ].
    enteringContext := dot := nil.
    ^ nil

    "Modified: / 18.8.1998 / 18:10:29 / cg"
!

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:where mayProceed:true
    ] 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
!

moveDotDown
    "/ sigh - must search
    |c|

    c := enteringContext.
    [ c notNil and:[ c sender ~~ dot ] ] whileTrue:[
	c := c sender.
    ].
    c notNil ifTrue:[
	dot := c.
	self printDot.
    ] ifFalse:[
	'** dot is the bottom of the calling chain' printCR. 
    ].
!

moveDotUp
    dot sender notNil ifTrue:[
	dot := dot sender.
	self printDot.
    ] ifFalse:[
	'** dot is the top of the calling chain' printCR.
    ].
!

printBacktraceFrom:aContext
    |context n|

    aContext isNil ifTrue:[
        'no context' errorPrintCR.
        ^ self
    ].

    context := aContext.
    n := commandCount.
    [context notNil] whileTrue: [
        context fullPrint.
        context := context sender.
        n notNil ifTrue:[
            n := n - 1.
            n <= 0 ifTrue:[
                ^ self
            ]
        ]
    ]
!

printDot
    dot fullPrint
!

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

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

!MiniDebugger methodsFor:'user commands'!

commandLoop
    |cmd done valid context id proc|

    done := false.
    [done] whileFalse:[
        valid := false.
        cmd := self getCommand:nil.
        cmd isNil ifTrue:[   "/ EOF -> continue
            cmd := $c
        ].

        commandArg notEmpty ifTrue:[
            id := Number readFrom:commandArg onError:nil.

            id notNil ifTrue:[
                proc := Process allSubInstances detect:[:p | p id == id] ifNone:nil.
                proc == Processor activeProcess ifTrue:[
                    id := proc := nil
                ]
            ]
        ].

        (cmd == $l) ifTrue:[
            valid := true.
            proc notNil ifTrue:[
                '-------- walkback of process ' print. id print. ' -------' printCR.
                self printBacktraceFrom:(proc suspendedContext)
            ] ifFalse:[
                id notNil ifTrue:[
                    'no process with id: ' print. id printCR.
                ] ifFalse:[
                    context isNil ifTrue: [
                        context := self getContext
                    ].
                    '-------- walkback of current process -------' printCR.
                    self printBacktraceFrom:context
                ]
            ].
        ].

        (cmd == $b) ifTrue:[
            valid := true.
            proc notNil ifTrue:[
                '-------- VM walkback of process ' print. id print. ' -------' printCR.
                ObjectMemory printStackBacktraceFrom:(proc suspendedContext)
            ] ifFalse:[
                id notNil ifTrue:[
                    'no process with id: ' print. id printCR.
                ] ifFalse:[
                    '-------- VM walkback of current process -------' printCR.
                    ObjectMemory printStackBacktrace
                ]
            ]
        ].

        (cmd == $S) ifTrue:[
            valid := true.
            ObjectMemory snapShotOn:'crash.img'.
        ].

        (cmd == $B) ifTrue:[
            valid := true.
            self printAllBacktraces
        ].

        (cmd == $P) ifTrue:[
            valid := true.
            self showProcesses.
        ].

        (cmd == $r) ifTrue:[
            valid := true.
            dot receiver printCR
        ].

        (cmd == $i) ifTrue:[
            valid := true.
            MiniInspector openOn:(dot receiver)
        ].

        (cmd == $I) ifTrue:[
            valid := true.
            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 == $u) ifTrue:[
            stepping := false.
            tracing := false.
            Processor activeProcess vmTrace:false.
        ].

        (cmd == $R) ifTrue:[
            valid := true. 
            proc notNil ifTrue:[
                proc resume.
            ]
        ].

        (cmd == $T) ifTrue:[
            valid := true. 
            proc notNil ifTrue:[
                proc terminate.
            ] ifFalse:[
                id notNil ifTrue:[
                    'no process with id: ' print. id printCR.
                ] ifFalse:[
                    Processor terminateActive
                ]
            ]
        ].

        (cmd == $W) ifTrue:[
            valid := true. 
            proc notNil ifTrue:[
                'stopping process id: ' print. id printCR.
                proc stop.
            ] ifFalse:[
                'invalid process id: ' print. id printCR.
            ]
        ].

        (cmd == $a) ifTrue:[
            "without id-arg, this is handled by caller"
            proc notNil ifTrue:[
                'aborting process id: ' print. id printCR.
                valid := true.
                proc interruptWith:[AbortSignal raise]
            ] ifFalse:[
                'aborting' printCR.
            ]
        ].

        (cmd == $Q) ifTrue:[
            valid := true. 
            proc notNil ifTrue:[
                proc terminateNoSignal.
            ] ifFalse:[
                id notNil ifTrue:[
                    'no process with id: ' print. id printCR.
                ] ifFalse:[
                    Processor terminateActiveNoSignal
                ]
            ]
        ].

        (cmd == $g) ifTrue:[
            valid := true. 
            id == 3 ifTrue:[
                ObjectMemory reclaimSymbols.
                ObjectMemory compressOldSpace.
            ] ifFalse:[
                id == 2 ifTrue:[
                    ObjectMemory reclaimSymbols.
                ] ifFalse:[
                    ObjectMemory garbageCollect.
                ]
            ]
        ].

        (cmd == $U) ifTrue:[valid := true. MessageTracer unwrapAllMethods].
        (cmd == $X) ifTrue:[valid := true. Smalltalk fatalAbort].
        (cmd == $x) ifTrue:[valid := true. OperatingSystem exit].

        (cmd == $.) ifTrue:[valid := true. self printDot ].
        (cmd == $-) ifTrue:[valid := true. self moveDotUp ].
        (cmd == $+) ifTrue:[valid := true. self moveDotDown ].

        "/ avoid usage print if return was typed ...
        ((cmd == Character return)
        or:[cmd == Character linefeed]) ifTrue:[valid := true.].

        valid ifFalse: [
            'valid commands:
   c ..... continue
   s ..... step
   t ..... trace (continue with trace)
   a [id]. abort (i.e. raise abort signal) in (current) process
   T [id]. terminate (current) process
   W [id]. stop (current) process
   R [id]. resume (current) process
   Q [id]. quick terminate (current) process - no unwinds or cleanup

   P ..... list processes
   l [id]. print context chain (of process with id)
   b [id]. full (VM) backtrace
   B ..... backtrace of all other processes

   U ..... unwrap all traced/breakpointed methods
   g ..... collect all garbage
   g 2.... collect all garbage & reclaim symbols
   g 3.... collect all garbage, reclaim symbols and compress

   S ..... save snapshot into crash.img
   X ..... exit (+core)
   x ..... exit Smalltalk

   . ..... print dot (the current context)
   - ..... move dot up
   + ..... move dot down

   r ..... receiver (in dot) printString
   i ..... inspect receiver (in dot)
   I ..... interpreter (expression evaluator)

   To repair a broken X-Connection, enter an interpreter and evaluate:
      Display := XWorkstation new initializeFor:''hostName:0''.
      Display startDispatch.
      NewLauncher openOnDevice:Display.
      <empty line>
   then enter ''c'' to continue; a NewLauncher should pop up soon.

'  errorPrintCR
        ]
    ].
    context := nil.
    ^ cmd

    "Modified: / 31.7.1998 / 17:10:23 / cg"
!

doAbort
    |con sig|

    (sig := AbortOperationRequest) 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: / 16.11.2001 / 17:39:14 / cg"
!

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

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

    (prompt 
	? (nesting == 0 ifTrue:[ 
	    'MiniDebugger> ' 
	  ] ifFalse:[ 
	    'MiniDebugger' , nesting printString , '>'
	  ])) print.

    UserInterruptSignal handle:[:ex |
        ex restart
    ] do:[
        |c cmd arg cnt|

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

        cnt := nil.
        (cmd isDigit) ifTrue:[
            cnt := 0.
            [cmd isDigit] whileTrue:[
                cnt := cnt * 10 + cmd digitValue.
                cmd := Character fromUser
            ].
            [cmd == Character space] whileTrue:[
                cmd := Character fromUser
            ].
        ].

        "
         collect to end-of-line in arg
        "
        c := cmd.
        arg := ''.
        [c isNil or:[c isEndOfLineCharacter]] whileFalse: [
            arg := arg copyWith:c.
            c := Character fromUser.
        ].
        commandArg := arg copyFrom:2.
        command := cmd.
        commandCount := cnt.
    ].
    ^ command

    "Modified: / 31.7.1998 / 16:11:01 / cg"
!

interpreterLoopWith:anObject
    |line done rslt|

    'read-eval-print loop; exit with empty line' printCR.
    '' printCR.

    done := false.
    [done] whileFalse:[
        '> ' print.

        line := Stdin nextLine.
        (line size == 0) ifTrue:[
            done := true
        ] ifFalse:[
            "/ rslt := Compiler evaluate:line 
            "/                  receiver:anObject
            "/                  notifying:nil.

	    rslt := Compiler
		evaluate:line
		in:dot 
		receiver:dot receiver
		notifying:nil
		ifFail:[].
	    rslt printCR.
        ]
    ]

    "Modified: / 31.7.1998 / 16:01:47 / 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 print. '''' printCR.

    Process allSubInstancesDo:[:p |
        'proc id=' print. (p id printStringPaddedTo:5) print. 
        (p state printStringPaddedTo:10) print. 
        ' pri=' print. (p priority printStringPaddedTo:2) print.
        ' creator:' print. (p creatorId printStringPaddedTo:5) print.
        ' name=''' print. p name print. 
        '''' printCR.
    ]

    "Modified: / 31.7.1998 / 16:30:19 / cg"
! !

!MiniDebugger class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MiniDebugger.st,v 1.58 2003-07-07 10:07:26 cg Exp $'
! !