From 7d7ea00a25f001cd9b51739c7e22207e8e7393b9 Mon Sep 17 00:00:00 2001 From: Alisu Date: Mon, 23 Sep 2019 13:30:56 +0200 Subject: [PATCH] Remove in Smalltalk ReleaseTests/SmartSuggestions/Zinc tests --- src/ReleaseTests/ObsoleteTest.class.st | 6 +++--- src/ReleaseTests/ReleaseTest.class.st | 6 +++--- src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st | 4 ++-- src/Zinc-Tests/ZnClientTest.class.st | 2 +- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/src/ReleaseTests/ObsoleteTest.class.st b/src/ReleaseTests/ObsoleteTest.class.st index 44bbf4121ad..f417ba47b8a 100644 --- a/src/ReleaseTests/ObsoleteTest.class.st +++ b/src/ReleaseTests/ObsoleteTest.class.st @@ -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. @@ -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. diff --git a/src/ReleaseTests/ReleaseTest.class.st b/src/ReleaseTests/ReleaseTest.class.st index 864c6208dab..d02cc4984fa 100644 --- a/src/ReleaseTests/ReleaseTest.class.st +++ b/src/ReleaseTests/ReleaseTest.class.st @@ -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 ] @@ -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). ] diff --git a/src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st b/src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st index d704fd8b05f..9c682283bf0 100644 --- a/src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st +++ b/src/SmartSuggestions-Tests/SugsMenuBuilderTest.class.st @@ -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' } @@ -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' } diff --git a/src/Zinc-Tests/ZnClientTest.class.st b/src/Zinc-Tests/ZnClientTest.class.st index 458883432d2..351e0101cae 100644 --- a/src/Zinc-Tests/ZnClientTest.class.st +++ b/src/Zinc-Tests/ZnClientTest.class.st @@ -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 ] ];