[squeak-dev] The Trunk: Tools-dtl.776.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 24 23:08:22 UTC 2017


David T. Lewis uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-dtl.776.mcz

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

Name: Tools-dtl.776
Author: dtl
Time: 24 November 2017, 6:08:14.219652 pm
UUID: c9c948eb-74b4-426b-8378-50d3ed174f81
Ancestors: Tools-tpr.775

Remove unnecessary references to global World.

=============== Diff against Tools-tpr.775 ===============

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].
  	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:
+ 		[Project current world
- 		[World
  			addAlarm: #changed:
  			withArguments: #(contentsSelection)
  			for: self
  			at: (Time millisecondClockValue + 200)].
  	^true!

Item was changed:
  ----- Method: Debugger>>runUntil (in category 'code pane menu') -----
  runUntil
  	"Step until an expression evaluates to other than false, reporting an error if it doesn't evaluate to true.
  	 Remember the expression in an inst var.  If shift is pressed when the expression is supplied, don't update the UI.
  	 If shift is pressed while stepping, stop stepping.  Using a user interrupt to break out would be more natural
  	 but Squeak currently doesn't provide a UserInterrupt expection.  It should do."
  	| expression receiver context method value lastUpdate updateUI breakOnShift |
  	expression := UIManager default 
  					request: 'run until expression is true (shift to disable ui update; shift to break).'
  					initialAnswer: (untilExpression ifNil: 'boolean expression').
  	(expression isNil or: [expression isEmpty]) ifTrue:
  		[^self].
  	updateUI := breakOnShift := Sensor shiftPressed not.
  	untilExpression := expression.
  	context := self selectedContext.
  	receiver := context receiver.
  	method := receiver class evaluatorClass new 
  				compiledMethodFor: untilExpression
  				in: context
  				to: receiver
  				notifying: nil
  				ifFail: [^ #failedDoit].
  
  	lastUpdate := Time millisecondClockValue.
  	Cursor execute showWhile:
  		[[self selectedContext == context
  		  and: [context willReturn not
  		  and: [(value := receiver with: context executeMethod: method) == false]]] whileTrue:
  			[interruptedProcess completeStep: self selectedContext.
  			 self selectedContext == context ifTrue:
  				[self resetContext: interruptedProcess stepToSendOrReturn changeContents: false].
  			 Time millisecondClockValue - lastUpdate > 50 ifTrue:
  				[updateUI ifTrue:
  					[self changed: #contentsSelection.
+ 					 Project current world displayWorldSafely].
- 					 World displayWorldSafely].
  				 breakOnShift
  					ifTrue: [Sensor shiftPressed ifTrue:
  								[self changed: #contentsSelection.
  								 self updateInspectors.
  								 ^self]]
  					ifFalse: [Sensor shiftPressed ifFalse: [breakOnShift := true]].
  				 lastUpdate := Time millisecondClockValue]]].
  	self changed: #contentsSelection.
  	self updateInspectors.
  	(value ~~ false and: [value ~~ true]) ifTrue:
  		[UIManager default inform: 'expression ', (untilExpression contractTo: 40), ' answered ', (value printString contractTo: 20), '!!!!']!



More information about the Squeak-dev mailing list