[squeak-dev] The Trunk: ST80-nice.79.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 27 03:00:56 UTC 2009


Nicolas Cellier uploaded a new version of ST80 to project The Trunk:
http://source.squeak.org/trunk/ST80-nice.79.mcz

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

Name: ST80-nice.79
Author: nice
Time: 27 December 2009, 4:00:33 am
UUID: b232da16-3dea-4aed-8c7a-af66448c3c9e
Ancestors: ST80-nice.78

Cosmetic: move or remove a few temps inside closures

=============== Diff against ST80-nice.78 ===============

Item was changed:
  ----- Method: FormMenuView>>makeColorConnections: (in category 'private') -----
  makeColorConnections: indexInterval
  
+ 	| connector aSwitchView |
- 	| connector buttonCache button aSwitchView |
  	connector := Object new.  "a dummy model for connecting dependents"
+ 	indexInterval do: [:index | | button buttonCache |
- 	indexInterval do: [:index |
  	buttonCache := (FormButtons at: index) shallowCopy.
  	buttonCache form: (FormButtons at: index) form copy.
  		buttonCache initialState = #true
  			ifTrue: [button := OneOnSwitch newOn]
  			ifFalse: [button := OneOnSwitch newOff].
  		button onAction: [model changeTool: buttonCache value].
  		button connection: connector.
  		aSwitchView := self makeViews: buttonCache for: button.
  		aSwitchView
  			borderWidthLeft: 1 right: 0 top: 1 bottom: 1;
  			action: #turnOn].
  	aSwitchView borderWidth: 1.
  !

Item was changed:
  ----- Method: PluggableTextController>>visibleAreas (in category 'transcript') -----
  visibleAreas
  	"Transcript dependents last controller visibleAreas"
+ 	| myTopController visibleAreas |
- 	| visibleAreas rect remnants myTopController |
  	myTopController := self view topView controller.
  	visibleAreas := Array with: view insetDisplayBox.
  	myTopController view uncacheBits.
  	ScheduledControllers scheduledWindowControllers do:
+ 		[:c | | remnants rect |
+ 		c == myTopController ifTrue: [^ visibleAreas].
- 		[:c | c == myTopController ifTrue: [^ visibleAreas].
  		rect := c view windowBox.
  		remnants := OrderedCollection new.
  		visibleAreas do: [:a | remnants addAll: (a areasOutside: rect)].
  		visibleAreas := remnants].
  	^ visibleAreas!

Item was changed:
  ----- Method: ParagraphEditor>>tallySelection (in category 'do-its') -----
  tallySelection
  	"Treat the current selection as an expression; evaluate it and return the time took for this evaluation"
+ 	| result rcvr ctxt valueAsString v |
- 	| result rcvr ctxt cm v valueAsString |
  	self lineSelectAndEmptyCheck: [^ -1].
  
  	(model respondsTo: #doItReceiver) 
  		ifTrue: [FakeClassPool adopt: model selectedClass.  "Include model pool vars if any"
  				rcvr := model doItReceiver.
  				ctxt := model doItContext]
  		ifFalse: [rcvr := ctxt := nil].
+ 	result := [ | cm |
- 	result := [
  		cm := rcvr class evaluatorClass new 
  			compiledMethodFor: self selectionAsStream
  			in: ctxt
  			to: rcvr
  			notifying: self
  			ifFail: [FakeClassPool adopt: nil. ^ #failedDoit]
  			logged: false.
  		Time millisecondsToRun: 
  			[v := cm valueWithReceiver: rcvr arguments: (Array with: ctxt)].
  	] 
  		on: OutOfScopeNotification 
  		do: [ :ex | ex resume: true].
  	FakeClassPool adopt: nil.
  
  	"We do not want to have large result displayed"
  	valueAsString := v printString.
  	(valueAsString size > 30) ifTrue: [valueAsString := (valueAsString copyFrom: 1 to: 30), '...'].
  	PopUpMenu 
  		inform: 'Time to compile and execute: ', result printString, 'ms res: ', valueAsString.
  !

Item was changed:
  ----- Method: FormMenuView>>makeConnections: (in category 'private') -----
  makeConnections: indexInterval
  
+ 	| connector aSwitchView |
- 	| connector buttonCache button aSwitchView |
  	connector := Object new.  "a dummy model for connecting dependents."
+ 	indexInterval do: [:index | | button buttonCache |
- 	indexInterval do: [:index |
  	buttonCache := (FormButtons at: index) shallowCopy.
  	buttonCache form: (FormButtons at: index) form copy.
  		buttonCache initialState = #true
  			ifTrue: [button := OneOnSwitch newOn]
  			ifFalse: [button := OneOnSwitch newOff].
  		button onAction: [model changeTool: buttonCache value].
  		button connection: connector.
  		aSwitchView := self makeViews: buttonCache for: button.
  		aSwitchView
  			borderWidthLeft: 1 right: 0 top: 1 bottom: 1;
  			action: #turnOn].
  	aSwitchView borderWidth: 1.
  !

Item was changed:
  ----- Method: ParagraphEditor>>saveContentsInFile (in category 'menu messages') -----
  saveContentsInFile
  	"Save the receiver's contents string to a file, prompting the user for a file-name.  Suggest a reasonable file-name."
  
+ 	| fileName stringToSave parentWindow labelToUse suggestedName |
- 	| fileName stringToSave parentWindow labelToUse suggestedName lastIndex |
  	stringToSave := paragraph text string.
  	stringToSave size == 0 ifTrue: [^ self inform: 'nothing to save.'].
  	parentWindow := self model dependents
  						detect: [:dep | dep isKindOf: SystemWindow orOf: StandardSystemView]
  						ifNone: [nil].
  	labelToUse := parentWindow
  		ifNil: 		['Untitled']
  		ifNotNil: 	[parentWindow label].
  	suggestedName := nil.
  	#(('Decompressed contents of: '		'.gz')) do:  "can add more here..."
+ 		[:leaderTrailer | | lastIndex |
- 		[:leaderTrailer |
  			(labelToUse beginsWith: leaderTrailer first) ifTrue:
  				[suggestedName := labelToUse copyFrom: leaderTrailer first size + 1 to: labelToUse size.
  				(labelToUse endsWith: leaderTrailer last)
  					ifTrue:
  						[suggestedName := suggestedName copyFrom: 1 to: suggestedName size - leaderTrailer last size]
  					ifFalse:
  						[lastIndex := suggestedName lastIndexOf: $. ifAbsent: [0].
  						(lastIndex = 0 or: [lastIndex = 1]) ifFalse:
  							[suggestedName := suggestedName copyFrom: 1 to: lastIndex - 1]]]].
  
  	suggestedName ifNil:
  		[suggestedName := labelToUse, '.text'].
  			
  	fileName := UIManager default request: 'File name?' translated
  			initialAnswer: suggestedName.
  	fileName isEmptyOrNil ifFalse:
  		[(FileStream newFileNamed: fileName) nextPutAll: stringToSave; close]!

Item was changed:
  ----- Method: Arc>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying') -----
  displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm
  
+ 	| nSegments line angle sin cos xn yn |
- 	| nSegments line angle sin cos xn yn xn1 yn1 |
  	nSegments := 12.0.
  	line := Line new.
  	line form: self form.
  	angle := 90.0 / nSegments.
  	sin := (angle * (2 * Float pi / 360.0)) sin.
  	cos := (angle * (2 * Float pi / 360.0)) cos.
  	quadrant = 1
  		ifTrue: 
  			[xn := radius asFloat.
  			yn := 0.0].
  	quadrant = 2
  		ifTrue: 
  			[xn := 0.0.
  			yn := 0.0 - radius asFloat].
  	quadrant = 3
  		ifTrue: 
  			[xn := 0.0 - radius asFloat.
  			yn := 0.0].
  	quadrant = 4
  		ifTrue: 
  			[xn := 0.0.
  			yn := radius asFloat].
  	nSegments asInteger
  		timesRepeat: 
+ 			[ | xn1 yn1 |
+ 			xn1 := xn * cos + (yn * sin).
- 			[xn1 := xn * cos + (yn * sin).
  			yn1 := yn * cos - (xn * sin).
  			line beginPoint: center + (xn asInteger @ yn asInteger).
  			line endPoint: center + (xn1 asInteger @ yn1 asInteger).
  			line
  				displayOn: aDisplayMedium
  				at: aPoint
  				clippingBox: clipRect
  				rule: anInteger
  				fillColor: aForm.
  			xn := xn1.
  			yn := yn1]!

Item was changed:
  ----- Method: ParagraphEditor>>explain (in category 'menu messages') -----
  explain
  	"Try to shed some light on what kind of entity the current selection
  is. 
  	The selection must be a single token or construct. Insert the answer
  after 
  	the selection. Send private messages whose names begin with 'explain' 
  	that return a string if they recognize the selection, else nil."
  
+ 	
- 	| string tiVars cgVars selectors delimitors numbers sorry reply symbol
- |
  Cursor execute showWhile: 
+ 			[ | symbol string delimitors reply numbers tiVars selectors sorry cgVars |
+ 			sorry := '"Sorry, I can''t explain that.  Please select a single
- 			[sorry := '"Sorry, I can''t explain that.  Please select a single
  token, construct, or special character.'.
  			sorry := sorry , (view canDiscardEdits
  							ifFalse: ['  Also, please cancel or accept."']
  							ifTrue: ['"']).
  			(string := self selection asString) isEmpty
  				ifTrue: [reply := '']
  				ifFalse: [string := self explainScan: string.
  					"Remove space, tab, cr"
  					"Temps and Instance vars need only test strings that are all
  letters"
  					(string detect: [:char | (char isLetter or: [char isDigit]) not]
  						ifNone: []) ifNil: 
  							[tiVars := self explainTemp: string.
  							tiVars == nil ifTrue: [tiVars := self explainInst: string]].
  					(tiVars == nil and: [model respondsTo: #explainSpecial:])
  						ifTrue: [tiVars := model explainSpecial: string].
  					tiVars == nil
  						ifTrue: [tiVars := '']
  						ifFalse: [tiVars := tiVars , '\' withCRs].
  					"Context, Class, Pool, and Global vars, and Selectors need 
  					only test symbols"
  					(Symbol hasInterned: string ifTrue: [:s | symbol := s])
  						ifTrue: [cgVars := self explainCtxt: symbol.
  							cgVars == nil
  								ifTrue: [cgVars := self explainClass: symbol.
  									cgVars == nil ifTrue: [cgVars := self explainGlobal: symbol]].
  							"See if it is a Selector (sent here or not)"
  							selectors := self explainMySel: symbol.
  							selectors == nil
  								ifTrue: 
  									[selectors := self explainPartSel: string.
  									selectors == nil ifTrue: [
  										selectors := self explainAnySel: symbol]]]
  						ifFalse: [selectors := self explainPartSel: string].
  					cgVars == nil
  						ifTrue: [cgVars := '']
  						ifFalse: [cgVars := cgVars , '\' withCRs].
  					selectors == nil
  						ifTrue: [selectors := '']
  						ifFalse: [selectors := selectors , '\' withCRs].
  					string size = 1
  						ifTrue: ["single special characters"
  							delimitors := self explainChar: string]
  						ifFalse: ["matched delimitors"
  							delimitors := self explainDelimitor: string].
  					numbers := self explainNumber: string.
  					numbers == nil ifTrue: [numbers := ''].
  					delimitors == nil ifTrue: [delimitors := ''].
  					reply := tiVars , cgVars , selectors , delimitors , numbers].
  			reply size = 0 ifTrue: [reply := sorry].
  			self afterSelectionInsertAndSelect: reply]!

Item was changed:
  ----- Method: MVCProject>>findProjectView: (in category 'utilities') -----
  findProjectView: projectDescription
  	"In this world, find the ProjectController for the project described by projectDescription."
  
+ 	| pName |
- 	| pName dpName proj |
  	pName := (projectDescription isString) 
  		ifTrue: [projectDescription]
  		ifFalse: [projectDescription name].
+ 	world scheduledControllers do: [:cont | | proj dpName |
- 	world scheduledControllers do: [:cont |
  		(cont isKindOf: ProjectController) ifTrue: [
  			((proj := cont model) class == Project and: 
  				[proj name = pName]) ifTrue: [^ cont view].
  			proj class == DiskProxy ifTrue: [ 
  				dpName := proj constructorArgs first.
  				dpName := (dpName findTokens: '/') last.
  				dpName := (Project parseProjectFileName: dpName unescapePercents) first.
  				dpName = pName ifTrue: [^ cont view]]]].
  	^ nil!

Item was changed:
  ----- Method: ParagraphEditor>>objectsReferencingIt (in category 'do-its') -----
  objectsReferencingIt
  	"Open a list inspector on all objects that reference the object that results when the current selection is evaluated.  "
+ 	
+ 	self terminateAndInitializeAround: [ | result |
- 	| result |
- 	self terminateAndInitializeAround: [
  	result := self evaluateSelection.
  	((result isKindOf: FakeClassPool) or: [result == #failedDoit])
  		ifTrue: [view flash]
  		ifFalse: [self systemNavigation
  					browseAllObjectReferencesTo: result
  					except: #()
  					ifNone: [:obj | view topView flash]].
  	]!

Item was changed:
  ----- Method: ParagraphEditor>>undoAgain:andReselect:typedKey: (in category 'undoers') -----
  undoAgain: indices andReselect: home typedKey: wasTypedKey
  	"The last command was again.  Undo it. Redoer: itself."
  
+ 	| findSize substText |
- 	| findSize substText index subject |
  	(self isRedoing & wasTypedKey) ifTrue: "redelete search key"
  		[self selectInterval: home.
  		self zapSelectionWith: self nullText].
  
  	findSize := (self isRedoing ifTrue: [FindText] ifFalse: [ChangeText]) size.
  	substText := self isUndoing ifTrue: [FindText] ifFalse: [ChangeText].
  	(self isUndoing ifTrue: [indices size to: 1 by: -1] ifFalse: [1 to: indices size]) do:
+ 		[:i | | index subject |
- 		[:i |
  		index := indices at: i.
  		(subject := index to: index + findSize - 1) = self selectionInterval ifFalse:
  			[self selectInterval: subject].
  		FindText == ChangeText ifFalse: [self zapSelectionWith: substText]].
  
  	self isUndoing
  		ifTrue:  "restore selection to where it was when 'again' was invoked"
  			[wasTypedKey
  				ifTrue: "search started by typing key at a caret; restore it"
  					[self selectAt: home first.
  					self zapSelectionWith: FindText.
  					self selectAt: home last + 1]
  				ifFalse: [self selectInterval: home]].
  
  	self undoMessage: UndoMessage forRedo: self isUndoing!




More information about the Squeak-dev mailing list