Skip to content

Commit

Permalink
Remove in Smalltalk ReleaseTests/SmartSuggestions/Zinc tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Alisu committed Sep 23, 2019
1 parent cba2846 commit 7d7ea00
Show file tree
Hide file tree
Showing 4 changed files with 9 additions and 9 deletions.
6 changes: 3 additions & 3 deletions src/ReleaseTests/ObsoleteTest.class.st
Expand Up @@ -27,7 +27,7 @@ ObsoleteTest >> tearDown [
{ #category : #tests }
ObsoleteTest >> testClassObsolete [
| aClass |
Smalltalk globals at: #ClassForObsoleteTest ifPresent: [ :cls | cls removeFromSystem ].
aTestEnvironment at: #ClassForObsoleteTest ifPresent: [ :cls | cls removeFromSystem ].
aClass := classFactory newClass.

self deny: aClass isObsolete.
Expand Down Expand Up @@ -70,8 +70,8 @@ ObsoleteTest >> testFixObsoleteSharedPools [
{ #category : #tests }
ObsoleteTest >> testTraitObsolete [
| aClass aTrait |
Smalltalk globals at: #ClassForObsoleteTest ifPresent: [ :cls | cls removeFromSystem ].
Smalltalk globals at: #TraitForObsoleteTest ifPresent: [ :tr | tr removeFromSystem ].
aTestEnvironment at: #ClassForObsoleteTest ifPresent: [ :cls | cls removeFromSystem ].
aTestEnvironment at: #TraitForObsoleteTest ifPresent: [ :tr | tr removeFromSystem ].

aTrait := classFactory newTrait.
aClass := classFactory newClassUsing: aTrait.
Expand Down
6 changes: 3 additions & 3 deletions src/ReleaseTests/ReleaseTest.class.st
Expand Up @@ -89,14 +89,14 @@ ReleaseTest >> knownProcesses [
ReleaseTest >> testAllClassPoolBindingAreClassVariables [
| wrong |
wrong := OrderedCollection new.
Smalltalk globals allClasses do: [ :class | wrong addAll: (class classVariables reject: [ :each | each isKindOf: ClassVariable ]) ].
aTestEnvironment allClasses do: [ :class | wrong addAll: (class classVariables reject: [ :each | each isKindOf: ClassVariable ]) ].
self assertEmpty: wrong
]

{ #category : #tests }
ReleaseTest >> testAllGlobalBindingAreGlobalVariables [
| wrong |
wrong := Smalltalk globals associations reject: [ :each | each isKindOf: GlobalVariable ].
wrong := aTestEnvironment associations reject: [ :each | each isKindOf: GlobalVariable ].
self assertEmpty: wrong
]

Expand Down Expand Up @@ -147,7 +147,7 @@ ReleaseTest >> testKeyClassesArePresentInStartupList [

keyClasses do: [ :className |
self assert: (registeredHandlers includes: className).
self assert: (self hasStartUpOrShutDownMethod: (Smalltalk globals at: className)) ].
self assert: (self hasStartUpOrShutDownMethod: (aTestEnvironment at: className)) ].

self assert: (registeredHandlers includes: #UIManagerSessionHandler).
]
Expand Down
4 changes: 2 additions & 2 deletions src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st
Expand Up @@ -14,7 +14,7 @@ SugsMenuBuilderTest >> testFindBestNodeForClassItsRBVariable [
node :=SugsMenuBuilder findBestNodeFor: SugsMockContext classContext.
self assert: (node isKindOf: RBVariableNode).
"Es una forma un tanto molesta de preguntar... es de clase?"
self assert:( node binding isLiteralVariable and: [Smalltalk globals includesAssociation: node binding assoc ]).
self assert:( node binding isLiteralVariable and: [aTestEnvironment includesAssociation: node binding assoc ]).
]

{ #category : #'tests - nodes' }
Expand All @@ -24,7 +24,7 @@ SugsMenuBuilderTest >> testFindBestNodeForClassVarItsRBVariable [
node :=SugsMenuBuilder findBestNodeFor: SugsMockContext classVariableContext .
self assert: (node isKindOf: RBVariableNode).
"Es una forma un tanto molesta de preguntar... es una var de clase?"
self assert:( node binding isLiteralVariable and: [(Smalltalk globals includesAssociation: node binding assoc ) not]).
self assert:( node binding isLiteralVariable and: [(aTestEnvironment includesAssociation: node binding assoc ) not]).
]

{ #category : #'tests - nodes' }
Expand Down
2 changes: 1 addition & 1 deletion src/Zinc-Tests/ZnClientTest.class.st
Expand Up @@ -160,7 +160,7 @@ ZnClientTest >> testGetGeoIP [
queryAt: 'address' put: '81.83.7.35';
accept: ZnMimeType applicationJson;
contentReader: [ :entity |
Smalltalk globals
aTestEnvironment
at: #NeoJSONReader
ifPresent: [ :parserClass | parserClass fromString: entity contents ]
ifAbsent: [ ^ self ] ];
Expand Down

0 comments on commit 7d7ea00

Please sign in to comment.