Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
16 changes: 16 additions & 0 deletions src/Refactoring-Core-Tests/RBConditionTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -295,3 +295,19 @@ RBConditionTest >> testTrue [
self assert: RBCondition true check.
self deny: RBCondition true not check.
]

{ #category : 'tests' }
RBConditionTest >> testViolatorsForNegatedConditionAreCorrect [

| abstract concrete condition negation doubleNegation |
abstract := { TestCase . Number }.
concrete := { Object . Point }.

condition := ReClassesAreAbstractCondition new classes: abstract, concrete.
negation := condition not.
doubleNegation := negation not.

self assert: condition violators asSet equals: concrete asSet.
self assert: negation violators asSet equals: abstract asSet.
self assert: doubleNegation violators asSet equals: condition violators asSet
]
158 changes: 135 additions & 23 deletions src/Refactoring-Core-Tests/ReClassesAreAbstractTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -6,60 +6,131 @@ Class {
#tag : 'Conditions'
}

{ #category : 'accessing' }
ReClassesAreAbstractTest >> classToTest [
^ ReClassesAreAbstractCondition
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsAbstract [
| classNumber cond |
classNumber := self model classNamed: #Number.

| abstract cond |
abstract := self model classNamed: #Number.
cond := self classToTest new classes: { abstract }.

self assert: cond check.
self assert: cond nonViolators equals: { abstract }.
self assert: cond violators isEmpty
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsAbstractMessage [
| abstract cond |
abstract := self model classNamed: #Number.

cond := ReClassesAreAbstractCondition new
classes: { classNumber }.
cond := self classToTest new
classes: { abstract }.

" Number is abstract"
self assert: cond errorString isEmpty
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsAbstractWithNegation [

| abstract cond |
abstract := self model classNamed: #Number.
cond := self classToTest new classes: { abstract }.

self assert: cond check.
self assert: cond nonViolators equals: { abstract }.
self assert: cond violators isEmpty.
self assert: cond nonViolators equals: { classNumber }

cond := cond not.
self deny: cond check.
self assert: cond violators equals: { abstract }.
self assert: cond nonViolators isEmpty.


]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsAbstractWithMessage [
| classNumber cond |
classNumber := self model classNamed: #Number.
ReClassesAreAbstractTest >> testClassIsAbstractWithNegationMessage [

| abstract cond |
abstract := self model classNamed: #Number.
cond := self classToTest new classes: { abstract }.

cond := ReClassesAreAbstractCondition new
classes: { classNumber }.
self assert: cond check.
self assert: cond errorString isEmpty.

self assert: cond errorString isEmpty
cond := cond not.
self deny: cond check.
self assert: 'Number is an abstract class.' equals: cond errorString


]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testNoClassIsAbstract [
ReClassesAreAbstractTest >> testClassIsNotAbstract [

| concrete cond |
concrete := self model classNamed: #Object.
cond := ReClassesAreAbstractCondition new classes: { concrete }.
cond := self classToTest new classes: { concrete }.

self deny: cond check.
self assert: cond violators equals: { concrete }.
self assert: cond nonViolators isEmpty
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testNoClassIsAbstractWithMessage [
ReClassesAreAbstractTest >> testClassIsNotAbstractMessage [

| concrete cond |
concrete := self model classNamed: #Object.
cond := ReClassesAreAbstractCondition new classes: { concrete }.
cond := self classToTest new classes: { concrete }.
self assert: 'Object is not an abstract class.' equals: cond errorString
]

self assert: ('*' , concrete name , '*' match: cond errorString)
{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsNotAbstractWithNegation [

| concrete cond |
concrete := self model classNamed: #Object.
cond := self classToTest new classes: { concrete }.

self deny: cond check.
self assert: cond violators equals: { concrete }.
self assert: cond nonViolators isEmpty.

cond := cond not.
self assert: cond check.
self assert: cond nonViolators equals: { concrete }.
self assert: cond violators isEmpty.

]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testClassIsNotAbstractWithNegationMessage [

| concrete cond |
concrete := self model classNamed: #Object.
cond := self classToTest new classes: { concrete }.

self deny: cond check.
self assert: 'Object is not an abstract class.' equals: cond errorString.

cond := cond not.
self assert: cond check.
self assert: cond errorString isEmpty
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testSomeClassesAreAbstract [
ReClassesAreAbstractTest >> testOneAbstractOneConcrete [

| abstract concrete cond |
abstract := self model classNamed: #Number.
concrete := self model classNamed: #Object.
cond := ReClassesAreAbstractCondition new classes: {
cond := self classToTest new classes: {
abstract.
concrete }.

Expand All @@ -69,15 +140,56 @@ ReClassesAreAbstractTest >> testSomeClassesAreAbstract [
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testSomeClassesAreAbstractWithMessage [
ReClassesAreAbstractTest >> testOneAbstractOneConcreteMessage [

| abstract concrete cond |
abstract := self model classNamed: #Number.
concrete := self model classNamed: #Object.
cond := ReClassesAreAbstractCondition new classes: {
cond := self classToTest new classes: {
abstract.
concrete }.

self assert: ('*' , concrete name , '*' match: cond errorString).
self deny: ('*' , abstract name , '*' match: cond errorString)
self assert: ('Object is not an abstract class.' match: cond errorString)
]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testOneAbstractOneConcreteWithNegation [

| abstract concrete areAbstract areConcrete |
abstract := self model classNamed: #Number.
concrete := self model classNamed: #Object.
areAbstract := self classToTest new classes: {
abstract.
concrete }.

self deny: areAbstract check.
self assert: areAbstract violators equals: { concrete }.
self assert: areAbstract nonViolators equals: { abstract }.

areConcrete := areAbstract not.
self deny: areConcrete check.
self assert: areConcrete violators equals: { abstract }.
self assert: areConcrete nonViolators equals: { concrete }.

]

{ #category : 'tests' }
ReClassesAreAbstractTest >> testOneAbstractOneConcreteWithNegationMessage [

| abstract concrete areAbstract areConcrete |
abstract := self model classNamed: #Number.
concrete := self model classNamed: #Object.
areAbstract := self classToTest new classes: {
abstract.
concrete }.
" Not all classes are abstract => cond fails "
self deny: areAbstract check.
self assert: areAbstract errorString equals: 'Object is not an abstract class.'.

" Not all classes are abstract — therefore, the negated condition (NOT) also fails.
This proves that `cond not check` is not equivalent to `cond check not`,
except in the special case where the condition applies to a single candidate. "
areConcrete := areAbstract not.
self deny: areConcrete check.
self assert: areConcrete errorString equals: 'Number is an abstract class.'
]
6 changes: 3 additions & 3 deletions src/Refactoring-Core-Tests/ReClassesEmptyTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ ReClassesEmptyTest >> testClassIsEmpty [
]

{ #category : 'tests' }
ReClassesEmptyTest >> testClassIsEmptyWithMessage [
ReClassesEmptyTest >> testClassIsEmptyMessage [

| empty cond |
empty := self model classNamed: #MyClassB.
Expand Down Expand Up @@ -50,7 +50,7 @@ ReClassesEmptyTest >> testClassIsNotEmpty [
]

{ #category : 'tests' }
ReClassesEmptyTest >> testClassIsNotEmptyWithMessage [
ReClassesEmptyTest >> testClassIsNotEmptyMessage [

| full cond |
full := self model classNamed: #MyClassAlpha.
Expand Down Expand Up @@ -79,7 +79,7 @@ ReClassesEmptyTest >> testSomeClassesAreEmpty [
]

{ #category : 'tests' }
ReClassesEmptyTest >> testSomeClassesAreEmptyWithMessage [
ReClassesEmptyTest >> testSomeClassesAreEmptyMessage [

| full empty cond |
full := self model classNamed: #MyClassAlpha.
Expand Down
6 changes: 3 additions & 3 deletions src/Refactoring-Core-Tests/ReClassesExistTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ ReClassesExistTest >> testClassDoesNotExist [
]

{ #category : 'tests' }
ReClassesExistTest >> testClassDoesNotExistWithMessage [
ReClassesExistTest >> testClassDoesNotExistMessage [
| nonexistent cond |
nonexistent := #Imaginary.
cond := ReClassesExistCondition new
Expand All @@ -42,7 +42,7 @@ ReClassesExistTest >> testClassExists [
]

{ #category : 'tests' }
ReClassesExistTest >> testClassExistsWithMessage [
ReClassesExistTest >> testClassExistsMessage [
| existing cond existingClass |
existing := #MyClassAlpha.
existingClass := self model classNamed: existing.
Expand Down Expand Up @@ -71,7 +71,7 @@ ReClassesExistTest >> testSomeClassesDoNotExist [
]

{ #category : 'tests' }
ReClassesExistTest >> testSomeClassesDoNotExistWithMessage [
ReClassesExistTest >> testSomeClassesDoNotExistMessage [

| nonexistent existing existingClass cond |
nonexistent := #Imaginary.
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
Class {
#name : 'ReClassesHaveNoSubclassesOrClassesEmptyTest',
#superclass : 'ReClassesConditionTest',
#category : 'Refactoring-Core-Tests-Conditions',
#package : 'Refactoring-Core-Tests',
#tag : 'Conditions'
}

{ #category : 'tests' }
ReClassesHaveNoSubclassesOrClassesEmptyTest >> testClassHasNoSubclassesAndNotEmpty [

| nosubs notempty hasNoSubs isEmpty noSubsOrEmpty noSubsAndEmpty hasNoSubsNot isEmptyNot noSubsOrEmptyNot noSubsAndEmptyNot |
nosubs := self model classNamed: #MyClassB.
notempty := self model classNamed: #MyClassAlpha.

hasNoSubs := ReClassesHaveNoSubclassesCondition new
classes: { nosubs }.
isEmpty := ReClassesEmptyCondition new
classes: { notempty }.
self assert: hasNoSubs check.
self deny: isEmpty check.
hasNoSubsNot := hasNoSubs not.
isEmptyNot := isEmpty not.
self deny: hasNoSubsNot check.
self assert: isEmptyNot check.
noSubsOrEmpty := hasNoSubs | isEmpty.
self assert: noSubsOrEmpty check.
noSubsAndEmpty:= hasNoSubs & isEmpty.
self deny: noSubsAndEmpty check.
noSubsOrEmptyNot := noSubsOrEmpty not.
noSubsAndEmptyNot := noSubsAndEmpty not.
self deny: noSubsOrEmptyNot check.
self assert: noSubsAndEmptyNot check

]
13 changes: 13 additions & 0 deletions src/Refactoring-Core-Tests/ReClassesHaveNoSubclassesTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,19 @@ ReClassesHaveNoSubclassesTest >> testClassHasNoSubclasses [
self assert: cond nonViolators equals: { nosubs }
]

{ #category : 'tests' }
ReClassesHaveNoSubclassesTest >> testClassHasNoSubclassesMessage [

| nosubs cond |
nosubs := self model classNamed: #MySubAccessingSuperclassState.

cond := ReClassesHaveNoSubclassesCondition new
classes: { nosubs }.

self assert: cond check.
self assert: cond errorString isEmpty
]

{ #category : 'tests' }
ReClassesHaveNoSubclassesTest >> testClassHasSubclasses [

Expand Down
Loading