Skip to content

Commit

Permalink
40448
Browse files Browse the repository at this point in the history
14622 PackageManifest can not be in package Manifest-Core...
	https://pharo.fogbugz.com/f/cases/14622

14738 DebugSession assumes sending #stepToSendOrReturn is always needed 
	https://pharo.fogbugz.com/f/cases/14738

14740 Faiing test: testMetaclassAndTraitClassRespectsPolymorphismRules 
	https://pharo.fogbugz.com/f/cases/14740

http://files.pharo.org/image/40/40448.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Jan 15, 2015
1 parent a6f7eed commit 814baf4
Show file tree
Hide file tree
Showing 18 changed files with 383 additions and 15 deletions.
Expand Up @@ -5,6 +5,6 @@ stepInto: aContext
(self isContextPostMortem: aContext) ifTrue: [^ self].

interruptedProcess step: aContext.
self updateContextTo: interruptedProcess stepToSendOrReturn.
self updateContextTo: (self stepToFirstInterestingBytecodeIn: interruptedProcess).

self triggerEvent: #stepInto
Expand Up @@ -9,7 +9,7 @@ stepOver: aContext
newContext := interruptedProcess completeStep: aContext.
self updateContextTo:
(newContext == aContext
ifTrue: [ interruptedProcess stepToSendOrReturn ]
ifTrue: [ (self stepToFirstInterestingBytecodeIn: interruptedProcess) ]
ifFalse: [ newContext ]).

self triggerEvent: #stepOver
Expand Up @@ -5,6 +5,6 @@ stepThrough: aContext
(self isContextPostMortem: aContext) ifTrue: [^ self].

interruptedProcess stepToHome: aContext.
self updateContextTo: interruptedProcess stepToSendOrReturn.
self updateContextTo: (self stepToFirstInterestingBytecodeIn: interruptedProcess).

self triggerEvent: #stepThrough
Expand Up @@ -9,9 +9,8 @@ rewindContextToMethod: aMethod fromContext: aContext
self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' withCRs ]
ifTrue: [
aMethod isQuick ifFalse: [
interruptedProcess
restartTopWith: aMethod;
stepToSendOrReturn ] ].
interruptedProcess restartTopWith: aMethod.
self stepToFirstInterestingBytecodeIn: interruptedProcess ] ].
self updateContextTo: ctxt.

"Issue 3015 - Hernan"
Expand Down
Expand Up @@ -4,8 +4,7 @@ unwindAndRestartToContext: aContext
ctx := interruptedProcess popTo: aContext.
ctx == aContext ifTrue: [
"Only restart the process if the stack was unwind"
interruptedProcess
restartTop;
stepToSendOrReturn ].
interruptedProcess restartTop.
self stepToFirstInterestingBytecodeIn: interruptedProcess ].
self flag: 'Should a warning be displayed if the the unwind failed?'.
self updateContextTo: aContext
@@ -0,0 +1,9 @@
stepToFirstInterestingBytecodeIn: aProcess
"After a restart of a method activation step to the first
bytecode instruction that is of interest for the debugger.
In this case step until a bytecode that causes a context switch,
as otherwise one will have to press may time step into without
seeing any visible results."

^ aProcess stepToSendOrReturn
Expand Up @@ -2,4 +2,4 @@ Object subclass: #PackageManifest
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Manifest-Core'
category: 'Kernel'

0 comments on commit 814baf4

Please sign in to comment.