Skip to content

Commit

Permalink
Merge pull request #10373 from astares/10372-Cleanup-UndefinedClassTest
Browse files Browse the repository at this point in the history
Cleanup UndefinedClassTest
  • Loading branch information
MarcusDenker committed Nov 24, 2021
2 parents 30fe8a7 + 7d5b9c4 commit a6b1df1
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 15 deletions.
13 changes: 13 additions & 0 deletions src/UndefinedClasses-Tests/ManifestUndefinedClassesTests.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
"
Please describe the package using the class comment of the included manifest class. The manifest class also includes other additional metadata for the package. These meta data are used by other tools such as the SmalllintManifestChecker and the critics Browser
"
Class {
#name : #ManifestUndefinedClassesTests,
#superclass : #PackageManifest,
#category : #'UndefinedClasses-Tests-Manifest'
}

{ #category : #'code-critics' }
ManifestUndefinedClassesTests class >> ruleUtilityMethodsRuleV1FalsePositive [
^ #(#(#(#RGMethodDefinition #(#UndefinedClassTest #createClassFromDefinitionString: #false)) #'2021-11-17T07:23:16.420579+01:00') )
]
34 changes: 19 additions & 15 deletions src/UndefinedClasses-Tests/UndefinedClassTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -4,27 +4,30 @@ Class {
#category : #'UndefinedClasses-Tests'
}

{ #category : #tests }
{ #category : #asserting }
UndefinedClassTest >> assertClassDoesNotExist: aSymbol [

self assert: (self class environment at: aSymbol ifAbsent: [ true ])
]

{ #category : #tests }
{ #category : #asserting }
UndefinedClassTest >> assertClassExist: aSymbol [

self assert: (self class environment includesKey: aSymbol)
]

{ #category : #compiling }
{ #category : #utilities }
UndefinedClassTest >> compile [
"self new compile"
<script: 'self new compile'>

self createClassFromDefinitionString: self undefinedDefinition


]

{ #category : #compiling }
{ #category : #utilities }
UndefinedClassTest >> createClassFromDefinitionString: aString [
"self new compile"
<script: 'self new compile'>

^ ShiftClassInstaller make: [ :builder |
builder
Expand All @@ -38,7 +41,7 @@ UndefinedClassTest >> tearDown [

self class environment at: #Foo ifPresent: [ :c | c removeFromSystem ].
self class environment at: #ColoredFoo ifPresent: [ :c | c removeFromSystem ].
super tearDown.
super tearDown
]

{ #category : #tests }
Expand All @@ -64,7 +67,7 @@ UndefinedClassTest >> testCreateSubclassOfArbitraryExpressionReturningNilThrowsE
package: ''Box'''.
] raise: Error.

self assertClassDoesNotExist: #ColoredFoo.
self assertClassDoesNotExist: #ColoredFoo
]

{ #category : #tests }
Expand All @@ -78,11 +81,12 @@ UndefinedClassTest >> testCreateSubclassOfNilCreatesSubclassOfNil [
package: ''Box'''.

self assertClassExist: #ColoredFoo.
self assert: (self class environment at: #ColoredFoo) superclass equals: nil.
self assert: (self class environment at: #ColoredFoo) superclass equals: nil
]

{ #category : #tests }
UndefinedClassTest >> testCreateTwoUndefinedClassesOfSameNameShouldBeSameClass [

| foo foo2 |
self assertClassDoesNotExist: #Foo.

Expand All @@ -93,7 +97,7 @@ UndefinedClassTest >> testCreateTwoUndefinedClassesOfSameNameShouldBeSameClass [
]

{ #category : #tests }
UndefinedClassTest >> testCreateUndefinedClassShouldCreateNewClassThatIsIndefined [
UndefinedClassTest >> testCreateUndefinedClassShouldCreateNewClassThatIsUndefined [

self assertClassDoesNotExist: #Foo.

Expand All @@ -118,7 +122,7 @@ UndefinedClassTest >> testInstallClassNameWithUnknownSuperclassName [

self assertClassExist: #ColoredFoo.
self assert: (self class environment at: #ColoredFoo) superclass equals: (self class environment at: #Foo).
self assert: (self class environment at: #Foo) isUndefined.
self assert: (self class environment at: #Foo) isUndefined

]

Expand All @@ -133,7 +137,7 @@ UndefinedClassTest >> testRemoveUndefinedClassShouldRemoveIt [

(ShSmalltalkGlobalsEnvironment new classNamed:#Foo) removeFromSystem.

self assertClassDoesNotExist: #Foo.
self assertClassDoesNotExist: #Foo
]

{ #category : #tests }
Expand Down Expand Up @@ -168,7 +172,7 @@ UndefinedClassTest >> testUndefinedMetaclassIsUndefined [
self assert: undefinedClass class isUndefined
]

{ #category : #'handler tests' }
{ #category : #'tests - handler' }
UndefinedClassTest >> testUnknowSuperclassShouldInheritFromUndefinedClass [
| newUndefinedClass |
self assertClassDoesNotExist: #Foo.
Expand All @@ -180,13 +184,13 @@ UndefinedClassTest >> testUnknowSuperclassShouldInheritFromUndefinedClass [
self assert: (self class environment at: #Foo) isUndefined
]

{ #category : #compiling }
{ #category : #accessing }
UndefinedClassTest >> tokens [

^ self undefinedDefinition splitOn: ' '
]

{ #category : #compiling }
{ #category : #accessing }
UndefinedClassTest >> undefinedDefinition [

^ 'Foo subclass: #ColoredFoo
Expand Down

0 comments on commit a6b1df1

Please sign in to comment.