The Inbox: Tests-ct.436.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: Tests-ct.436.mcz

commits-2
A new version of Tests was added to project The Inbox:
http://source.squeak.org/inbox/Tests-ct.436.mcz

==================== Summary ====================

Name: Tests-ct.436
Author: ct
Time: 5 June 2020, 9:43:01.213974 pm
UUID: 13ae0b1e-24b2-224c-b79d-43e68b3a1208
Ancestors: Tests-mt.435

Fixes failing MCPackageTest >> #test{Load, Unload}Order which I originally introduced in Tests-ct.426.

I had forgot to commit the mock preambles. Beside of that, it turned out that there was a lot of global state not properly sandboxed or reset by the MCTestCases. Enhance #clearPackageCache, fix implementations of #setUp/#tearDown methods, test MCSnapshotBrowser with and without scripts, and apply some minor refactoring. Remove accidentally added Tests-MonticelloMocks from organization.

Please report any further global state if observed.

=============== Diff against Tests-mt.435 ===============

Item was changed:
  SystemOrganization addCategory: #'Tests-Bugs'!
  SystemOrganization addCategory: #'Tests-Compiler'!
  SystemOrganization addCategory: #'Tests-Dependencies'!
  SystemOrganization addCategory: #'Tests-Digital Signatures'!
  SystemOrganization addCategory: #'Tests-Environments'!
  SystemOrganization addCategory: #'Tests-Exceptions'!
  SystemOrganization addCategory: #'Tests-FilePackage'!
  SystemOrganization addCategory: #'Tests-Files'!
  SystemOrganization addCategory: #'Tests-Finalization'!
  SystemOrganization addCategory: #'Tests-Hex'!
  SystemOrganization addCategory: #'Tests-Installer-Core'!
  SystemOrganization addCategory: #'Tests-Localization'!
  SystemOrganization addCategory: #'Tests-Monticello'!
  SystemOrganization addCategory: #'Tests-Monticello-Mocks'!
  SystemOrganization addCategory: #'Tests-Monticello-Utils'!
  SystemOrganization addCategory: #'Tests-Object Events'!
  SystemOrganization addCategory: #'Tests-ObjectsAsMethods'!
  SystemOrganization addCategory: #'Tests-PrimCallController'!
  SystemOrganization addCategory: #'Tests-Release'!
  SystemOrganization addCategory: #'Tests-System-Applications'!
  SystemOrganization addCategory: #'Tests-System-Digital Signatures'!
  SystemOrganization addCategory: #'Tests-System-Object Storage'!
  SystemOrganization addCategory: #'Tests-System-Preferences'!
  SystemOrganization addCategory: #'Tests-System-Support'!
  SystemOrganization addCategory: #'Tests-Utilities'!
  SystemOrganization addCategory: #'Tests-VM'!
- SystemOrganization addCategory: #'Tests-MonticelloMocks'!

Item was changed:
  ----- Method: MCChangeNotificationTest>>tearDown (in category 'running') -----
  tearDown
 
+ workingCopy unregister.
+
+ ^ super tearDown!
- super tearDown.
- workingCopy unregister!

Item was changed:
  ----- Method: MCClassDefinitionTest>>tearDown (in category 'running') -----
  tearDown
 
+ Smalltalk at: 'MCMockClassC' ifPresent: [:c | c removeFromSystem].
+
+ ^ super tearDown!
- super tearDown.
- Smalltalk at: 'MCMockClassC' ifPresent: [:c | c removeFromSystem]!

Item was changed:
  ----- Method: MCDictionaryRepositoryTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  repository :=  MCDictionaryRepository new dictionary: self dictionary!

Item was changed:
  ----- Method: MCDirectoryRepositoryTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  repository := MCDirectoryRepository directory: self directory!

Item was changed:
  ----- Method: MCDirectoryRepositoryTest>>tearDown (in category 'running') -----
  tearDown
 
+ self directory recursiveDelete.
+
+ ^ super tearDown!
- super tearDown.
- self directory recursiveDelete!

