Skip to content

Commit

Permalink
fix ston replication issue with events
Browse files Browse the repository at this point in the history
The events inst var was being sent to the server via ston. Not a problem before but it was picking up a dialog in the recently added 'find method' code. This caused walkbacks. Fixed.
Added new tests for find method feature.
  • Loading branch information
Eric Winger authored and Eric Winger committed Jan 31, 2019
1 parent 5ebb8f8 commit 013283f
Show file tree
Hide file tree
Showing 7 changed files with 70 additions and 49 deletions.
5 changes: 5 additions & 0 deletions sources/JadeiteFindMethodDialog.cls
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,10 @@ ok
super ok.
!

onViewClosed
super onViewClosed.
self model value removeAllEventsTriggered!

onViewOpened

super onViewOpened.
Expand All @@ -46,6 +50,7 @@ updateList
!JadeiteFindMethodDialog categoriesFor: #createSchematicWiring!private! !
!JadeiteFindMethodDialog categoriesFor: #listPresenter!accessing!private! !
!JadeiteFindMethodDialog categoriesFor: #ok!event handlers!public! !
!JadeiteFindMethodDialog categoriesFor: #onViewClosed!event handlers!public! !
!JadeiteFindMethodDialog categoriesFor: #onViewOpened!event handlers!public! !
!JadeiteFindMethodDialog categoriesFor: #updateList!private! !

Expand Down
34 changes: 33 additions & 1 deletion sources/JadeiteProjectBrowserTestCase.cls
Original file line number Diff line number Diff line change
Expand Up @@ -1320,8 +1320,14 @@ test_findMethodDoesNotChangeCategories
self assert: self categoryListPresenter selection equals: 'Accessing'.
self assert: self methodListPresenter selection selector equals: #filters. !

test_findMethodDoesNothingWhenClassNotSelected
self testsIssue: #issue420 withTitle: 'Customer requests "Find Method" feature'.
self selectServiceNamed: 'Rowan' in: self projectListPresenter.
self selectServiceNamed: 'Rowan-Services-Core' in: self packageListPresenter.
self assert: self projectsPresenter findMethod equals: self projectsPresenter. "would normally raise a dialog" !

test_findMethodShowsAllMethods
| methodService methodListSize unopenedDialog |
| methodListSize unopenedDialog |
self testsIssue: #issue420 withTitle: 'Customer requests "Find Method" feature'.
self selectServiceNamed: 'Rowan' in: self projectListPresenter.
self selectServiceNamed: 'Rowan-Services-Core' in: self packageListPresenter.
Expand All @@ -1334,6 +1340,30 @@ test_findMethodShowsAllMethods
equals: self projectsPresenter selectedClass methods size.
self assert: unopenedDialog listPresenter list size > methodListSize!

