The Trunk: Tools-eem.633.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Tools-eem.633.mcz

commits-2
Eliot Miranda uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-eem.633.mcz

==================== Summary ====================

Name: Tools-eem.633
Author: eem
Time: 17 September 2015, 1:18:07.129 pm
UUID: 2a5a8395-fa44-4d48-b6ed-a920c18dbc02
Ancestors: Tools-mt.632

Fix hard VM crash when defining quick methods from MNUs in the debugger.  The bug is that the sender context (Message>>sentTo:) is doing a perform:withArguments:[inSuperclass:] but the receiver and arguments have already been removed from the context, so simply backing up to the point of send and proceeding will have disastrous consequences; there must be a receiver and arguments on the stack.  So if the arguments are unavailable we simply restart the context inmstead of backing up to the point of send.


To reproduce:
0. make sure e.g. Object>>#zork is unimplemented
1. evaluate "nil zork"
2. in the debugger examine the doesNotUnderstand: context and then hit proceed.
3. click the Create button and define
        Object>>#zork
                ^nil
4. (the debugger sets the active context to Message>>sentTo:) hit proceed

Before the VM woudl crash.  Now the debugger sets the pc to the start of the Message>>sentTo: method.

=============== Diff against Tools-mt.632 ===============

Item was changed:
  ----- Method: Debugger>>contents:notifying: (in category 'accessing') -----
  contents: aText notifying: aController
  "The retrieved information has changed and its source must now be updated.
  In this case, the retrieved information is the method of the selected context."
  | result selector classOfMethod category h ctxt newMethod |
  contextStackIndex = 0 ifTrue:
  [^false].
  self selectedContext isExecutingBlock ifTrue:
  [h := self selectedContext activeHome.
  h ifNil:
  [self inform: 'Method for block not found on stack, can''t edit and continue'.
  ^false].
  (self confirm: 'I will have to revert to the method from\which this block originated.  Is that OK?' withCRs) ifFalse:
  [^false].
  self resetContext: h changeContents: false.
  "N.B. Only reset the contents if the compilation succeeds.  If contents are reset
  when compilation fails both compiler error message and modifications are lost."
  (result := self contents: aText notifying: aController) ifTrue:
  [self contentsChanged].
  ^result].
 
  classOfMethod := self selectedClass.
  category := self selectedMessageCategoryName.
  selector := self selectedClass newParser parseSelector: aText.
  (selector == self selectedMessageName
  or: [(self selectedMessageName beginsWith: 'DoIt')
  and: [selector numArgs = self selectedMessageName numArgs]]) ifFalse:
  [self inform: 'can''t change selector'.
  ^false].
  selector := classOfMethod
  compile: aText
  classified: category
  notifying: aController.
  selector ifNil: [^false]. "compile cancelled"
  contents := aText.
  newMethod := classOfMethod compiledMethodAt: selector.
  newMethod isQuick ifTrue:
+ [self cutBackExecutionToSenderContext].
- [self down.
- self selectedContext jump: (self selectedContext previousPc - self selectedContext pc)].
  ctxt := interruptedProcess popTo: self selectedContext.
  ctxt == self selectedContext
  ifFalse:
  [self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' withCRs]
  ifTrue:
  [newMethod isQuick ifFalse:
  [interruptedProcess
  restartTopWith: newMethod;
  stepToSendOrReturn].
  contextVariablesInspector object: nil].
  self resetContext: ctxt.
  Smalltalk isMorphic ifTrue:
  [World
  addAlarm: #changed:
  withArguments: #(contentsSelection)
  for: self
  at: (Time millisecondClockValue + 200)].
  ^true!

Item was added:
+ ----- Method: Debugger>>cutBackExecutionToSenderContext (in category 'private') -----
+ cutBackExecutionToSenderContext
+ "When accepting a new version of a method which can't be simulated (i.e. a quick method) we
+ must cut back to the sender.  But this is non-trivial. If the quick method has been reached via
+ a perform: (as it is when one uses Create toi implement a method from an MNU) then the relevant
+ arguments won't be on the stack and we can't simply proceed without crashing the VM."
+ | oldContext context sel |
+ oldContext := self selectedContext.
+ self down.
+ context := self selectedContext.
+ context jump: (context previousPc - context pc).
+ sel := context selectorToSendOrSelf.
+ sel numArgs = oldContext method numArgs
+ ifTrue:
+ [context push: oldContext receiver.
+ oldContext arguments do:
+ [:arg| context push: arg]]
+ ifFalse:
+ [context privRefresh; stepToSendOrReturn]!