[bug][fix] selector finder in 2.5

Mark Guzdial guzdial at cc.gatech.edu
Thu Aug 19 16:41:42 UTC 1999


I found two bugs in SelectorFinder in 2.5:
- I found that the ability to provide arguments and an answer was broken in
MVC.  Maybe it never worked, since MethodFinder looks for the
SelectionFinder explicitly in the WorldMorph and stuffs the answer in
directly.
- I also found that if you got the arguments and answer wrong (say, left
out the periods), the SelectorFinder became unusable.  This was because the
error returned ^self inform: 'error message' -- which returns self.  Thus,
the selection list became filled with the browser, which never understood
isEmpty.

The below changeset fixes both of these -- SelectorFinder works in MVC as
in Morphic, and the error condition doesn't mess up the browser window.

Mark

'From Squeak 2.5 of August 6, 1999 on 19 August 1999 at 12:38:07 pm'!

!MethodFinder methodsFor: 'search' stamp: 'mjg 8/19/1999 12:29'!
findMessage
	"Control the search."

	| selFinder |
	data do: [:alist |
		(alist isKindOf: SequenceableCollection) ifFalse: [
			^ 'first and third items are not Arrays']].
	Approved ifNil: [self initialize].	"Sets of allowed selectors"
	expressions _ WriteStream on: (String new: 400).
	self search: true.	"multi"
	Smalltalk isMorphic ifTrue: [
		((selFinder _ World submorphs first model) isKindOf:
SelectorBrowser) ifTrue: [
			selFinder selectorList: selector asSortedArray]].
	selector isEmpty ifTrue: [^ 'no single method does that function'].
	^ expressions contents
			! !

!MethodFinder methodsFor: 'search' stamp: 'mjg 8/19/1999 12:11'!
findMessageForDisplay
	"Do search for the SelectorBrowser the search."

	self findMessage.
	^ selector asSortedArray
			! !


!MethodFinder class methodsFor: 'as yet unclassified' stamp: 'mjg 8/19/1999
12:11'!
methodForDisplay: dataAndAnswers
	"Return an expression that computes these answers."

	^ (self new) load: dataAndAnswers; findMessageForDisplay! !


!SelectorBrowser methodsFor: 'as yet unclassified' stamp: 'mjg 8/19/1999
12:36'!
quickList
	"Compute the selectors for the single example of receiver and args,
in the very top pane"

	| data array ccc where mfresults|
	ccc _ data _ contents asString.
	"delete trailing period"
	data last isSeparator ifTrue: [data _ data allButLast].
	data last isSeparator ifTrue: [data _ data allButLast].
	data last = $. ifTrue: [data _ data allButLast].
	"enclose args in one more level"
	where _ 0.
	data size to: 1 by: -1 do: [:ii |
		(data at: ii) = $. ifTrue: [
			(data at: ii+1) isDigit ifFalse: [
				where = 0 ifTrue: [where _ ii]]]].
	where = 0 ifTrue: [self inform: 'If you are giving an example of
receiver, \args, and result, please put periods between the
parts.\Otherwise just type one selector fragment' withCRs. ^''].
	data _ data copyReplaceFrom: where to: where-1 with: '}'.
		"enclose args in { }"
	array _ Compiler evaluate: '{{', data, '}'.		"eval"
	mfresults _ (MethodFinder methodForDisplay: array).
	self selectorList: mfresults.
	self contents: ccc.	"restore top pane, since MethodFinder
clears it"
	^ selectorList! !

!SelectorBrowser methodsFor: 'as yet unclassified' stamp: 'mjg 8/19/1999
12:30'!
selectorList: anExternalList

	self contents: ''.
	classList _ #().  classListIndex _ 0.
	selectorIndex _ 0.
	selectorList _ anExternalList.
	self changed: #messageList.
	self changed: #classList.
	Smalltalk isMorphic ifTrue: [self changed: #contents.].

! !



--------------------------
Mark Guzdial : Georgia Tech : College of Computing : Atlanta, GA 30332-0280
(404) 894-5618 : Fax (404) 894-0673 : guzdial at cc.gatech.edu
http://www.cc.gatech.edu/gvu/people/Faculty/Mark.Guzdial.html





More information about the Squeak-dev mailing list