Item was changed:
  ----- Method: MCEnvironmentLoadTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  environment := Environment named: 'MCEnvironmentLoadTest'.
 
  "This is required in order to not importSelf more than once"
  environment stopObserving: environment.
 
  "This is required to make own declarations visible in environment"
  environment importSelf.
 
  "Import the required PoolDictionary used by the package"
  environment bindingOf: #MCMockAPoolDictionary
  ifAbsent: [environment from: Smalltalk globals import: #MCMockAPoolDictionary].
  environment from: Smalltalk globals import: #(MCMock MCSnapshotTest Object).!

Item was changed:
  ----- Method: MCEnvironmentLoadTest>>tearDown (in category 'running') -----
  tearDown
+
  (environment allClassesAndTraits sorted: [:a :b |
  (a allSuperclasses includes: b) or: [a name < b name]])
  do: [:each | each removeFromSystem].
+
+ ^ super tearDown!
- super tearDown!

Item was changed:
  ----- Method: MCFileInTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  expected := self mockSnapshot.
  stream := RWBinaryOrTextStream on: String new.!

Item was changed:
  ----- Method: MCFileInTest>>tearDown (in category 'running') -----
  tearDown
 
- super tearDown.
  (diff isNil or: [diff isEmpty not])
  ifTrue: [expected updatePackage: self mockPackage].
+ SystemOrganizer default removeEmptyCategories.
+
+ ^ super tearDown!
- SystemOrganizer default removeEmptyCategories!

Item was changed:
  ----- Method: MCInitializationTest>>tearDown (in category 'running') -----
  tearDown
 
+ (MCWorkingCopy forPackage: self mockPackage) unregister.
+
+ ^ super tearDown!
- super tearDown.
- (MCWorkingCopy forPackage: self mockPackage) unregister!

Item was changed:
  ----- Method: MCMczInstallerTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  expected := self mockVersion.
  self change: #one toReturn: 2.!

Item was changed:
  ----- Method: MCMczInstallerTest>>tearDown (in category 'running') -----
  tearDown
 
- super tearDown.
  expected snapshot updatePackage: self mockPackage.
+ self deleteFile.
+
+ ^ super tearDown!
- self deleteFile.!

Item was changed:
  ----- Method: MCMethodDefinitionTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  extensionPackage := (MCWorkingCopy forPackage: (MCPackage named: 'FooBarBaz')).
  navigation := (Smalltalk hasClassNamed: #SystemNavigation)
  ifTrue: [(Smalltalk at: #SystemNavigation) new]
  ifFalse: [Smalltalk].
  isModified := self ownPackage modified.
  overrideTimestamp := (self class >> #override) timeStamp!

Item was changed:
  ----- Method: MCMethodDefinitionTest>>tearDown (in category 'running') -----
  tearDown
 
  self restoreMocks.
  extensionPackage unregister.
  extensionPackage := nil.
  MCMockPackageInfo new mcPackage workingCopy unregister.
  self class
  compile: 'override ^ 1'
  classified: 'mocks'
  withStamp: overrideTimestamp
  notifying: nil.
  SystemOrganizer default removeEmptyCategories.
  self ownPackage modified: isModified.
+
+ ^ super tearDown!
- super tearDown
- !

Item was added:
+ ----- Method: MCMockPackageInfo>>initialize (in category 'initialize-release') -----
+ initialize
+
+ super initialize.
+
+ #(preamble postscript preambleOfRemoval postscriptOfRemoval)
+ do: [:selector |
+ self perform: selector asSimpleSetter with: selector asString].!

Item was changed:
  ----- Method: MCPackageTest>>tearDown (in category 'running') -----
  tearDown
 
+ self mockSnapshot install.
+
+ ^ super tearDown!
- super tearDown.
- self mockSnapshot install!

Item was changed:
  ----- Method: MCPatchTest>>setUp (in category 'running') -----
  setUp
+
+ | rev1 rev2 |
+ super setUp.
+
- |rev1 rev2|
  rev1 :=  MCSnapshotResource takeSnapshot.
  self change: #one toReturn: 2.
  rev2 :=  MCSnapshotResource takeSnapshot.
  patch := rev2 patchRelativeToBase: rev1.
  self change: #one toReturn: 1.!

Item was changed:
  ----- Method: MCPatchTest>>tearDown (in category 'running') -----
  tearDown
 
+ self restoreMocks.
+
+ ^ super tearDown!
- super tearDown.
- self restoreMocks!

Item was changed:
  ----- Method: MCSerializationTest>>tearDown (in category 'running') -----
  tearDown
+
  self restoreMocks.
+
+ ^ super tearDown!
- super tearDown.!

Item was changed:
  ----- Method: MCSnapshotBrowserTest>>assertTextIs: (in category 'asserting') -----
  assertTextIs: aString
+ ^ self assert: aString equals: self textMorph contents asString!
- self assert: self textMorph contents = aString.!

Item was changed:
  ----- Method: MCSnapshotBrowserTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  "to not disturb the tests"
  originalAnnotationPanePref := Preferences annotationPanes.
  Preferences disable: #annotationPanes.
  model := MCSnapshotBrowser forSnapshot: MCSnapshotResource current snapshot.
  self buildWindow!

Item was changed:
  ----- Method: MCSnapshotBrowserTest>>tearDown (in category 'running') -----
  tearDown
+
  originalAnnotationPanePref ifTrue: [Preferences enable: #annotationPanes].
+
+ ^ super tearDown!
- super tearDown.!

Item was changed:
  ----- Method: MCSnapshotBrowserTest>>testNoSelection (in category 'tests') -----
  testNoSelection
+
+ | text |
  self assertAListMatches: self allCategories.
  self denyAListIncludesAnyOf: self definedClasses.
  self denyAListIncludesAnyOf: self allProtocols.
  self denyAListIncludesAnyOf: self allMethods.
+
+ text := self textMorph contents asString.
+
+ #(preamble postscript preambleOfRemoval postscriptOfRemoval)
+ do: [:selector |
+ self assert: [text includesSubstring: selector]].!
- "and if there I need to see the packages scripts (or none)"
- self assertTextIs: '(package defines no scripts)'.!

Item was added:
+ ----- Method: MCSnapshotBrowserTest>>testNoSelectionNoScripts (in category 'tests') -----
+ testNoSelectionNoScripts
+
+ #(preamble postscript preambleOfRemoval postscriptOfRemoval)
+ do: [:selector |
+ self mockPackage packageInfo perform: selector asSimpleSetter with: nil].
+ model snapshot: MCSnapshotResource new snapshot.
+ model changed: #text. "update"
+
+ self assertTextIs: '(package defines no scripts)'.!

Item was changed:
  ----- Method: MCSnapshotTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  snapshot :=  self mockSnapshot.!

Item was changed:
  ----- Method: MCStWriterTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  stream := RWBinaryOrTextStream on: String new.
  writer := MCStWriter on: stream.
  !

Item was changed:
  ----- Method: MCStWriterTest>>tearDown (in category 'running') -----
  tearDown
 
  SystemOrganizer default removeEmptyCategories.
+
+ ^ super tearDown !
- super tearDown !

Item was changed:
  ----- Method: MCTestCase>>clearPackageCache (in category 'running') -----
  clearPackageCache
  "Remove all mock packages created during the tests from the package cache."
 
+ | directory cacheFiles cacheNames |
- | directory |
  directory := MCCacheRepository default directory.
+ cacheNames := {self mockVersionName. self mockVersionInfo name}.
+ cacheFiles := cacheNames gather: [:name |
+ directory fileNamesMatching: name , '*'].
+ cacheFiles do: [:each |
+ directory deleteFileNamed: each].!
- (directory fileNamesMatching: self mockVersionName, '*') do: [ :each |
- directory deleteFileNamed: each ]!

Item was added:
+ ----- Method: MCTestCase>>setUp (in category 'running') -----
+ setUp
+
+ super setUp.
+
+ MCMockPackageInfo new register.!

Item was changed:
  ----- Method: MCTestCase>>tearDown (in category 'running') -----
  tearDown
 
+ self clearPackageCache.
+ "Environment current packageOrganizer unregisterPackageNamed:
+ MCSnapshotResource mockPackageName."
+ self flag: #todo. "Unfortunately breaks the tests"
+
+ ^ super tearDown!
- self clearPackageCache!

Item was changed:
  ----- Method: MCVersionTest>>setUp (in category 'running') -----
  setUp
+
+ super setUp.
+
  visited := OrderedCollection new.!

Item was changed:
  ----- Method: MCWorkingCopyRenameTest>>setUp (in category 'running') -----
  setUp
+
  | repos1 repos2 |
+ super setUp.
+
  repositoryGroup := MCRepositoryGroup new.
  workingCopy := MCWorkingCopy forPackage: self mockPackage.
  versions := Dictionary new.
  versions2 := Dictionary new.
  repos1 := MCDictionaryRepository new dictionary: versions.
  repos2 := MCDictionaryRepository new dictionary: versions2.
  repositoryGroup addRepository: repos1.
  repositoryGroup addRepository: repos2.
  MCRepositoryGroup default removeRepository: repos1; removeRepository: repos2.
  workingCopy repositoryGroup: repositoryGroup.
  savedInitials := Utilities authorInitialsPerSe.
  Utilities authorInitials: 'abc'.!

Item was changed:
  ----- Method: MCWorkingCopyRenameTest>>tearDown (in category 'running') -----
  tearDown
+
- super tearDown.
  workingCopy unregister.
  SystemOrganizer default removeEmptyCategories.
  MCSnapshotTest organization removeEmptyCategories.
+ Utilities authorInitials: savedInitials.
+
+ ^ super tearDown!
- Utilities authorInitials: savedInitials!

Item was changed:
  ----- Method: MCWorkingCopyTest>>setUp (in category 'running') -----
  setUp
+
  | repos1 repos2 |
+ super setUp.
+
  self clearPackageCache.
  repositoryGroup := MCRepositoryGroup new.
  workingCopy := MCWorkingCopy forPackage: self mockPackage.
  versions := Dictionary new.
  versions2 := Dictionary new.
  repos1 := MCDictionaryRepository new dictionary: versions.
  repos2 := MCDictionaryRepository new dictionary: versions2.
  repositoryGroup addRepository: repos1.
  repositoryGroup addRepository: repos2.
  MCRepositoryGroup default removeRepository: repos1; removeRepository: repos2.
  workingCopy repositoryGroup: repositoryGroup.
  savedInitials := Utilities authorInitialsPerSe.
  Utilities authorInitials: 'abc'.!

Item was changed:
  ----- Method: MCWorkingCopyTest>>tearDown (in category 'running') -----
  tearDown
+
- super tearDown.
  workingCopy unregister.
  self restoreMocks.
  SystemOrganizer default removeEmptyCategories.
  MCSnapshotTest organization removeEmptyCategories.
+ Utilities authorInitials: savedInitials.
+
+ ^ super tearDown!
- Utilities authorInitials: savedInitials!