[enh]find globals for browser revised for v2.7a recent changes

Stephan B. Wessels stephan.wessels at sdrc.com
Thu Nov 11 14:58:50 UTC 1999


--------------0D7F3959188B6E6206076C81
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit


After looking over the most recent update to v2.7a I decided to modify my
approach to the find class of a global menu pick in Browser.  It's now a unique
menu pick with the associated methods factored as required.

  - Steve



--------------0D7F3959188B6E6206076C81
Content-Type: text/plain; charset=us-ascii;
 name="find global.11Nov953am.cs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="find global.11Nov953am.cs"


'From Squeak2.7alpha of 8 November 1999 [latest update: #1606] on 11 November 1999 at 9:53:59 am'!

!Browser methodsFor: 'system category functions' stamp: 'sbw 10/23/1999 17:44'!
classNotFound
	self changed: #flash.
	^nil! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:49'!
findClass
	| foundClass |
	foundClass _ self findClassQuery.
	self findClass: foundClass! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:49'!
findClass: aClass
	aClass isNil ifTrue: [^nil].
 	self systemCategoryListIndex: (self systemCategoryList indexOf: aClass category).
	self selectClass: aClass
! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:36'!
findClassQuery
	"Search for a class by name.  Answers the selected class name or nil."
	| pattern classNames index toMatch exactMatch potentialClassNames |
	self okToChange ifFalse: [^ self classNotFound].
	pattern _ FillInTheBlank request: 'Class name or fragment?'.
	pattern isEmpty ifTrue: [^ self classNotFound].
	toMatch _ (pattern copyWithout: $.) asLowercase.
	potentialClassNames _ self potentialClassNames asOrderedCollection.
	classNames _ pattern last = $. 
		ifTrue: [potentialClassNames select:
					[:nm |  nm asLowercase = toMatch]]
		ifFalse: [potentialClassNames select: 
					[:n | n includesSubstring: toMatch caseSensitive: false]].
	classNames isEmpty ifTrue: [^ self classNotFound].
	exactMatch _ classNames detect: [:each | each asLowercase = toMatch] ifNone: [nil].
	index _ classNames size = 1
		ifTrue:	[1]
		ifFalse:	[exactMatch
			ifNil: [(PopUpMenu labelArray: classNames lines: #()) startUp]
			ifNotNil: [classNames addFirst: exactMatch.
				(PopUpMenu labelArray: classNames lines: #(1)) startUp]].
	index = 0 ifTrue: [^ self classNotFound].
	^Smalltalk at: (classNames at: index) asSymbol! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:50'!
findGlobal
	| foundClass |
	foundClass _ self findGlobalQuery.
	self findClass: foundClass! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:44'!
findGlobalQuery
	"Search for a class by global variable name.  Answers the selected class name or nil."

	| globalName global className |
	self okToChange ifFalse: [^ self classNotFound].
	globalName _ FillInTheBlank request: 'Global name?'.
	globalName isEmpty ifTrue: [^ self classNotFound].
	(Smalltalk includesKey: globalName asSymbol) ifTrue: [
		global _ Smalltalk at: globalName asSymbol.
		(global isKindOf: Class) ifFalse: [
			className _ global class name.
			^Smalltalk at: className]].
	^self classNotFound! !

!Browser methodsFor: 'system category functions' stamp: 'sbw 11/11/1999 09:51'!
systemCategoryMenu: aMenu

^ aMenu labels:
'find class... (f)
find class of global...
recent classes...
browse all
browse
printOut
fileOut
reorganize
update
add item...
rename...
remove' 
	lines: #(3 5 7 9)
	selections:
		#(findClass findGlobal recent browseAllClasses buildSystemCategoryBrowser
		printOutSystemCategory fileOutSystemCategory
		editSystemCategories updateSystemCategories
		addSystemCategory renameSystemCategory removeSystemCategory )
! !



--------------0D7F3959188B6E6206076C81--





More information about the Squeak-dev mailing list