[squeak-dev] The Trunk: Tools-ul.279.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 16 04:16:24 UTC 2010


Levente Uzonyi uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-ul.279.mcz

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

Name: Tools-ul.279
Author: ul
Time: 16 November 2010, 5:15:38.602 am
UUID: 583987ca-82be-1f4a-9b4e-1707cf6e2c8e
Ancestors: Tools-ul.277

- use #= for integer comparison instead of #== (http://bugs.squeak.org/view.php?id=2788 )

=============== Diff against Tools-ul.277 ===============

Item was changed:
  ----- Method: Browser>>classListIndex: (in category 'class list') -----
  classListIndex: anInteger 
  	"Set anInteger to be the index of the current class selection."
  
  	| className currentMessageCategoryName currentMessageName |
  	currentMessageCategoryName := [self selectedMessageCategoryName]
  										on: Error
  										do: [:ex| ex return: nil].
  	currentMessageName := [self selectedMessageName]
  								on: Error
  								do: [:ex| ex return: nil].
  
  	classListIndex := anInteger.
  	self setClassOrganizer.
  
  	"Try to reselect the category and/or selector if the new class has them."
  	messageCategoryListIndex := self messageCategoryList
  										indexOf: currentMessageCategoryName
  										ifAbsent: [0].
  	messageListIndex := messageCategoryListIndex = 0
  							ifTrue: [0]
  							ifFalse: [self messageList
  										indexOf: currentMessageName
  										ifAbsent: [0]].
  
  	messageListIndex ~= 0 ifTrue:
  		[self editSelection: #editMessage] ifFalse:
  	[messageCategoryListIndex ~= 0 ifTrue:
  		[self editSelection: #newMessage] ifFalse:
  	[self classCommentIndicated
  		ifTrue: []
  		ifFalse: [self editSelection: (anInteger = 0
+ 					ifTrue: [(metaClassIndicated or: [ systemCategoryListIndex = 0 ])
- 					ifTrue: [metaClassIndicated | (systemCategoryListIndex == 0)
  						ifTrue: [#none]
  						ifFalse: [#newClass]]
  					ifFalse: [#editClass])]]].
  	contents := nil.
  	self selectedClass isNil
  		ifFalse: [className := self selectedClass name.
  					(RecentClasses includes: className)
  				ifTrue: [RecentClasses remove: className].
  			RecentClasses addFirst: className.
  			RecentClasses size > 16
  				ifTrue: [RecentClasses removeLast]].
  	self changed: #classSelectionChanged.
  	self changed: #classCommentText.
  	self changed: #classListIndex.	"update my selection"
  	self changed: #messageCategoryList.
  	self changed: #messageList.
  	self changed: #relabel.
  	self contentsChanged!

Item was changed:
  ----- Method: Browser>>recent (in category 'class list') -----
  recent
  	"Let the user select from a list of recently visited classes.  11/96 stp.
  	 12/96 di:  use class name, not classes themselves.
  	 : dont fall into debugger in empty case"
  
  	| className class recentList |
  	recentList := RecentClasses select: [:n | Smalltalk hasClassNamed: n].
+ 	recentList size = 0 ifTrue: [^ Beeper beep].
- 	recentList size == 0 ifTrue: [^ Beeper beep].
  	className := UIManager default chooseFrom: recentList values: recentList.
  	className == nil ifTrue: [^ self].
  	class := Smalltalk at: className.
  	self selectCategoryForClass: class.
  	self classListIndex: (self classListIndexOf: class name)!

Item was changed:
  ----- Method: Browser>>removeMessage (in category 'message functions') -----
  removeMessage
  	"If a message is selected, create a Confirmer so the user can verify that  
  	the currently selected message should be removed from the system. If 
  	so,  
  	remove it. If the Preference 'confirmMethodRemoves' is set to false, the 
  	confirmer is bypassed."
  	| messageName confirmation |
  	messageListIndex = 0
  		ifTrue: [^ self].
  	self okToChange
  		ifFalse: [^ self].
  	messageName := self selectedMessageName.
  	confirmation := self systemNavigation   confirmRemovalOf: messageName on: self selectedClassOrMetaClass.
+ 	confirmation = 3
- 	confirmation == 3
  		ifTrue: [^ self].
  	self selectedClassOrMetaClass removeSelector: messageName.
  	self messageListIndex: 0.
  	self changed: #messageList.
  	self setClassOrganizer.
  	"In case organization not cached"
+ 	confirmation = 2
- 	confirmation == 2
  		ifTrue: [self systemNavigation browseAllCallsOn: messageName]!

Item was changed:
  ----- Method: ChangeList class>>browseRecentLogOn:startingFrom: (in category 'public access') -----
  browseRecentLogOn: origChangesFile startingFrom: initialPos 
  	"Prompt with a menu of how far back to go when browsing a changes file."
  
  	| end banners positions pos chunk i changesFile |
  	changesFile := origChangesFile readOnlyCopy.
  	banners := OrderedCollection new.
  	positions := OrderedCollection new.
  	end := changesFile size.
  	changesFile setConverterForCode.
  	pos := initialPos.
  	[pos = 0
  		or: [banners size > 20]]
  		whileFalse: [changesFile position: pos.
  			chunk := changesFile nextChunk.
  			i := chunk indexOfSubCollection: 'priorSource: ' startingAt: 1.
  			i > 0
  				ifTrue: [positions addLast: pos.
  					banners
  						addLast: (chunk copyFrom: 5 to: i - 2).
  					pos := Number
  								readFrom: (chunk copyFrom: i + 13 to: chunk size)]
  				ifFalse: [pos := 0]].
  	changesFile close.
+ 	banners size = 0 ifTrue: [^ self inform: 
- 	banners size == 0 ifTrue: [^ self inform: 
  'this image has never been saved
  since changes were compressed' translated].
  	pos := UIManager default chooseFrom:  banners values: positions title: 'Browse as far back as...' translated.
  	pos ifNil: [^ self].
  	self browseRecent: end - pos on: origChangesFile!

Item was changed:
  ----- Method: ChangeList>>browseAllVersionsOfSelections (in category 'menu actions') -----
  browseAllVersionsOfSelections
  	"Opens a Versions browser on all the currently selected methods, showing each alongside all of their historical versions."
  	|  oldSelection aList |
  	oldSelection := self listIndex.
  	aList := OrderedCollection new.
  	Cursor read showWhile: [
  		1 to: changeList size do: [:i |
  			(listSelections at: i) ifTrue: [
  				listIndex := i.
  				self browseVersions.
  				aList add: i.
  				]]].
  	listIndex := oldSelection.
  
+ 	aList size = 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts'].
- 	aList size == 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts'].
  !

Item was changed:
  ----- Method: ChangeList>>browseCurrentVersionsOfSelections (in category 'menu actions') -----
  browseCurrentVersionsOfSelections
  	"Opens a message-list browser on the current in-memory versions of all methods that are currently seleted"
  	| aList |
  	aList := OrderedCollection new.
  	Cursor read showWhile: [
  		1 to: changeList size do: [:i |
  			(listSelections at: i) ifTrue: [
  				| aClass aChange |
  				aChange := changeList at: i.
  				(aChange type = #method
  					and: [(aClass := aChange methodClass) notNil
  					and: [aClass includesSelector: aChange methodSelector]])
  						ifTrue: [
  							aList add: (
  								MethodReference new
  									setStandardClass: aClass  
  									methodSymbol: aChange methodSelector
  							)
  						]]]].
  
+ 	aList size = 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts'].
- 	aList size == 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts'].
  	ToolSet
  		browseMessageSet: aList
  		name: 'Current versions of selected methods in ', file localName
  		autoSelect: nil!

Item was changed:
  ----- Method: ChangeList>>removeNonSelections (in category 'menu actions') -----
  removeNonSelections
  	"Remove the unselected items from the receiver."
  
  	| newChangeList newList |
  
  	newChangeList := OrderedCollection new.
  	newList := OrderedCollection new.
  
  	1 to: changeList size do:
  		[:i | (listSelections at: i) ifTrue:
  			[newChangeList add: (changeList at: i).
  			newList add: (list at: i)]].
+ 	newChangeList size = 0 ifTrue:
- 	newChangeList size == 0 ifTrue:
  		[^ self inform: 'That would remove everything.
  Why would you want to do that?'].
  
  	newChangeList size < changeList size
  		ifTrue:
  			[changeList := newChangeList.
  			list := newList.
  			listIndex := 0.
  			listSelections := Array new: list size withAll: false].
  	self changed: #list
  
  	!

Item was changed:
  ----- Method: ChangeSorter class>>browseChangeSetsWithClass:selector: (in category 'browse') -----
  browseChangeSetsWithClass: class selector: selector
  	"Put up a menu comprising a list of change sets that hold changes for the given class and selector.  If the user selects one, open a single change-sorter onto it"
  
  	| hits index |
  	hits := self allChangeSets select: 
  		[:cs | (cs atSelector: selector class: class) ~~ #none].
  	hits isEmpty ifTrue: [^ self inform: class name, '.', selector , '
  is not in any change set'].
+ 	index := hits size = 1
- 	index := hits size == 1
  		ifTrue:	[1]
  		ifFalse:	[(UIManager default chooseFrom: (hits collect: [:cs | cs name])
  					lines: #())].
  	index = 0 ifTrue: [^ self].
  	(ChangeSorter new myChangeSet: (hits at: index)) open.
  !

Item was changed:
  ----- Method: ChangeSorter class>>browseChangeSetsWithSelector: (in category 'browse') -----
  browseChangeSetsWithSelector: aSelector
  	"Put up a list of all change sets that contain an addition, deletion, or change of any method with the given selector"
  
  	| hits index |
  	hits := self allChangeSets select: 
  		[:cs | cs hasAnyChangeForSelector: aSelector].
  	hits isEmpty ifTrue: [^ self inform: aSelector , '
  is not in any change set'].
+ 	index := hits size = 1
- 	index := hits size == 1
  		ifTrue:	[1]
  		ifFalse:	[(UIManager default chooseFrom: (hits collect: [:cs | cs name])
  					lines: #())].
  	index = 0 ifTrue: [^ self].
  	(ChangeSetBrowser new myChangeSet: (hits at: index)) open
  
  "ChangeSorter browseChangeSetsWithSelector: #clearPenTrails"
  !

Item was changed:
  ----- Method: ChangeSorter>>contents:notifying: (in category 'code pane') -----
  contents: aString notifying: aController 
  	"Compile the code in aString. Notify aController of any syntax errors. 
  	Create an error if the category of the selected message is unknown. 
  	Answer false if the compilation fails. Otherwise, if the compilation 
  	created a new method, deselect the current selection. Then answer true."
  	| category selector class oldSelector |
  
  	(class := self selectedClassOrMetaClass) ifNil:
+ 		[(myChangeSet preambleString == nil or: [aString size = 0]) ifTrue: [ ^ false].
- 		[(myChangeSet preambleString == nil or: [aString size == 0]) ifTrue: [ ^ false].
  		(aString count: [:char | char == $"]) odd 
  			ifTrue: [self inform: 'unmatched double quotes in preamble']
  			ifFalse: [(Scanner new scanTokens: aString) size > 0 ifTrue: [
  				self inform: 'Part of the preamble is not within double-quotes.
  To put a double-quote inside a comment, type two double-quotes in a row.
  (Ignore this warning if you are including a doIt in the preamble.)']].
  		myChangeSet preambleString: aString.
  		self currentSelector: nil.  "forces update with no 'unsubmitted chgs' feedback"
  		^ true].
  	oldSelector := self selectedMessageName.
  	category := class organization categoryOfElement: oldSelector.
  	selector := class compile: aString
  				classified: category
  				notifying: aController.
  	selector ifNil: [^ false].
  	(self messageList includes: selector)
  		ifTrue: [self currentSelector: selector]
  		ifFalse: [self currentSelector: oldSelector].
  	self update.
  	^ true!

Item was changed:
  ----- Method: ChangeSorter>>removeMessage (in category 'message list') -----
  removeMessage
  	"Remove the selected msg from the system. Real work done by the 
  	parent, a ChangeSorter"
  	| confirmation sel |
  	self okToChange
  		ifFalse: [^ self].
  	currentSelector
  		ifNotNil: [confirmation := self systemNavigation   confirmRemovalOf: (sel := self selectedMessageName) on: self selectedClassOrMetaClass.
+ 			confirmation = 3
- 			confirmation == 3
  				ifTrue: [^ self].
  			self selectedClassOrMetaClass removeSelector: sel.
  			self update.
+ 			confirmation = 2
- 			confirmation == 2
  				ifTrue: [self systemNavigation browseAllCallsOn: sel]]!

Item was changed:
  ----- Method: ChangeSorter>>rename (in category 'changeSet menu') -----
  rename
  	"Store a new name string into the selected ChangeSet.  reject duplicate name; allow user to back out"
  
  	| newName |
  	newName := UIManager default request: 'New name for this change set'
  						initialAnswer: myChangeSet name.
+ 	(newName = myChangeSet name or: [newName size = 0]) ifTrue:
- 	(newName = myChangeSet name or: [newName size == 0]) ifTrue:
  			[^ Beeper beep].
  
  	(self class changeSetNamed: newName) ifNotNil:
  			[^ Utilities inform: 'Sorry that name is already used'].
  
  	myChangeSet name: newName.
  	self update.
  	self changed: #mainButtonName.
  	self changed: #relabel.!

Item was changed:
  ----- Method: CodeHolder>>addPriorVersionsCountForSelector:ofClass:to: (in category 'annotation') -----
  addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream
  	"add an annotation detailing the prior versions count"
  	| versionsCount |
  
  	versionsCount := VersionsBrowser versionCountForSelector: aSelector class: aClass.
  	aStream nextPutAll: 
  				((versionsCount > 1
  					ifTrue:
+ 						[versionsCount = 2 ifTrue:
- 						[versionsCount == 2 ifTrue:
  							['1 prior version']
  							ifFalse:
  								[versionsCount printString, ' prior versions']]
  					ifFalse:
  						['no prior versions']), self annotationSeparator)!

Item was changed:
  ----- Method: CodeHolder>>annotationForSelector:ofClass: (in category 'annotation') -----
  annotationForSelector: aSelector ofClass: aClass 
  	"Provide a line of content for an annotation pane, representing  
  	information about the given selector and class"
  	| separator aStream requestList |
  	aSelector == #Comment
  		ifTrue: [^ self annotationForClassCommentFor: aClass].
  	aSelector == #Definition
  		ifTrue: [^ self annotationForClassDefinitionFor: aClass].
  	aSelector == #Hierarchy
  		ifTrue: [^ self annotationForHierarchyFor: aClass].
  	aStream := ReadWriteStream on: ''.
  	requestList := self annotationRequests.
  	separator := requestList size > 1
  				ifTrue: [self annotationSeparator]
  				ifFalse: [''].
  	requestList
  		do: [:aRequest | | aString sendersCount aComment aCategory implementorsCount aList stamp | 
  			aRequest == #firstComment
  				ifTrue: [aComment := aClass firstCommentAt: aSelector.
  					aComment isEmptyOrNil
  						ifFalse: [aStream nextPutAll: aComment , separator]].
  			aRequest == #masterComment
  				ifTrue: [aComment := aClass supermostPrecodeCommentFor: aSelector.
  					aComment isEmptyOrNil
  						ifFalse: [aStream nextPutAll: aComment , separator]].
  			aRequest == #documentation
  				ifTrue: [aComment := aClass precodeCommentOrInheritedCommentFor: aSelector.
  					aComment isEmptyOrNil
  						ifFalse: [aStream nextPutAll: aComment , separator]].
  			aRequest == #timeStamp
  				ifTrue: [stamp := self timeStamp.
  					aStream
  						nextPutAll: (stamp size > 0
  								ifTrue: [stamp , separator]
  								ifFalse: ['no timeStamp' , separator])].
  			aRequest == #messageCategory
  				ifTrue: [aCategory := aClass organization categoryOfElement: aSelector.
  					aCategory
  						ifNotNil: ["woud be nil for a method no longer present,  
  							e.g. in a recent-submissions browser"
  							aStream nextPutAll: aCategory , separator]].
  			aRequest == #sendersCount
  				ifTrue: [sendersCount := (self systemNavigation allCallsOn: aSelector) size.
+ 					sendersCount := sendersCount = 1
- 					sendersCount := sendersCount == 1
  								ifTrue: ['1 sender']
  								ifFalse: [sendersCount printString , ' senders'].
  					aStream nextPutAll: sendersCount , separator].
  			aRequest == #implementorsCount
  				ifTrue: [implementorsCount := self systemNavigation numberOfImplementorsOf: aSelector.
+ 					implementorsCount := implementorsCount = 1
- 					implementorsCount := implementorsCount == 1
  								ifTrue: ['1 implementor']
  								ifFalse: [implementorsCount printString , ' implementors'].
  					aStream nextPutAll: implementorsCount , separator].
  			aRequest == #priorVersionsCount
  				ifTrue: [self
  						addPriorVersionsCountForSelector: aSelector
  						ofClass: aClass
  						to: aStream].
  			aRequest == #priorTimeStamp
  				ifTrue: [stamp := VersionsBrowser
  								timeStampFor: aSelector
  								class: aClass
  								reverseOrdinal: 2.
  					stamp
  						ifNotNil: [aStream nextPutAll: 'prior time stamp: ' , stamp , separator]].
  			aRequest == #recentChangeSet
  				ifTrue: [aString := ChangesOrganizer mostRecentChangeSetWithChangeForClass: aClass selector: aSelector.
  					aString size > 0
  						ifTrue: [aStream nextPutAll: aString , separator]].
  			aRequest == #allChangeSets
  				ifTrue: [aList := ChangesOrganizer allChangeSetsWithClass: aClass selector: aSelector.
  					aList size > 0
  						ifTrue: [aList size = 1
  								ifTrue: [aStream nextPutAll: 'only in change set ']
  								ifFalse: [aStream nextPutAll: 'in change sets: '].
  							aList
  								do: [:aChangeSet | aStream nextPutAll: aChangeSet name , ' ']]
  						ifFalse: [aStream nextPutAll: 'in no change set'].
  					aStream nextPutAll: separator]].
  	^ aStream contents!

Item was changed:
  ----- Method: CodeHolder>>showUnreferencedClassVars (in category 'traits') -----
  showUnreferencedClassVars
  	"Search for all class variables known to the selected class, and put up a 
  	list of those that have no references anywhere in the system. The 
  	search includes superclasses, so that you don't need to navigate your 
  	way to the class that defines each class variable in order to determine 
  	whether it is unreferenced"
  	| cls aList aReport |
  	((cls := self selectedClass) isNil or: [cls isTrait]) ifTrue: [^ self].
  	aList := self systemNavigation allUnreferencedClassVariablesOf: cls.
+ 	aList size = 0
- 	aList size == 0
  		ifTrue: [^ self inform: 'There are no unreferenced
  class variables in
  ' , cls name].
  	aReport := String
  				streamContents: [:aStream | 
  					aStream nextPutAll: 'Unreferenced class variable(s) in ' , cls name;
  						 cr.
  					aList
  						do: [:el | aStream tab; nextPutAll: el; cr]].
  	Transcript cr; show: aReport.
  	UIManager default chooseFrom: aList values: aList 
  		title: 'Unreferenced
  class variables in 
  ' , cls name!

Item was changed:
  ----- Method: CodeHolder>>showUnreferencedInstVars (in category 'traits') -----
  showUnreferencedInstVars
  	"Search for all instance variables known to the selected class, and put up a list of those that have no references anywhere in the system.  The search includes superclasses, so that you don't need to navigate your way to the class that defines each inst variable in order to determine whether it is unreferenced"
  
  	| cls aList aReport |
  	((cls := self selectedClassOrMetaClass) isNil or: [cls isTrait]) ifTrue: [^ self].
  	aList := cls allUnreferencedInstanceVariables.
+ 	aList size = 0 ifTrue: [^ self inform: 'There are no unreferenced
- 	aList size == 0 ifTrue: [^ self inform: 'There are no unreferenced
  instance variables in
  ', cls name].
  	aReport := String streamContents:
  		[:aStream |
  			aStream nextPutAll: 'Unreferenced instance variable(s) in ', cls name; cr.
  			aList do: [:el | aStream tab; nextPutAll: el; cr]].
  	Transcript cr; show: aReport.
  	UIManager default chooseFrom: aList values: aList title: 'Unreferenced
  instance variables in 
  ', cls name!

Item was changed:
  ----- Method: CustomMenu>>invokeOn:orSendTo: (in category 'invocation') -----
  invokeOn: targetObject orSendTo: anObject
  	"Pop up this menu and return the result of sending to the target object the selector corresponding to the menu item selected by the user. Return  nil if no item is selected.  If the chosen selector has arguments, obtain appropriately.  If the recipient does not respond to the resulting message, send it to the alternate object provided"
  
  	| aSelector anIndex recipient |
  	^ (aSelector := self startUp) ifNotNil:
  		[anIndex := self selection.
  		recipient := ((targets := self targets) isEmptyOrNil or: [anIndex > targets size])
  			ifTrue:
  				[targetObject]
  			ifFalse:
  				[targets at: anIndex].
+ 		aSelector numArgs = 0
- 		aSelector numArgs == 0
  			ifTrue:
  				[recipient perform: aSelector orSendTo: anObject]
  			ifFalse:
  				[recipient perform: aSelector withArguments: (self arguments at: anIndex)]]!

Item was changed:
  ----- Method: FileContentsBrowser>>findClass (in category 'class list') -----
  findClass
  	| pattern foundClass classNames index foundPackage |
  	self okToChange ifFalse: [^ self classNotFound].
  	pattern := (UIManager default request: 'Class Name?') asLowercase.
  	pattern isEmpty ifTrue: [^ self].
  	classNames := Set new.
  	self packages do:[:p| classNames addAll: p classes keys].
  	classNames := classNames asArray select: 
  		[:n | (n asLowercase indexOfSubCollection: pattern startingAt: 1) > 0].
  	classNames isEmpty ifTrue: [^ self].
+ 	index := classNames size = 1
- 	index := classNames size == 1
  				ifTrue:	[1]
  				ifFalse:	[(UIManager default chooseFrom: classNames lines: #())].
  	index = 0 ifTrue: [^ self].
  	foundPackage := nil.
  	foundClass := nil.
  	self packages do:[:p| 
  		(p classes includesKey: (classNames at: index)) ifTrue:[
  			foundClass := p classes at: (classNames at: index).
  			foundPackage := p]].
  	foundClass isNil ifTrue:[^self].
   	self systemCategoryListIndex: (self systemCategoryList indexOf: foundPackage packageName asSymbol).
  	self classListIndex: (self classList indexOf: foundClass name). !

Item was changed:
  ----- Method: Inspector>>chasePointers (in category 'menu commands') -----
  chasePointers
  	| selected  saved |
+ 	self selectionIndex = 0 ifTrue: [^ self changed: #flash].
- 	self selectionIndex == 0 ifTrue: [^ self changed: #flash].
  	selected := self selection.
  	saved := self object.
  	[self object: nil.
  	(Smalltalk includesKey: #PointerFinder)
  		ifTrue: [PointerFinder on: selected]
  		ifFalse: [self inspectPointers]]
  		ensure: [self object: saved]!

Item was changed:
  ----- Method: Inspector>>inspectElement (in category 'menu commands') -----
  inspectElement
  	| sel selSize countString count nameStrs |
  	"Create and schedule an Inspector on an element of the receiver's model's currently selected collection."
  
  	self selectionIndex = 0 ifTrue: [^ self changed: #flash].
  	((sel := self selection) isKindOf: SequenceableCollection) ifFalse:
  		[(sel isKindOf: MorphExtension) ifTrue: [^ sel inspectElement].
  		^ sel inspect].
+ 	(selSize := sel size) = 1 ifTrue: [^ sel first inspect].
- 	(selSize := sel size) == 1 ifTrue: [^ sel first inspect].
  	selSize <= 20 ifTrue:
  		[nameStrs := (1 to: selSize) asArray collect: [:ii | 
  			ii printString, '   ', (((sel at: ii) printStringLimitedTo: 25) replaceAll: Character cr with: Character space)].
  		count := UIManager default chooseFrom: (nameStrs substrings) title: 'which element?'.
  		count = 0 ifTrue: [^ self].
  		^ (sel at: count) inspect].
  
  	countString := UIManager default request: 'Which element? (1 to ', selSize printString, ')' initialAnswer: '1'.
  	countString isEmptyOrNil ifTrue: [^ self].
  	count := Integer readFrom: (ReadStream on: countString).
  	(count > 0 and: [count <= selSize])
  		ifTrue: [(sel at: count) inspect]
  		ifFalse: [Beeper beep]!

Item was changed:
  ----- Method: Inspector>>objectReferencesToSelection (in category 'menu commands') -----
  objectReferencesToSelection
  	"Open a list inspector on all the objects that point to the value of the selected instance variable, if any.  "
  
+ 	self selectionIndex = 0 ifTrue: [^ self changed: #flash].
- 	self selectionIndex == 0 ifTrue: [^ self changed: #flash].
  	self systemNavigation
  		browseAllObjectReferencesTo: self selection
  		except: (Array with: self object)
  		ifNone: [:obj | self changed: #flash].
  !

Item was changed:
  ----- Method: Inspector>>viewerForValue (in category 'menu commands') -----
  viewerForValue
  	"Open up a viewer on the value of the receiver's current selection"
  
  	| objectToRepresent |
+ 	objectToRepresent := self selectionIndex = 0 ifTrue: [object] ifFalse: [self selection].
- 	objectToRepresent := self selectionIndex == 0 ifTrue: [object] ifFalse: [self selection].
  	objectToRepresent beViewed
  	!

Item was changed:
  ----- Method: MessageNames>>messageList (in category 'selector list') -----
  messageList
  	"Answer the receiver's message list, computing it if necessary. The way 
  	to force a recomputation is to set the messageList to nil"
  	messageList
+ 		ifNil: [messageList := selectorListIndex = 0
- 		ifNil: [messageList := selectorListIndex == 0
  						ifTrue: [#()]
  						ifFalse: [self systemNavigation
  								allImplementorsOf: (selectorList at: selectorListIndex)].
  			self
  				messageListIndex: (messageList size > 0
  						ifTrue: [1]
  						ifFalse: [0])].
  	^ messageList!

Item was changed:
  ----- Method: MessageSet>>filterToMessagesInChangesFile (in category 'filtering') -----
  filterToMessagesInChangesFile
  	"Filter down only to messages whose source code risides in the Changes file.  This allows one to ignore long-standing methods that live in the .sources file."
  
  	
  	self filterFrom:
  		[:aClass :aSelector | | cm |
  			aClass notNil and: [aSelector notNil and:
  				[(self class isPseudoSelector: aSelector) not and:
  					[(cm := aClass compiledMethodAt: aSelector ifAbsent: [nil]) notNil and:
+ 					[cm fileIndex ~= 1]]]]]!
- 					[cm fileIndex ~~ 1]]]]]!

Item was changed:
  ----- Method: MessageSet>>filterToMessagesInSourcesFile (in category 'filtering') -----
  filterToMessagesInSourcesFile
  	"Filter down only to messages whose source code resides in the .sources file."
  
  	
  	self filterFrom: [:aClass :aSelector | | cm |
  		(aClass notNil and: [aSelector notNil]) and:
  			[(self class isPseudoSelector: aSelector) not and:
  				[(cm := aClass compiledMethodAt: aSelector ifAbsent: [nil]) notNil and:
+ 					[cm fileIndex = 1]]]]!
- 					[cm fileIndex == 1]]]]!

Item was changed:
  ----- Method: MessageSet>>removeMessage (in category 'message functions') -----
  removeMessage
  	"Remove the selected message from the system. 1/15/96 sw"
  	| messageName confirmation |
  	messageListIndex = 0
  		ifTrue: [^ self].
  	self okToChange
  		ifFalse: [^ self].
  	messageName := self selectedMessageName.
  	confirmation := self systemNavigation  confirmRemovalOf: messageName on: self selectedClassOrMetaClass.
+ 	confirmation = 3
- 	confirmation == 3
  		ifTrue: [^ self].
  	self selectedClassOrMetaClass removeSelector: messageName.
  	self deleteFromMessageList: self selection.
  	self reformulateList.
+ 	confirmation = 2
- 	confirmation == 2
  		ifTrue: [self systemNavigation browseAllCallsOn: messageName]!

Item was changed:
  ----- Method: MessageSet>>setFilteredList: (in category 'private') -----
  setFilteredList: newList 
  	"Establish newList as the new list if appropriate, and adjust the window title accordingly; if the new list is of the same size as the old, warn and do nothing"
+ 	newList size = 0 ifTrue:
- 	newList size == 0 ifTrue:
  		[ self inform: 'Nothing would be left in the list if you did that'.
  		^false ].
+ 	newList size = messageList size ifTrue:
- 	newList size == messageList size ifTrue:
  		[ self inform: 'That leaves the list unchanged'.
  		^false ].
  	self
  		 initializeMessageList: newList ;
  		 adjustWindowTitleAfterFiltering.
  	^true!

Item was changed:
  ----- Method: SelectionMenu class>>fromArray: (in category 'instance creation') -----
  fromArray: anArray
  	"Construct a menu from anArray.  The elements of anArray must be either:
  	*  A pair of the form: <label> <selector>
  or	*  The 'dash' (or 'minus sign') symbol
  
  	Refer to the example at the bottom of the method"
  
  	| labelList lines selections anIndex |
  	labelList := OrderedCollection new.
  	lines := OrderedCollection new.
  	selections := OrderedCollection new.
  	anIndex := 0.
  	anArray do:
  		[:anElement |
+ 			anElement size = 1
- 			anElement size == 1
  				ifTrue:
  					[(anElement == #-) ifFalse: [self error: 'badly-formed menu constructor'].
  					lines add: anIndex]
  				ifFalse:
+ 					[anElement size = 2 ifFalse: [self error: 'badly-formed menu constructor'].
- 					[anElement size == 2 ifFalse: [self error: 'badly-formed menu constructor'].
  					anIndex := anIndex + 1.
  					labelList add: anElement first.
  					selections add: anElement second]].
  	^ self labelList: labelList lines: lines selections: selections
  
  "(SelectionMenu fromArray:
  	#(	('first label'		moja)
  		('second label'	mbili)
  		-
  		('third label' 	tatu)
  		-
  		('fourth label'	nne)
  		('fifth label'	tano))) startUp"!

Item was changed:
  ----- Method: StringHolder>>messageListSelectorTitle (in category '*Tools') -----
  messageListSelectorTitle
  	| selector aString aStamp aSize |
  
  	(selector := self selectedMessageName)
  		ifNil:
  			[aSize := self messageList size.
+ 			^ (aSize = 0 ifTrue: ['no'] ifFalse: [aSize printString]), ' message', (aSize = 1 ifTrue: [''] ifFalse: ['s'])]
- 			^ (aSize == 0 ifTrue: ['no'] ifFalse: [aSize printString]), ' message', (aSize == 1 ifTrue: [''] ifFalse: ['s'])]
  		ifNotNil:
  			[Preferences timeStampsInMenuTitles
  				ifFalse:	[^ nil].
  			aString := selector truncateWithElipsisTo: 28.
  			^ (aStamp := self timeStamp) size > 0
  				ifTrue:
  					[aString, String cr, aStamp]
  				ifFalse:
  					[aString]]!

Item was changed:
  ----- Method: StringHolder>>withSelectorAndMessagesIn:evaluate: (in category '*Tools') -----
  withSelectorAndMessagesIn: aCompiledMethod evaluate: aBlock
  	"Allow the user to choose one selector, chosen from the currently selected message's selector, as well as those of all messages sent by it, and evaluate aBlock on behalf of chosen selector.  If there is only one possible choice, simply make it; if there are multiple choices, put up a menu, and evaluate aBlock on behalf of the the chosen selector, doing nothing if the user declines to choose any"
  
  	| selectorOrNil litGetter messages |
  	selectorOrNil := aCompiledMethod selector.
  	messages := Preferences thoroughSenders
  					ifTrue:
  						[litGetter := [:set :l|
  										(l isSymbol and: [l size > 0 and: [l first isLowercase]]) ifTrue:
  											[set add: l].
  										l isArray ifTrue:
  											[l inject: set into: litGetter copy].
  										set].
  						aCompiledMethod allLiterals
  						, (aCompiledMethod pragmas collect: [:pragma| pragma keyword])
  							inject: aCompiledMethod messages into: litGetter copy]
  					ifFalse: [aCompiledMethod messages].
  	(messages isEmpty	"if no messages, use only selector"
+ 	or: [messages size = 1 and: [messages includes: selectorOrNil]]) ifTrue:
- 	or: [messages size == 1 and: [messages includes: selectorOrNil]]) ifTrue:
  		[^selectorOrNil ifNotNil: [aBlock value: selectorOrNil]].  "If only one item, there is no choice"
  
  	self systemNavigation 
  		showMenuOf: messages
  		withFirstItem: selectorOrNil
  		ifChosenDo: [:sel | aBlock value: sel]!

Item was changed:
  ----- Method: Utilities class>>browseRecentSubmissions (in category '*Tools') -----
  browseRecentSubmissions
  	"Open up a browser on the most recent methods submitted in the image.  5/96 sw."
  
  	"Utilities browseRecentSubmissions"
  
  	| recentMessages |
  
+ 	self recentMethodSubmissions size = 0 ifTrue:
- 	self recentMethodSubmissions size == 0 ifTrue:
  		[^ self inform: 'There are no recent submissions'].
  	
  	recentMessages := RecentSubmissions copy reversed.
  	RecentMessageSet 
  		openMessageList: recentMessages 
  		name: 'Recent submissions -- youngest first ' 
  		autoSelect: nil!

Item was changed:
  ----- Method: VersionsBrowser>>addPriorVersionsCountForSelector:ofClass:to: (in category 'misc') -----
  addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream
  	"Add an annotation detailing the prior versions count.  Specially handled here for the case of a selector no longer in the system, whose prior versions are seen in a versions browser -- in this case, the inherited version of this method will not work."
  
  	(aClass includesSelector: aSelector) ifTrue:
  		[^ super addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream].
  
  	aStream nextPutAll: 
  		((changeList size > 0
  			ifTrue:
+ 				[changeList size = 1
- 				[changeList size == 1
  					ifTrue:
  						['Deleted - one prior version']
  					ifFalse:
  						['Deleted - ', changeList size printString, ' prior versions']]
  			ifFalse:
  				['surprisingly, no prior versions']), self annotationSeparator)!

Item was changed:
  ----- Method: VersionsBrowser>>scanVersionsOf:class:meta:category:selector: (in category 'init & update') -----
  scanVersionsOf: method class: class meta: meta category: category selector: selector
  	| position prevPos prevFileIndex preamble tokens sourceFilesCopy stamp cat |
  	selectorOfMethod := selector.
  	currentCompiledMethod := method.
  	classOfMethod := meta ifTrue: [class class] ifFalse: [class].
  	cat := category ifNil: [''].
  	changeList := OrderedCollection new.
  	list := OrderedCollection new.
  	self addedChangeRecord ifNotNil: [ :change |
  		self addItem: change text: ('{1} (in {2})' translated format: { change stamp. change fileName }) ].
  	listIndex := 0.
  	position := method filePosition.
  	sourceFilesCopy := SourceFiles collect:
  		[:x | x isNil ifTrue: [ nil ]
  				ifFalse: [x readOnlyCopy]].
+ 	method fileIndex = 0 ifTrue: [^ nil].
- 	method fileIndex == 0 ifTrue: [^ nil].
  	file := sourceFilesCopy at: method fileIndex.
  
  	[position notNil & file notNil]
  		whileTrue:
  		[preamble := method getPreambleFrom: file at: (0 max: position - 3).
  
  		"Preamble is likely a linked method preamble, if we're in
  			a changes file (not the sources file).  Try to parse it
  			for prior source position and file index"
  		prevPos := nil.
  		stamp := ''.
  		(preamble findString: 'methodsFor:' startingAt: 1) > 0
  			ifTrue: [tokens := Scanner new scanTokens: preamble]
  			ifFalse: [tokens := Array new  "ie cant be back ref"].
  		((tokens size between: 7 and: 8)
+ 			and: [(tokens at: tokens size - 5) = #methodsFor:])
- 			and: [(tokens at: tokens size-5) = #methodsFor:])
  			ifTrue:
+ 				[(tokens at: tokens size - 3) = #stamp:
- 				[(tokens at: tokens size-3) = #stamp:
  				ifTrue: ["New format gives change stamp and unified prior pointer"
+ 						stamp := tokens at: tokens size - 2.
- 						stamp := tokens at: tokens size-2.
  						prevPos := tokens last.
  						prevFileIndex := sourceFilesCopy fileIndexFromSourcePointer: prevPos.
  						prevPos := sourceFilesCopy filePositionFromSourcePointer: prevPos]
  				ifFalse: ["Old format gives no stamp; prior pointer in two parts"
+ 						prevPos := tokens at: tokens size - 2.
- 						prevPos := tokens at: tokens size-2.
  						prevFileIndex := tokens last].
+ 				cat := tokens at: tokens size - 4.
- 				cat := tokens at: tokens size-4.
  				(prevPos = 0 or: [prevFileIndex = 0]) ifTrue: [prevPos := nil]].
  		((tokens size between: 5 and: 6)
+ 			and: [(tokens at: tokens size - 3) = #methodsFor:])
- 			and: [(tokens at: tokens size-3) = #methodsFor:])
  			ifTrue:
+ 				[(tokens at: tokens size - 1) = #stamp:
- 				[(tokens at: tokens size-1) = #stamp:
  				ifTrue: ["New format gives change stamp and unified prior pointer"
  						stamp := tokens at: tokens size].
+ 				cat := tokens at: tokens size - 2].
- 				cat := tokens at: tokens size-2].
   		self addItem:
  				(ChangeRecord new file: file position: position type: #method
  						class: class name category: category meta: meta stamp: stamp)
  			text: stamp , ' ' , class name , (meta ifTrue: [' class '] ifFalse: [' ']) , selector, ' {', cat, '}'.
  		position := prevPos.
  		prevPos notNil ifTrue:
  			[file := sourceFilesCopy at: prevFileIndex]].
  	sourceFilesCopy do: [:x | x notNil ifTrue: [x close]].
  	listSelections := Array new: list size withAll: false!




More information about the Squeak-dev mailing list