test_findMethodShowsOnlyOneSide
| unopenedDialog |
self testsIssue: #issue420 withTitle: 'Customer requests "Find Method" feature'.
self selectServiceNamed: 'Rowan' in: self projectListPresenter.
self selectServiceNamed: 'Rowan-Services-Core' in: self packageListPresenter.
self selectServiceNamed: 'RowanService' in: self classListPresenter.
unopenedDialog := JadeiteFindMethodDialog create: 'DefaultView'
on: self projectsPresenter selectedClass.
self assertIsNil: (unopenedDialog listPresenter list
detect: [:methodService | methodService selector = #autoCommit]
ifNone: []).
self denyIsNil: (unopenedDialog listPresenter list
detect: [:methodService | methodService selector = #answer:]
ifNone: []).
self projectsPresenter selectClassTab.
unopenedDialog := JadeiteFindMethodDialog create: 'DefaultView'
on: self projectsPresenter selectedClass.
self denyIsNil: (unopenedDialog listPresenter list
detect: [:methodService | methodService selector = #autoCommit]
ifNone: []).
self assertIsNil: (unopenedDialog listPresenter list
detect: [:methodService | methodService selector = #answer:]
ifNone: []). !

test_gitBranchesDoesNotShowHead
"this may be a brittle test because it assumes RowanSample1 has only the master branch.
But it's based on the local checkout so the test runner can control this. "
Expand Down Expand Up @@ -3388,7 +3418,9 @@ waitForPresenter: presenter
!JadeiteProjectBrowserTestCase categoriesFor: #test_findClass!public!test class list!tests! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_findMethodChangesCategories!public!test categories! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_findMethodDoesNotChangeCategories!public!test categories! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_findMethodDoesNothingWhenClassNotSelected!public!tests! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_findMethodShowsAllMethods!public!tests! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_findMethodShowsOnlyOneSide!public!tests! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_gitBranchesDoesNotShowHead!public!test projects! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_goToDefinedClassFromClassList!public!test defined package! !
!JadeiteProjectBrowserTestCase categoriesFor: #test_goToDefinedClassFromHierarchy!public!test class hierarchy!test defined package! !
Expand Down
4 changes: 2 additions & 2 deletions sources/JadeiteProjectsBrowserPresenter.cls
Original file line number Diff line number Diff line change
Expand Up @@ -680,9 +680,9 @@ findClass
findMethod
self selectedClass isNil ifTrue: [^self].
^self class
browseMethodIn: gciSession
findMethodIn: gciSession
class: self selectedClass
presenter: self !
presenter: self!

findMethod: selector
"assume we have a populated method list"
Expand Down
14 changes: 7 additions & 7 deletions sources/Rowan UI Base.pax
Original file line number Diff line number Diff line change
Expand Up @@ -332,12 +332,12 @@ package methodNames
add: 'JadePresenter class' -> #browseImplementorsOf:session:;
add: 'JadePresenter class' -> #browseLiteralReferences:;
add: 'JadePresenter class' -> #browseLiteralReferences:session:;
add: 'JadePresenter class' -> #browseMethodIn:class:presenter:;
add: 'JadePresenter class' -> #browseMethodsContaining:;
add: 'JadePresenter class' -> #browseMethodsContaining:session:;
add: 'JadePresenter class' -> #browseSendersIn:;
add: 'JadePresenter class' -> #browseSendersOf:session:;
add: 'JadePresenter class' -> #convertToPattern:;
add: 'JadePresenter class' -> #findMethodIn:class:presenter:;
add: 'JadePresenter class' -> #issueCommand:session:;
add: 'JadePresenter class' -> #openDictionaryBrowserOn:session:;
add: 'JadePresenter class' -> #openGitHubJadeiteProject;
Expand Down Expand Up @@ -1877,11 +1877,6 @@ browseLiteralReferences: string session: session
shell updateCaptionFromSearchString: 'Literal References To ' , string asString printString.
^shell!

browseMethodIn: session class: classService presenter: browser
| methodService |
methodService := JadeiteFindMethodDialog showModal: 'DefaultView' on: classService.
^self basicBrowseMethod: methodService presenter: browser!

browseMethodsContaining: session
| string |
(string := Prompter prompt: 'Enter string:' caption: 'Browse Methods Containing ...') isNil
Expand Down Expand Up @@ -1925,6 +1920,11 @@ convertToPattern: wildcardString
wildcardString last = $* ifTrue: [list addLast: $*].
^list asArray!

findMethodIn: session class: classService presenter: browser
| methodService |
methodService := JadeiteFindMethodDialog showModal: 'DefaultView' on: classService.
^self basicBrowseMethod: methodService presenter: browser!

issueCommand: services session: session
^BrowserUpdate current issueCommand: services session: session!

Expand Down Expand Up @@ -2000,12 +2000,12 @@ symbolsFrom: selector session: session
!JadePresenter class categoriesFor: #browseImplementorsOf:session:!browsing!public! !
!JadePresenter class categoriesFor: #browseLiteralReferences:!browsing!public! !
!JadePresenter class categoriesFor: #browseLiteralReferences:session:!browsing!public! !
!JadePresenter class categoriesFor: #browseMethodIn:class:presenter:!browsing!public! !
!JadePresenter class categoriesFor: #browseMethodsContaining:!browsing!public! !
!JadePresenter class categoriesFor: #browseMethodsContaining:session:!browsing!public! !
!JadePresenter class categoriesFor: #browseSendersIn:!browsing!public! !
!JadePresenter class categoriesFor: #browseSendersOf:session:!browsing!public! !
!JadePresenter class categoriesFor: #convertToPattern:!browsing support!private! !
!JadePresenter class categoriesFor: #findMethodIn:class:presenter:!browsing!public! !
!JadePresenter class categoriesFor: #issueCommand:session:!public! !
!JadePresenter class categoriesFor: #openDictionaryBrowserOn:session:!browsing support!public! !
!JadePresenter class categoriesFor: #openGitHubJadeiteProject!browsing!public! !
Expand Down
19 changes: 1 addition & 18 deletions sources/RowanBrowserService.cls
Original file line number Diff line number Diff line change
Expand Up @@ -27,9 +27,7 @@ basicPrepareForReplication
ifNotNil: [removedMethods do: [:methodService | methodService basicPrepareForReplication]]!

excludedInstVars

^#( 'hierarchyServices' )
!
^super excludedInstVars , #('hierarchyServices')!

hash
^name hash!
Expand Down Expand Up @@ -88,20 +86,6 @@ removedMethods: anObject
replicateFrom: newService
self isBrowserService ifTrue: [super replicateFrom: newService]!

stonOn: stonWriter
| instanceVariableNames |
(instanceVariableNames := self class allInstVarNames reject: [:iv | self excludedInstVars includes: iv]) isEmpty
ifTrue: [stonWriter writeObject: self do: [stonWriter encodeMap: #()]]
ifFalse:
[stonWriter writeObject: self
streamMap:
[:dictionary |
instanceVariableNames do:
[:each |
(self instVarAt: (instanceVariableNames indexOf: each))
ifNotNil: [:value | dictionary at: each asSymbol put: value]
ifNil: [self stonShouldWriteNilInstVars ifTrue: [dictionary at: each asSymbol put: nil]]]]]!

testCount
^testCount!

Expand Down Expand Up @@ -140,7 +124,6 @@ testPackages: presenter
!RowanBrowserService categoriesFor: #removedMethods!accessing!private! !
!RowanBrowserService categoriesFor: #removedMethods:!accessing!private! !
!RowanBrowserService categoriesFor: #replicateFrom:!public!replication!updating! !
!RowanBrowserService categoriesFor: #stonOn:!must not strip!public!ston! !
!RowanBrowserService categoriesFor: #testCount!accessing!private! !
!RowanBrowserService categoriesFor: #testCount:!accessing!private! !
!RowanBrowserService categoriesFor: #testPackages:!public!updating! !
Expand Down
18 changes: 1 addition & 17 deletions sources/RowanClassService.cls
Original file line number Diff line number Diff line change
Expand Up @@ -135,7 +135,7 @@ displayStringFor: displayThing

excludedInstVars

^#( 'hierarchyServices' )
^super excludedInstVars, #( 'hierarchyServices' )
!

expand
Expand Down Expand Up @@ -311,21 +311,6 @@ shouldReplicateInstVarAtIndex: index newService: newService
(self class indexOfInstVar: 'methods') = index ifTrue: [newService meta = meta ifFalse: [^false]].
^true!

stonOn: stonWriter
| instanceVariableNames |
(instanceVariableNames := self class allInstVarNames
reject: [:iv | self excludedInstVars includes: iv]) isEmpty
ifTrue: [stonWriter writeObject: self do: [stonWriter encodeMap: #()]]
ifFalse:
[stonWriter writeObject: self
streamMap:
[:dictionary |
instanceVariableNames do:
[:each |
(self instVarNamed: each)
ifNotNil: [:value | dictionary at: each asSymbol put: value]
ifNil: [self stonShouldWriteNilInstVars ifTrue: [dictionary at: each asSymbol put: nil]]]]]!

sunitMethodsUpdate: presenter browser: browser
| selections oldClassService |
browser classListPresenter selections isEmpty ifTrue: [^self].
Expand Down Expand Up @@ -474,7 +459,6 @@ visibleTests
!RowanClassService categoriesFor: #selectedPackageServices:!accessing!private! !
!RowanClassService categoriesFor: #shouldColorAsExtension!public!testing! !
!RowanClassService categoriesFor: #shouldReplicateInstVarAtIndex:newService:!public!testing! !
!RowanClassService categoriesFor: #stonOn:!must not strip!public!ston! !
!RowanClassService categoriesFor: #sunitMethodsUpdate:browser:!public!updating! !
!RowanClassService categoriesFor: #template!accessing!private! !
!RowanClassService categoriesFor: #template:!accessing!private! !
Expand Down
25 changes: 21 additions & 4 deletions sources/RowanService.cls
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,11 @@ emptyFilterListsIn: browser
browser categoryListPresenter sortBlock: [:x :y | x < y].
browser variableListPresenter sortBlock: [:x :y | x < y].!

excludedInstVars

^#( 'events' )
!

filterUpdate: presenter browser: anObject
!

Expand Down Expand Up @@ -230,9 +235,20 @@ sortAspect

^name!

stonOn: anObject

^super stonOn: anObject "Dolphin strips out the #stonOn: in Object. try to save it"!
stonOn: stonWriter
| instanceVariableNames |
(instanceVariableNames := self class allInstVarNames
reject: [:iv | self excludedInstVars includes: iv]) isEmpty
ifTrue: [stonWriter writeObject: self do: [stonWriter encodeMap: #()]]
ifFalse:
[stonWriter writeObject: self
streamMap:
[:dictionary |
instanceVariableNames do:
[:each |
(self instVarNamed: each)
ifNotNil: [:value | dictionary at: each asSymbol put: value]
ifNil: [self stonShouldWriteNilInstVars ifTrue: [dictionary at: each asSymbol put: nil]]]]]!

sunitMethodsUpdate: presenter browser: browser!

Expand Down Expand Up @@ -318,6 +334,7 @@ variableListUpdate: aPresenter! !
!RowanService categoriesFor: #dictionaryUpdate:!public!updating! !
!RowanService categoriesFor: #displayString!displaying!public! !
!RowanService categoriesFor: #emptyFilterListsIn:!Init / Release!private! !
!RowanService categoriesFor: #excludedInstVars!public!ston! !
!RowanService categoriesFor: #filterUpdate:browser:!public!updating! !
!RowanService categoriesFor: #frameListUpdate:!Debugger!public!updating! !
!RowanService categoriesFor: #globalsUpdate:!public!updating! !
Expand Down Expand Up @@ -356,7 +373,7 @@ variableListUpdate: aPresenter! !
!RowanService categoriesFor: #replicateFrom:!public!replication!updating! !
!RowanService categoriesFor: #shouldReplicateInstVarAtIndex:newService:!public!testing! !
!RowanService categoriesFor: #sortAspect!accessing!public! !
!RowanService categoriesFor: #stonOn:!must not strip!public! !
!RowanService categoriesFor: #stonOn:!must not strip!public!ston! !
!RowanService categoriesFor: #sunitMethodsUpdate:browser:!public!updating! !
!RowanService categoriesFor: #superclassListUpdate:!public!updating! !
!RowanService categoriesFor: #testClasses:!public!updating! !
Expand Down

0 comments on commit 013283f

Please sign in to comment.