MiniDebugger.st
changeset 20843 e144b279147d
parent 20826 1d49eb5d790f
child 20846 69db65101d7e
equal deleted inserted replaced
20842:57ae16d01413 20843:e144b279147d
    94 
    94 
    95     Error handle:[:ex |
    95     Error handle:[:ex |
    96         ex return
    96         ex return
    97     ] do:[
    97     ] do:[
    98         thisContext isRecursive ifTrue:[
    98         thisContext isRecursive ifTrue:[
    99             "/ 'recursive lowLevelError in debugger ignored' lowLevelErrorPrintCR.
    99             "/ 'recursive _error in debugger ignored' _errorPrintCR.
   100             ^ self
   100             ^ self
   101         ].
   101         ].
   102 
   102 
   103         aString lowLevelErrorPrintCR.
   103         aString _errorPrintCR.
   104         Processor notNil ifTrue:[
   104         Processor notNil ifTrue:[
   105             active := Processor activeProcess.
   105             active := Processor activeProcess.
   106             'process: id=' lowLevelErrorPrint. active id lowLevelErrorPrint.
   106             'process: id=' _errorPrint. active id _errorPrint.
   107             ' name=' lowLevelErrorPrint. active name lowLevelErrorPrintCR.
   107             ' name=' _errorPrint. active name _errorPrintCR.
   108 
   108 
   109             'context: ' lowLevelErrorPrint. aContext printString lowLevelErrorPrintCR.
   109             'context: ' _errorPrint. aContext printString _errorPrintCR.
   110             (con := aContext) notNil ifTrue:[
   110             (con := aContext) notNil ifTrue:[
   111                 con := con sender.
   111                 con := con sender.
   112                 ' ......: ' lowLevelErrorPrint. con printString lowLevelErrorPrintCR.
   112                 ' ......: ' _errorPrint. con printString _errorPrintCR.
   113                 [con notNil] whileTrue:[
   113                 [con notNil] whileTrue:[
   114                     sender := con sender.
   114                     sender := con sender.
   115                     (sender notNil and:[sender selector == con selector]) ifTrue:[
   115                     (sender notNil and:[sender selector == con selector]) ifTrue:[
   116                         ' ......: ' lowLevelErrorPrint. sender printString lowLevelErrorPrintCR.
   116                         ' ......: ' _errorPrint. sender printString _errorPrintCR.
   117                         ' ......:  [** intermediate recursive contexts skipped **]' lowLevelErrorPrintCR.
   117                         ' ......:  [** intermediate recursive contexts skipped **]' _errorPrintCR.
   118                         [sender notNil
   118                         [sender notNil
   119                          and:[sender selector == con selector
   119                          and:[sender selector == con selector
   120                          and:[sender method == con method]]] whileTrue:[
   120                          and:[sender method == con method]]] whileTrue:[
   121                             con := sender.
   121                             con := sender.
   122                             sender := con sender.
   122                             sender := con sender.
   123                         ].
   123                         ].
   124                     ].
   124                     ].
   125                     con := sender.
   125                     con := sender.
   126                     ' ......: ' lowLevelErrorPrint. con printString lowLevelErrorPrintCR.
   126                     ' ......: ' _errorPrint. con printString _errorPrintCR.
   127                 ]
   127                 ]
   128             ]
   128             ]
   129         ].
   129         ].
   130         NotFirstTimeEntered ~~ true ifTrue:[
   130         NotFirstTimeEntered ~~ true ifTrue:[
   131             NotFirstTimeEntered := true.
   131             NotFirstTimeEntered := true.
   132             'Type "c" to proceed, "?" for help' lowLevelErrorPrintCR.
   132             'Type "c" to proceed, "?" for help' _errorPrintCR.
   133         ].
   133         ].
   134     ].
   134     ].
   135 
   135 
   136     OperatingSystem hasConsole ifFalse:[
   136     OperatingSystem hasConsole ifFalse:[
   137         Error handle:[:ex |
   137         Error handle:[:ex |
   138             ex return
   138             ex return
   139         ] do:[
   139         ] do:[
   140             self warn:('Unexpected lowLevelError:\' , aString , '\\No MiniDebugger functionality available') withCRs .
   140             self warn:('Unexpected _error:\' , aString , '\\No MiniDebugger functionality available') withCRs .
   141         ].
   141         ].
   142 
   142 
   143         Error handle:[:ex |
   143         Error handle:[:ex |
   144             'cannot raise Abort - exiting ...' lowLevelErrorPrintCR.
   144             'cannot raise Abort - exiting ...' _errorPrintCR.
   145             OperatingSystem exit:10.
   145             OperatingSystem exit:10.
   146         ] do:[
   146         ] do:[
   147             AbortOperationRequest raise.
   147             AbortOperationRequest raise.
   148         ]
   148         ]
   149     ] ifTrue:[
   149     ] ifTrue:[
   226     StepInterruptPending := nil.
   226     StepInterruptPending := nil.
   227     ObjectMemory stepInterruptHandler:nil
   227     ObjectMemory stepInterruptHandler:nil
   228 !
   228 !
   229 
   229 
   230 trace:aBlock
   230 trace:aBlock
   231     self trace:aBlock with:[:where | where lowLevelErrorPrintCR]
   231     self trace:aBlock with:[:where | where _errorPrintCR]
   232 
   232 
   233     "Modified: 20.5.1996 / 10:27:37 / cg"
   233     "Modified: 20.5.1996 / 10:27:37 / cg"
   234 !
   234 !
   235 
   235 
   236 trace:aBlock on:aStream
   236 trace:aBlock on:aStream
   283     ].
   283     ].
   284 
   284 
   285     stillHere := true.
   285     stillHere := true.
   286     [stillHere] whileTrue:[
   286     [stillHere] whileTrue:[
   287         AbortOperationRequest handle:[:ex |
   287         AbortOperationRequest handle:[:ex |
   288             '** Abort caught - back in previous debugLevel' lowLevelErrorPrintCR.
   288             '** Abort caught - back in previous debugLevel' _errorPrintCR.
   289         ] do:[
   289         ] do:[
   290             Error handle:[:ex |
   290             Error handle:[:ex |
   291                 StreamError handle:[:ex|
   291                 StreamError handle:[:ex|
   292                     "You won't see this probably - but you will see it when doing a syscall trace"
   292                     "You won't see this probably - but you will see it when doing a syscall trace"
   293                     'Error while processing lowLevelError in MiniDebugger (Stdout closed?):' lowLevelErrorPrintCR.
   293                     'Error while processing _error in MiniDebugger (Stdout closed?):' _errorPrintCR.
   294                     ex description lowLevelErrorPrintCR.
   294                     ex description _errorPrintCR.
   295                     OperatingSystem exit:10.
   295                     OperatingSystem exit:10.
   296                 ] do:[
   296                 ] do:[
   297                     'Error while executing MiniDebugger command: ' lowLevelErrorPrint.
   297                     'Error while executing MiniDebugger command: ' _errorPrint.
   298                     ex description lowLevelErrorPrintCR.
   298                     ex description _errorPrintCR.
   299                     yesNo := self getCommand:'- (i)gnore / (p)roceed / (d)ebug / b(acktrace) ? '.
   299                     yesNo := self getCommand:'- (i)gnore / (p)roceed / (d)ebug / b(acktrace) ? '.
   300                     yesNo == $d ifTrue:[
   300                     yesNo == $d ifTrue:[
   301                         MiniDebugger enterWithMessage:'Debugging debugger' mayProceed:true.
   301                         MiniDebugger enterWithMessage:'Debugging debugger' mayProceed:true.
   302                         ex proceed
   302                         ex proceed
   303                     ].
   303                     ].
   373     ].
   373     ].
   374     stepping ifTrue:[
   374     stepping ifTrue:[
   375         where notNil ifTrue:[
   375         where notNil ifTrue:[
   376             self printContext:where
   376             self printContext:where
   377         ] ifFalse:[
   377         ] ifFalse:[
   378             'stepInterrupt: no context' lowLevelErrorPrintCR
   378             'stepInterrupt: no context' _errorPrintCR
   379         ].
   379         ].
   380         self enter:where mayProceed:true
   380         self enter:where mayProceed:true
   381     ] ifFalse:[
   381     ] ifFalse:[
   382         where notNil ifTrue:[
   382         where notNil ifTrue:[
   383             traceBlock notNil ifTrue:[
   383             traceBlock notNil ifTrue:[
   384                 traceBlock value:where
   384                 traceBlock value:where
   385             ]
   385             ]
   386         ] ifFalse:[
   386         ] ifFalse:[
   387             'traceInterrupt: no context' lowLevelErrorPrintCR
   387             'traceInterrupt: no context' _errorPrintCR
   388         ].
   388         ].
   389         ObjectMemory flushInlineCaches.
   389         ObjectMemory flushInlineCaches.
   390         StepInterruptPending := 1.
   390         StepInterruptPending := 1.
   391         InterruptPending := 1
   391         InterruptPending := 1
   392     ]
   392     ]
   468     ].
   468     ].
   469     c notNil ifTrue:[
   469     c notNil ifTrue:[
   470         dot := c.
   470         dot := c.
   471         "/ dot fullPrint.
   471         "/ dot fullPrint.
   472     ] ifFalse:[
   472     ] ifFalse:[
   473         '** dot is the bottom of the calling chain' lowLevelErrorPrintCR.
   473         '** dot is the bottom of the calling chain' _errorPrintCR.
   474     ].
   474     ].
   475 !
   475 !
   476 
   476 
   477 moveDotUp
   477 moveDotUp
   478     dot sender notNil ifTrue:[
   478     dot sender notNil ifTrue:[
   479         dot := dot sender.
   479         dot := dot sender.
   480         "/ dot fullPrint.
   480         "/ dot fullPrint.
   481     ] ifFalse:[
   481     ] ifFalse:[
   482         '** dot is the top of the calling chain' lowLevelErrorPrintCR.
   482         '** dot is the top of the calling chain' _errorPrintCR.
   483     ].
   483     ].
   484 !
   484 !
   485 
   485 
   486 printBacktraceFrom:aContext
   486 printBacktraceFrom:aContext
   487     |context n|
   487     |context n|
   488 
   488 
   489     aContext isNil ifTrue:[
   489     aContext isNil ifTrue:[
   490         'no context' lowLevelErrorPrintCR.
   490         'no context' _errorPrintCR.
   491         ^ self
   491         ^ self
   492     ].
   492     ].
   493 
   493 
   494     context := aContext.
   494     context := aContext.
   495     n := commandCount.
   495     n := commandCount.
   508 printContext:aContext
   508 printContext:aContext
   509     "print the receiver, selector and args of the context"
   509     "print the receiver, selector and args of the context"
   510 
   510 
   511     "/ aContext fullPrint.
   511     "/ aContext fullPrint.
   512 
   512 
   513     aContext receiverPrintString lowLevelErrorPrint. ' ' lowLevelErrorPrint. 
   513     aContext receiverPrintString _errorPrint. ' ' _errorPrint. 
   514     aContext selector asString lowLevelErrorPrint.
   514     aContext selector asString _errorPrint.
   515     aContext argumentCount ~~ 0 ifTrue: [
   515     aContext argumentCount ~~ 0 ifTrue: [
   516         ' ' lowLevelErrorPrint. aContext argsDisplayString lowLevelErrorPrint
   516         ' ' _errorPrint. aContext argsDisplayString _errorPrint
   517     ].
   517     ].
   518     ' [' lowLevelErrorPrint. 
   518     ' [' _errorPrint. 
   519     aContext lineNumber asString lowLevelErrorPrint. 
   519     aContext lineNumber asString _errorPrint. 
   520     ']' lowLevelErrorPrintCR
   520     ']' _errorPrintCR
   521 !
   521 !
   522 
   522 
   523 printDot
   523 printDot
   524     self printContext:dot.
   524     self printContext:dot.
   525     '  receiver: ' lowLevelErrorPrint. dot receiver printString lowLevelErrorPrintCR.
   525     '  receiver: ' _errorPrint. dot receiver printString _errorPrintCR.
   526     '  selector: ' lowLevelErrorPrint. dot selector lowLevelErrorPrintCR.
   526     '  selector: ' _errorPrint. dot selector _errorPrintCR.
   527     '  args: ' lowLevelErrorPrintCR.
   527     '  args: ' _errorPrintCR.
   528     dot args keysAndValuesDo:[:idx :eachArg |
   528     dot args keysAndValuesDo:[:idx :eachArg |
   529         '    ' lowLevelErrorPrint. idx  printString lowLevelErrorPrint. 
   529         '    ' _errorPrint. idx  printString _errorPrint. 
   530         ': ' lowLevelErrorPrint. eachArg printString lowLevelErrorPrintCR.
   530         ': ' _errorPrint. eachArg printString _errorPrintCR.
   531     ].
   531     ].
   532     '  vars: ' lowLevelErrorPrintCR.
   532     '  vars: ' _errorPrintCR.
   533     dot vars keysAndValuesDo:[:idx :eachVar |
   533     dot vars keysAndValuesDo:[:idx :eachVar |
   534         '    ' lowLevelErrorPrint. idx  printString lowLevelErrorPrint. 
   534         '    ' _errorPrint. idx  printString _errorPrint. 
   535         ': ' lowLevelErrorPrint. eachVar printString lowLevelErrorPrintCR.
   535         ': ' _errorPrint. eachVar printString _errorPrintCR.
   536     ].
   536     ].
   537 !
   537 !
   538 
   538 
   539 printDotsMethodSource
   539 printDotsMethodSource
   540     self printDotsMethodSource:false
   540     self printDotsMethodSource:false
   544     |home mthd src pcLineNr startLnr stopLnr|
   544     |home mthd src pcLineNr startLnr stopLnr|
   545 
   545 
   546     home := dot methodHome.
   546     home := dot methodHome.
   547     mthd := home method.
   547     mthd := home method.
   548     mthd isNil ifTrue:[
   548     mthd isNil ifTrue:[
   549         '** no source **' lowLevelErrorPrintCR.
   549         '** no source **' _errorPrintCR.
   550         ^ self.
   550         ^ self.
   551     ].
   551     ].
   552     src := mthd source.
   552     src := mthd source.
   553     src isNil ifTrue:[
   553     src isNil ifTrue:[
   554         '** no source **' lowLevelErrorPrintCR.
   554         '** no source **' _errorPrintCR.
   555         ^ self.
   555         ^ self.
   556     ].
   556     ].
   557     pcLineNr := dot lineNumber.
   557     pcLineNr := dot lineNumber.
   558 
   558 
   559     src := src asCollectionOfLines.
   559     src := src asCollectionOfLines.
   564         startLnr := pcLineNr-10 max:1.
   564         startLnr := pcLineNr-10 max:1.
   565         stopLnr := pcLineNr+10 min:src size.
   565         stopLnr := pcLineNr+10 min:src size.
   566     ].
   566     ].
   567     startLnr to:stopLnr do:[:lNr |
   567     startLnr to:stopLnr do:[:lNr |
   568         lNr == pcLineNr ifTrue:[
   568         lNr == pcLineNr ifTrue:[
   569             '>> ' lowLevelErrorPrint.
   569             '>> ' _errorPrint.
   570         ] ifFalse:[
   570         ] ifFalse:[
   571             '   ' lowLevelErrorPrint.
   571             '   ' _errorPrint.
   572         ].
   572         ].
   573         (lNr printStringLeftPaddedTo:3) lowLevelErrorPrint. ' ' lowLevelErrorPrint.
   573         (lNr printStringLeftPaddedTo:3) _errorPrint. ' ' _errorPrint.
   574         (src at:lNr) asString lowLevelErrorPrintCR.
   574         (src at:lNr) asString _errorPrintCR.
   575     ]
   575     ]
   576 !
   576 !
   577 
   577 
   578 stepping
   578 stepping
   579     traceBlock := nil.
   579     traceBlock := nil.
   611 doAbort
   611 doAbort
   612     |con sig|
   612     |con sig|
   613 
   613 
   614     (sig := AbortOperationRequest) isHandled ifTrue:[
   614     (sig := AbortOperationRequest) isHandled ifTrue:[
   615         sig raise.
   615         sig raise.
   616         'abort raise failed' lowLevelErrorPrintCR.
   616         'abort raise failed' _errorPrintCR.
   617     ].
   617     ].
   618 
   618 
   619     "TEMPORARY kludge - find event handler context
   619     "TEMPORARY kludge - find event handler context
   620      this will be removed, once real debugging is possible
   620      this will be removed, once real debugging is possible
   621     "
   621     "
   624         con := self findContext:#dispatch.
   624         con := self findContext:#dispatch.
   625     ].
   625     ].
   626     con notNil ifTrue:[
   626     con notNil ifTrue:[
   627         "got it"
   627         "got it"
   628         con return.
   628         con return.
   629         'return failed' lowLevelErrorPrintCR.
   629         'return failed' _errorPrintCR.
   630     ].
   630     ].
   631 
   631 
   632     'found no context to resume' lowLevelErrorPrintCR.
   632     'found no context to resume' _errorPrintCR.
   633 
   633 
   634     "Modified: / 16.11.2001 / 17:39:14 / cg"
   634     "Modified: / 16.11.2001 / 17:39:14 / cg"
   635 !
   635 !
   636 
   636 
   637 doCommand:cmd
   637 doCommand:cmd
   658         ]
   658         ]
   659     ].
   659     ].
   660 
   660 
   661     (cmd == $w) ifTrue:[
   661     (cmd == $w) ifTrue:[
   662         proc notNil ifTrue:[
   662         proc notNil ifTrue:[
   663             '-------- walkback of process ' lowLevelErrorPrint. id lowLevelErrorPrint. ' -------' lowLevelErrorPrintCR.
   663             '-------- walkback of process ' _errorPrint. id _errorPrint. ' -------' _errorPrintCR.
   664             self printBacktraceFrom:(proc suspendedContext)
   664             self printBacktraceFrom:(proc suspendedContext)
   665         ] ifFalse:[
   665         ] ifFalse:[
   666             id notNil ifTrue:[
   666             id notNil ifTrue:[
   667                 'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   667                 'no process with id: ' _errorPrint. id _errorPrintCR.
   668             ] ifFalse:[
   668             ] ifFalse:[
   669                 '-------- walkback of current process -------' lowLevelErrorPrintCR.
   669                 '-------- walkback of current process -------' _errorPrintCR.
   670                 self printBacktraceFrom:(self getContext)
   670                 self printBacktraceFrom:(self getContext)
   671             ]
   671             ]
   672         ].
   672         ].
   673         ^ false
   673         ^ false
   674     ].
   674     ].
   675 
   675 
   676     (cmd == $b) ifTrue:[
   676     (cmd == $b) ifTrue:[
   677         proc notNil ifTrue:[
   677         proc notNil ifTrue:[
   678             '-------- VM walkback of process ' lowLevelErrorPrint. id lowLevelErrorPrint. ' -------' lowLevelErrorPrintCR.
   678             '-------- VM walkback of process ' _errorPrint. id _errorPrint. ' -------' _errorPrintCR.
   679             (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
   679             (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
   680                 ObjectMemory printStackBacktraceFrom:(proc suspendedContext)
   680                 ObjectMemory printStackBacktraceFrom:(proc suspendedContext)
   681             ] ifFalse:[
   681             ] ifFalse:[
   682                 self printBacktraceFrom:(proc suspendedContext)
   682                 self printBacktraceFrom:(proc suspendedContext)
   683                 "/ proc suspendedContext fullPrintAllOn:(Processor activeProcess environmentAt:#Stderr)
   683                 "/ proc suspendedContext fullPrintAllOn:(Processor activeProcess environmentAt:#Stderr)
   684             ].    
   684             ].    
   685         ] ifFalse:[
   685         ] ifFalse:[
   686             id notNil ifTrue:[
   686             id notNil ifTrue:[
   687                 'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   687                 'no process with id: ' _errorPrint. id _errorPrintCR.
   688             ] ifFalse:[
   688             ] ifFalse:[
   689                 '-------- VM walkback of current process -------' lowLevelErrorPrintCR.
   689                 '-------- VM walkback of current process -------' _errorPrintCR.
   690                 (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
   690                 (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
   691                     ObjectMemory printStackBacktrace
   691                     ObjectMemory printStackBacktrace
   692                 ] ifFalse:[
   692                 ] ifFalse:[
   693                     "/ self printBacktraceFrom:(self getContext)
   693                     "/ self printBacktraceFrom:(self getContext)
   694                     thisContext fullPrintAllOn:(Processor activeProcess environmentAt:#Stderr)
   694                     thisContext fullPrintAllOn:(Processor activeProcess environmentAt:#Stderr)
   697         ].
   697         ].
   698         ^ false
   698         ^ false
   699     ].
   699     ].
   700 
   700 
   701     (cmd == $S) ifTrue:[
   701     (cmd == $S) ifTrue:[
   702         'saving "crash.img"...' lowLevelErrorPrint.
   702         'saving "crash.img"...' _errorPrint.
   703         ObjectMemory writeCrashImage.
   703         ObjectMemory writeCrashImage.
   704         'done.' lowLevelErrorPrintCR.
   704         'done.' _errorPrintCR.
   705         ^ false
   705         ^ false
   706     ].
   706     ].
   707     (cmd == $C) ifTrue:[
   707     (cmd == $C) ifTrue:[
   708         |changesFilename|
   708         |changesFilename|
   709 
   709 
   710         changesFilename := Timestamp now
   710         changesFilename := Timestamp now
   711              printStringFormat:'changes_%(year)-%(month)-%(day)__%h:%m:%s.chg'.
   711              printStringFormat:'changes_%(year)-%(month)-%(day)__%h:%m:%s.chg'.
   712         OperatingSystem isMSWINDOWSlike ifTrue:[ changesFilename replaceAll:$: with:$_ ].
   712         OperatingSystem isMSWINDOWSlike ifTrue:[ changesFilename replaceAll:$: with:$_ ].
   713 
   713 
   714         ChangeSet current fileOutAs: changesFilename.
   714         ChangeSet current fileOutAs: changesFilename.
   715         ('saved session changes to "',changesFilename,'".') lowLevelErrorPrintCR.
   715         ('saved session changes to "',changesFilename,'".') _errorPrintCR.
   716         ^ false
   716         ^ false
   717     ].
   717     ].
   718 
   718 
   719     (cmd == $B) ifTrue:[
   719     (cmd == $B) ifTrue:[
   720         self printAllBacktraces.
   720         self printAllBacktraces.
   729         self showProcesses:#live.
   729         self showProcesses:#live.
   730         ^ false
   730         ^ false
   731     ].
   731     ].
   732 
   732 
   733     (cmd == $r) ifTrue:[
   733     (cmd == $r) ifTrue:[
   734         dot receiver lowLevelErrorPrintCR.
   734         dot receiver _errorPrintCR.
   735         ^ false
   735         ^ false
   736     ].
   736     ].
   737 
   737 
   738     (cmd == $i) ifTrue:[
   738     (cmd == $i) ifTrue:[
   739         |inspectedObject|
   739         |inspectedObject|
   754     (cmd == $E) ifTrue:[
   754     (cmd == $E) ifTrue:[
   755         Parser evaluate:commandArg.
   755         Parser evaluate:commandArg.
   756         ^ false
   756         ^ false
   757     ].
   757     ].
   758     (cmd == $e) ifTrue:[
   758     (cmd == $e) ifTrue:[
   759         (Parser evaluate:commandArg) lowLevelErrorPrintCR.
   759         (Parser evaluate:commandArg) _errorPrintCR.
   760         ^ false
   760         ^ false
   761     ].
   761     ].
   762 
   762 
   763     (cmd == $c) ifTrue:[^ true].
   763     (cmd == $c) ifTrue:[^ true].
   764     (cmd == $s) ifTrue:[^ true].
   764     (cmd == $s) ifTrue:[^ true].
   774 
   774 
   775     (cmd == $h) ifTrue:[
   775     (cmd == $h) ifTrue:[
   776         (bool notNil) ifTrue:[
   776         (bool notNil) ifTrue:[
   777             Smalltalk ignoreHalt:bool not.
   777             Smalltalk ignoreHalt:bool not.
   778         ].
   778         ].
   779         'halts are ' lowLevelErrorPrint. (Smalltalk ignoreHalt ifTrue:['disabled'] ifFalse:['enabled']) lowLevelErrorPrintCR.
   779         'halts are ' _errorPrint. (Smalltalk ignoreHalt ifTrue:['disabled'] ifFalse:['enabled']) _errorPrintCR.
   780         ^ false
   780         ^ false
   781     ].
   781     ].
   782 
   782 
   783     (cmd == $R) ifTrue:[
   783     (cmd == $R) ifTrue:[
   784         proc notNil ifTrue:[
   784         proc notNil ifTrue:[
   790     (cmd == $T) ifTrue:[
   790     (cmd == $T) ifTrue:[
   791         proc notNil ifTrue:[
   791         proc notNil ifTrue:[
   792             proc terminate.
   792             proc terminate.
   793         ] ifFalse:[
   793         ] ifFalse:[
   794             id notNil ifTrue:[
   794             id notNil ifTrue:[
   795                 'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   795                 'no process with id: ' _errorPrint. id _errorPrintCR.
   796             ] ifFalse:[
   796             ] ifFalse:[
   797                 Processor terminateActive
   797                 Processor terminateActive
   798             ]
   798             ]
   799         ].
   799         ].
   800         ^ false
   800         ^ false
   801     ].
   801     ].
   802 
   802 
   803     (cmd == $W) ifTrue:[
   803     (cmd == $W) ifTrue:[
   804         proc notNil ifTrue:[
   804         proc notNil ifTrue:[
   805             'stopping process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   805             'stopping process id: ' _errorPrint. id _errorPrintCR.
   806             proc stop.
   806             proc stop.
   807         ] ifFalse:[
   807         ] ifFalse:[
   808             'invalid process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   808             'invalid process id: ' _errorPrint. id _errorPrintCR.
   809         ].
   809         ].
   810         ^ false
   810         ^ false
   811     ].
   811     ].
   812 
   812 
   813     (cmd == $a) ifTrue:[
   813     (cmd == $a) ifTrue:[
   814         "without id-arg, this is handled by caller"
   814         "without id-arg, this is handled by caller"
   815         proc notNil ifTrue:[
   815         proc notNil ifTrue:[
   816             'aborting process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   816             'aborting process id: ' _errorPrint. id _errorPrintCR.
   817             proc interruptWith:[AbortOperationRequest raise]
   817             proc interruptWith:[AbortOperationRequest raise]
   818         ] ifFalse:[
   818         ] ifFalse:[
   819             'aborting' lowLevelErrorPrintCR.
   819             'aborting' _errorPrintCR.
   820         ].
   820         ].
   821         ^ false
   821         ^ false
   822     ].
   822     ].
   823 
   823 
   824     (cmd == $Q) ifTrue:[
   824     (cmd == $Q) ifTrue:[
   825         proc notNil ifTrue:[
   825         proc notNil ifTrue:[
   826             proc terminateNoSignal.
   826             proc terminateNoSignal.
   827         ] ifFalse:[
   827         ] ifFalse:[
   828             id notNil ifTrue:[
   828             id notNil ifTrue:[
   829                 'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
   829                 'no process with id: ' _errorPrint. id _errorPrintCR.
   830             ] ifFalse:[
   830             ] ifFalse:[
   831                 Processor terminateActiveNoSignal
   831                 Processor terminateActiveNoSignal
   832             ]
   832             ]
   833         ].
   833         ].
   834         ^ false
   834         ^ false
   901     (prompt
   901     (prompt
   902         ? (nesting == 0 ifTrue:[
   902         ? (nesting == 0 ifTrue:[
   903             'MiniDebugger> '
   903             'MiniDebugger> '
   904           ] ifFalse:[
   904           ] ifFalse:[
   905             'MiniDebugger' , nesting printString , '>'
   905             'MiniDebugger' , nesting printString , '>'
   906           ])) lowLevelErrorPrint.
   906           ])) _errorPrint.
   907 
   907 
   908     UserInterrupt handle:[:ex |
   908     UserInterrupt handle:[:ex |
   909         ex restart
   909         ex restart
   910     ] do:[
   910     ] do:[
   911         |c cmd arg cnt|
   911         |c cmd arg cnt|
   912 
   912 
   913         cmd := self getCharacter.
   913         cmd := self getCharacter.
   914         cmd isNil ifTrue:[
   914         cmd isNil ifTrue:[
   915             '<EOF>' lowLevelErrorPrintCR.
   915             '<EOF>' _errorPrintCR.
   916             "
   916             "
   917              mhmh end-of-file;
   917              mhmh end-of-file;
   918              return a 'c' (for continue); hope that's ok.
   918              return a 'c' (for continue); hope that's ok.
   919             "
   919             "
   920             cmd := $c
   920             cmd := $c
   928                 cmd := self getCharacter
   928                 cmd := self getCharacter
   929             ] doWhile:[cmd notNil and:[cmd isDigit]].
   929             ] doWhile:[cmd notNil and:[cmd isDigit]].
   930             [cmd notNil and:[cmd == Character space]] whileTrue:[
   930             [cmd notNil and:[cmd == Character space]] whileTrue:[
   931                 cmd := self getCharacter
   931                 cmd := self getCharacter
   932             ].
   932             ].
   933             cmd isNil ifTrue:[ '<EOF>' lowLevelErrorPrintCR ].
   933             cmd isNil ifTrue:[ '<EOF>' _errorPrintCR ].
   934         ].
   934         ].
   935 
   935 
   936         "
   936         "
   937          collect to end-of-line in arg
   937          collect to end-of-line in arg
   938         "
   938         "
   939         c := cmd.
   939         c := cmd.
   940         arg := ''.
   940         arg := ''.
   941         [c isNil or:[c isEndOfLineCharacter]] whileFalse: [
   941         [c isNil or:[c isEndOfLineCharacter]] whileFalse: [
   942             arg := arg copyWith:c.
   942             arg := arg copyWith:c.
   943             c := self getCharacter.
   943             c := self getCharacter.
   944             c isNil ifTrue:[ '<EOF>' lowLevelErrorPrintCR ].
   944             c isNil ifTrue:[ '<EOF>' _errorPrintCR ].
   945         ].
   945         ].
   946         commandArg := (arg copyFrom:2) withoutSeparators.
   946         commandArg := (arg copyFrom:2) withoutSeparators.
   947         command := cmd.
   947         command := cmd.
   948         commandCount := cnt.
   948         commandCount := cnt.
   949     ].
   949     ].
   954 
   954 
   955 helpOn:commandArg
   955 helpOn:commandArg
   956     |args className sym val match showMethod|
   956     |args className sym val match showMethod|
   957 
   957 
   958     commandArg withoutSeparators isEmpty ifTrue:[
   958     commandArg withoutSeparators isEmpty ifTrue:[
   959         'usage: H className [methodPattern]' lowLevelErrorPrintCR.
   959         'usage: H className [methodPattern]' _errorPrintCR.
   960         ^self
   960         ^self
   961     ].
   961     ].
   962     args := commandArg asCollectionOfWords.
   962     args := commandArg asCollectionOfWords.
   963     className := args first.
   963     className := args first.
   964 
   964 
   965     (sym := className asSymbolIfInterned) isNil ifTrue:[
   965     (sym := className asSymbolIfInterned) isNil ifTrue:[
   966         'no such class' lowLevelErrorPrintCR.
   966         'no such class' _errorPrintCR.
   967         ^ self.
   967         ^ self.
   968     ].
   968     ].
   969     val := Smalltalk at:sym ifAbsent:['no such class' lowLevelErrorPrintCR. ^ self.].
   969     val := Smalltalk at:sym ifAbsent:['no such class' _errorPrintCR. ^ self.].
   970     val isBehavior ifFalse:[
   970     val isBehavior ifFalse:[
   971         'not a class: ' lowLevelErrorPrint. className lowLevelErrorPrintCR.
   971         'not a class: ' _errorPrint. className _errorPrintCR.
   972         val := val class.
   972         val := val class.
   973         'showing help for ' lowLevelErrorPrint. val name lowLevelErrorPrintCR.
   973         'showing help for ' _errorPrint. val name _errorPrintCR.
   974     ].
   974     ].
   975     args size > 1 ifTrue:[
   975     args size > 1 ifTrue:[
   976         match := args at:2
   976         match := args at:2
   977     ] ifFalse:[
   977     ] ifFalse:[
   978         match := '*'
   978         match := '*'
   984 
   984 
   985             ((match includesMatchCharacters and:[ sel matches:match caseSensitive:false])
   985             ((match includesMatchCharacters and:[ sel matches:match caseSensitive:false])
   986             or:[ sel asLowercase startsWith:match asLowercase ]) ifTrue:[
   986             or:[ sel asLowercase startsWith:match asLowercase ]) ifTrue:[
   987                 mthd := cls compiledMethodAt:sel.
   987                 mthd := cls compiledMethodAt:sel.
   988                 mthd category ~= 'documentation' ifTrue:[
   988                 mthd category ~= 'documentation' ifTrue:[
   989                     sel lowLevelErrorPrintCR.
   989                     sel _errorPrintCR.
   990                     (mthd comment ? '') asStringCollection do:[:l |
   990                     (mthd comment ? '') asStringCollection do:[:l |
   991                         '    ' lowLevelErrorPrint. l withoutSeparators lowLevelErrorPrintCR.
   991                         '    ' _errorPrint. l withoutSeparators _errorPrintCR.
   992                     ].
   992                     ].
   993                     '' lowLevelErrorPrintCR
   993                     '' _errorPrintCR
   994                 ].
   994                 ].
   995             ].
   995             ].
   996         ].
   996         ].
   997 
   997 
   998     val theMetaclass selectors copy sort do:[:sel |
   998     val theMetaclass selectors copy sort do:[:sel |
  1043 
  1043 
  1044 printAllBacktraces
  1044 printAllBacktraces
  1045     Process allInstancesDo:[:p |
  1045     Process allInstancesDo:[:p |
  1046         (p isActive not
  1046         (p isActive not
  1047         and:[p isDead not]) ifTrue:[
  1047         and:[p isDead not]) ifTrue:[
  1048             '---------------------------------------------------------' lowLevelErrorPrintCR.
  1048             '---------------------------------------------------------' _errorPrintCR.
  1049             '  proc id=' lowLevelErrorPrint. p id asString lowLevelErrorPrint.
  1049             '  proc id=' _errorPrint. p id asString _errorPrint.
  1050             ' name=''' lowLevelErrorPrint. p name asString lowLevelErrorPrint.
  1050             ' name=''' _errorPrint. p name asString _errorPrint.
  1051             ''' createdBy: ' lowLevelErrorPrint. p creatorId asString lowLevelErrorPrint.
  1051             ''' createdBy: ' _errorPrint. p creatorId asString _errorPrint.
  1052             ' state=' lowLevelErrorPrint.  p state asString lowLevelErrorPrint.
  1052             ' state=' _errorPrint.  p state asString _errorPrint.
  1053             ' prio=' lowLevelErrorPrint. p priority asString lowLevelErrorPrintCR.
  1053             ' prio=' _errorPrint. p priority asString _errorPrintCR.
  1054             '' lowLevelErrorPrintCR. '' lowLevelErrorPrintCR.
  1054             '' _errorPrintCR. '' _errorPrintCR.
  1055 
  1055 
  1056             self printBacktraceFrom:(p suspendedContext)
  1056             self printBacktraceFrom:(p suspendedContext)
  1057         ]
  1057         ]
  1058     ]
  1058     ]
  1059 !
  1059 !
  1064 
  1064 
  1065 showProcesses:how
  1065 showProcesses:how
  1066     |active|
  1066     |active|
  1067 
  1067 
  1068     active := Processor activeProcess.
  1068     active := Processor activeProcess.
  1069     'current id=' lowLevelErrorPrint. 
  1069     'current id=' _errorPrint. 
  1070     active id printString lowLevelErrorPrint. 
  1070     active id printString _errorPrint. 
  1071     ' name=''' lowLevelErrorPrint. active name lowLevelErrorPrint. '''' lowLevelErrorPrintCR.
  1071     ' name=''' _errorPrint. active name _errorPrint. '''' _errorPrintCR.
  1072 
  1072 
  1073     (Process allSubInstances sort:[:a :b | (a id ? -1)<(b id ? -1)]) do:[:p |
  1073     (Process allSubInstances sort:[:a :b | (a id ? -1)<(b id ? -1)]) do:[:p |
  1074         |doShow|
  1074         |doShow|
  1075 
  1075 
  1076         doShow := (how == #all).
  1076         doShow := (how == #all).
  1077         doShow := doShow or:[ (how == #dead) and:[ p isDead ]].
  1077         doShow := doShow or:[ (how == #dead) and:[ p isDead ]].
  1078         doShow := doShow or:[ (how ~~ #dead) and:[ p isDead not ]].
  1078         doShow := doShow or:[ (how ~~ #dead) and:[ p isDead not ]].
  1079         doShow ifTrue:[
  1079         doShow ifTrue:[
  1080             'proc id=' lowLevelErrorPrint. (p id printStringPaddedTo:6) lowLevelErrorPrint.
  1080             'proc id=' _errorPrint. (p id printStringPaddedTo:6) _errorPrint.
  1081             (p state printStringPaddedTo:10) lowLevelErrorPrint.
  1081             (p state printStringPaddedTo:10) _errorPrint.
  1082             ' pri=' lowLevelErrorPrint. (p priority printStringPaddedTo:2) lowLevelErrorPrint.
  1082             ' pri=' _errorPrint. (p priority printStringPaddedTo:2) _errorPrint.
  1083             ' creator:' lowLevelErrorPrint. (p creatorId printStringPaddedTo:5) lowLevelErrorPrint.
  1083             ' creator:' _errorPrint. (p creatorId printStringPaddedTo:5) _errorPrint.
  1084             ' group:' lowLevelErrorPrint. (p processGroupId printStringPaddedTo:5) lowLevelErrorPrint.
  1084             ' group:' _errorPrint. (p processGroupId printStringPaddedTo:5) _errorPrint.
  1085             ' sys:' lowLevelErrorPrint. (p isSystemProcess ifTrue:'y' ifFalse:'n') lowLevelErrorPrint.
  1085             ' sys:' _errorPrint. (p isSystemProcess ifTrue:'y' ifFalse:'n') _errorPrint.
  1086             ' ui:' lowLevelErrorPrint. (p isGUIProcess ifTrue:'y' ifFalse:'n') lowLevelErrorPrint.
  1086             ' ui:' _errorPrint. (p isGUIProcess ifTrue:'y' ifFalse:'n') _errorPrint.
  1087             ' name=''' lowLevelErrorPrint. p name lowLevelErrorPrint.
  1087             ' name=''' _errorPrint. p name _errorPrint.
  1088             '''' lowLevelErrorPrintCR.
  1088             '''' _errorPrintCR.
  1089         ]
  1089         ]
  1090     ]
  1090     ]
  1091 
  1091 
  1092     "Modified: / 31.7.1998 / 16:30:19 / cg"
  1092     "Modified: / 31.7.1998 / 16:30:19 / cg"
  1093 !
  1093 !
  1128    r ........ receiver (in dot) printString
  1128    r ........ receiver (in dot) printString
  1129    i [expr] . inspect expression (or receiver in dot)
  1129    i [expr] . inspect expression (or receiver in dot)
  1130    I ........ interpreter (expression evaluator)
  1130    I ........ interpreter (expression evaluator)
  1131    e expr ... evaluate expression & print result ("E" to not print)
  1131    e expr ... evaluate expression & print result ("E" to not print)
  1132    ? c [p] .. help on class c (selectors matching p)
  1132    ? c [p] .. help on class c (selectors matching p)
  1133 '  lowLevelErrorPrintCR.
  1133 '  _errorPrintCR.
  1134 
  1134 
  1135    (XWorkstation notNil and:[ Screen default isKindOf:XWorkstation ]) ifTrue:[
  1135    (XWorkstation notNil and:[ Screen default isKindOf:XWorkstation ]) ifTrue:[
  1136 '   To repair a broken X-Connection, enter an interpreter (enter "I") and evaluate:
  1136 '   To repair a broken X-Connection, enter an interpreter (enter "I") and evaluate:
  1137       Display := XWorkstation new.
  1137       Display := XWorkstation new.
  1138       Display initializeFor:''localhost:0''.
  1138       Display initializeFor:''localhost:0''.
  1139       Display startDispatch.
  1139       Display startDispatch.
  1140       NewLauncher openOnDevice:Display.
  1140       NewLauncher openOnDevice:Display.
  1141       #exit
  1141       #exit
  1142     then enter "c" to continue; a NewLauncher should pop up soon.
  1142     then enter "c" to continue; a NewLauncher should pop up soon.
  1143 '  lowLevelErrorPrintCR
  1143 '  _errorPrintCR
  1144     ]
  1144     ]
  1145 
  1145 
  1146     "Modified: / 03-02-2014 / 10:38:36 / cg"
  1146     "Modified: / 03-02-2014 / 10:38:36 / cg"
  1147 ! !
  1147 ! !
  1148 
  1148