Skip to content

Commit

Permalink
Starting to write tests for a method equivalent tree checker.
Browse files Browse the repository at this point in the history
  • Loading branch information
Ducasse authored and balsa-sarenac committed Apr 26, 2024
1 parent a81dbfe commit c665858
Show file tree
Hide file tree
Showing 4 changed files with 127 additions and 0 deletions.
@@ -0,0 +1,13 @@
Class {
#name : 'RBEquivalentMethodRootHolder',
#superclass : 'Object',
#category : 'Refactoring-DataForTesting-MiniHierarchy',
#package : 'Refactoring-DataForTesting',
#tag : 'MiniHierarchy'
}

{ #category : 'for tests' }
RBEquivalentMethodRootHolder >> simpleMethodReturn [

^ 42
]
@@ -0,0 +1,19 @@
Class {
#name : 'RBEquivalentMethodSubclassHolder',
#superclass : 'RBEquivalentMethodRootHolder',
#category : 'Refactoring-DataForTesting-MiniHierarchy',
#package : 'Refactoring-DataForTesting',
#tag : 'MiniHierarchy'
}

{ #category : 'for tests' }
RBEquivalentMethodSubclassHolder >> anotherMethod: arg [

^ arg raisedTo: 5
]

{ #category : 'for tests' }
RBEquivalentMethodSubclassHolder >> simpleLocalMethodReturn [

^ 42 + 33
]
@@ -0,0 +1,50 @@
Class {
#name : 'EquivalentTreeChecker',
#superclass : 'Object',
#instVars : [
'selector',
'class',
'model'
],
#category : 'Refactoring-Transformations-Tests-Test',
#package : 'Refactoring-Transformations-Tests',
#tag : 'Test'
}

{ #category : 'query' }
EquivalentTreeChecker >> allMethodsInHierarchy [
^ ((class withAllSuperclassesUntil: Object)
flatCollect: [ :class | class methods])
]

{ #category : 'as yet unclassified' }
EquivalentTreeChecker >> allMethodsInHierarchyOf: aRBClass [

^ ((aRBClass withAllSuperclassesUntil: Object)
flatCollect: [ :class | class methods collect: [ :each | each method ] ])
]

{ #category : 'as yet unclassified' }
EquivalentTreeChecker >> methodsToBeChecked [

^ (self allMethodsInHierarchyOf: self definingClass) reject: [
:m | m selector = selector ]
]

{ #category : 'instance creation' }
EquivalentTreeChecker >> model: aModel [

model := aModel
]

{ #category : 'instance creation' }
EquivalentTreeChecker >> on: aClass [

class := model classNamed: aClass name
]

{ #category : 'instance creation' }
EquivalentTreeChecker >> rbClassFor: aClass [

^ model classNamed: aClass name
]
45 changes: 45 additions & 0 deletions src/Refactoring-Transformations-Tests/EquivalentTreeTest.class.st
@@ -0,0 +1,45 @@
Class {
#name : 'EquivalentTreeTest',
#superclass : 'TestCase',
#category : 'Refactoring-Transformations-Tests-Test',
#package : 'Refactoring-Transformations-Tests',
#tag : 'Test'
}

{ #category : 'tests' }
EquivalentTreeTest >> testAllMethodsInHierarchy [

| checker allMethods model |
model := RBNamespace new.
checker := EquivalentTreeChecker new.
checker model: model.
checker on: RBEquivalentMethodSubclassHolder.

allMethods := checker allMethodsInHierarchy.

"pay attention that we want to have rbMethods"
"pay attention rb-Methods are not cached so the includes: did not find them."
self assert:
((allMethods collect: [:each | each selector ])
includesAll: ((model classNamed: RBEquivalentMethodSubclassHolder name) methods collect: [:each | each selector])).

self assert:
((allMethods collect: [:each | each selector ])
includesAll: ((model classNamed: RBEquivalentMethodSubclassHolder superclass name) methods collect: [:each | each selector])).


"since we did redefine supermethods, none of Object should be listed."
self deny:
((allMethods collect: [:each | each selector ])
includesAll: ((model classNamed: Object name) methods collect: [:each | each selector])).
]

{ #category : 'tests' }
EquivalentTreeTest >> testSimpleLocalMethodReturn [

| checker|
checker := EquivalentTreeChecker new.
checker checkIfMethod: RBEquivalentMethodSubclassHolder>>#simpleLocalMethodReturn


]

0 comments on commit c665858

Please sign in to comment.