Skip to content

Commit 3f2ed0e

Browse files
authored
Merge pull request #16584 from StevenCostiou/Reflectivity-Test-Bug
Fixing reflectivity tests that can randomly fail because of unstable and unpredictable tests generating methods
2 parents 94539ac + a49af14 commit 3f2ed0e

File tree

2 files changed

+6
-14
lines changed

2 files changed

+6
-14
lines changed

src/Reflectivity-Tests/LinkInstallerTest.class.st

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ LinkInstallerTest >> setUp [
3232
{ #category : 'running' }
3333
LinkInstallerTest >> tearDown [
3434
ReflectivityExamples2 new removeModifiedMethodWithInstVarAccess.
35+
ReflectivityExamples2 new removeNewMethodWithInstVarAccess.
3536
ReflectivityExamples new removeTemporaryMethods.
3637
super tearDown
3738
]
@@ -475,8 +476,7 @@ LinkInstallerTest >> testPermaLinkNotInstalledOnObjectIfExistsInClass [
475476
link installOnVariableNamed: #instVar for: obj option: #all instanceSpecific: true.
476477
self assert: link nodes size equals: 8.
477478

478-
link uninstall.
479-
ReflectivityExamples2 new removeNewMethodWithInstVarAccess
479+
link uninstall
480480
]
481481

482482
{ #category : 'links - updating' }
@@ -751,8 +751,7 @@ LinkInstallerTest >> testSlotOrVarLinksAddedAfterMethodAddition [
751751

752752
|methodNode link|
753753
methodNode := (ReflectivityExamples2 >> #methodWithInstVarAccess) ast.
754-
ReflectivityExamples2 new removeNewMethodWithInstVarAccess.
755-
754+
756755
link := MetaLink new.
757756
link installOnVariableNamed: #instVar for: ReflectivityExamples2 option: #all instanceSpecific: false.
758757

@@ -771,8 +770,7 @@ LinkInstallerTest >> testSlotOrVarLinksAddedAfterMethodAdditionForObject [
771770

772771
methodNode := (ReflectivityExamples2 >> #methodWithInstVarAccess) ast.
773772
obj := ReflectivityExamples2 new.
774-
ReflectivityExamples2 new removeNewMethodWithInstVarAccess.
775-
773+
776774
link := MetaLink new.
777775
link installOnVariableNamed: #instVar for: obj option: #all instanceSpecific: true.
778776

@@ -787,7 +785,7 @@ LinkInstallerTest >> testSlotOrVarLinksAddedAfterMethodAdditionForObject [
787785
{ #category : 'permalinks' }
788786
LinkInstallerTest >> testSlotOrVarLinksRemainAfterMethodModification [
789787
|methodNode link|
790-
788+
ReflectivityExamples2 new generateNewMethodWithInstVarAccess.
791789
ReflectivityExamples2 new resetModifiedMethodWithInstVarAccess.
792790
methodNode := (ReflectivityExamples2 >> #modifiedMethodWithInstVarAccess) ast.
793791

@@ -808,6 +806,7 @@ LinkInstallerTest >> testSlotOrVarLinksRemainAfterMethodModificationForObject [
808806
|methodNode link obj|
809807

810808
obj := ReflectivityExamples2 new.
809+
ReflectivityExamples2 new generateNewMethodWithInstVarAccess.
811810
ReflectivityExamples2 new resetModifiedMethodWithInstVarAccess.
812811
methodNode := (ReflectivityExamples2 >> #modifiedMethodWithInstVarAccess) ast.
813812

src/Reflectivity-Tests/ReflectivityExamples2.class.st

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -83,13 +83,6 @@ ReflectivityExamples2 >> modifyMethodWithInstVarAccess [
8383
instVar > 5 ifTrue:[^ instVar raisedTo: 2]'
8484
]
8585

86-
{ #category : 'example' }
87-
ReflectivityExamples2 >> newMethodWithInstVarAccess [
88-
instVar := 5.
89-
instVar := 6.
90-
instVar > 5 ifTrue:[^ instVar raisedTo: 2]
91-
]
92-
9386
{ #category : 'removing' }
9487
ReflectivityExamples2 >> removeModifiedMethodWithInstVarAccess [
9588
self class removeSelector: #modifiedMethodWithInstVarAccess

0 commit comments

Comments
 (0)