[Pkg] The Trunk: Tests-nice.387.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 7 00:02:51 UTC 2017


Nicolas Cellier uploaded a new version of Tests to project The Trunk:
http://source.squeak.org/trunk/Tests-nice.387.mcz

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

Name: Tests-nice.387
Author: nice
Time: 7 December 2017, 1:02:38.147384 am
UUID: 6ba78d9d-9e75-4507-8095-3e6693a32c91
Ancestors: Tests-tpr.386

Fix MCMethodDefinitionTest which was not reentrant

The tearDown unregister a working copy of  (MCPackage named: 'FooBarBaz'), so the setUp somehow has to recreate it. Otherwise, the tests might start failing at second run. 

The bug has been identified by Torsten Bergmann and reported on pharo dev mailing list (see thread "Running tests in MCMethodDefinitionTest").

Cherry pick his fix from https://github.com/pharo-project/pharo/pull/583/files, along with a few other cosmetics:
- Fix a missing super tearDown.
- Classify the unclassified methods.
- Comment some classes.
- remove an unused ivar

TODO: setUp should better call super setUp (even if no-op)

=============== Diff against Tests-tpr.386 ===============

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-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-System-Digital Signatures'!
- SystemOrganization addCategory: #'Tests-System-Preferences'!

Item was changed:
+ ----- Method: MCDictionaryRepositoryTest>>addVersion: (in category 'actions') -----
- ----- Method: MCDictionaryRepositoryTest>>addVersion: (in category 'as yet unclassified') -----
  addVersion: aVersion
  	dict at: aVersion info put: aVersion!

Item was changed:
+ ----- Method: MCDictionaryRepositoryTest>>deleteNode: (in category 'actions') -----
- ----- Method: MCDictionaryRepositoryTest>>deleteNode: (in category 'as yet unclassified') -----
  deleteNode: aNode
  	dict removeKey: aNode!

Item was changed:
+ ----- Method: MCDictionaryRepositoryTest>>dictionary (in category 'accessing') -----
- ----- Method: MCDictionaryRepositoryTest>>dictionary (in category 'as yet unclassified') -----
  dictionary
  	^ dict ifNil: [dict := Dictionary new]!

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

Item was changed:
+ ----- Method: MCDirectoryRepositoryTest>>addVersion: (in category 'actions') -----
- ----- Method: MCDirectoryRepositoryTest>>addVersion: (in category 'as yet unclassified') -----
  addVersion: aVersion
  	| file |
  	file := FileStream newFileNamed: (directory fullNameFor: aVersion fileName).
  	aVersion fileOutOn: file.
  	file close.!

Item was changed:
+ ----- Method: MCDirectoryRepositoryTest>>directory (in category 'accessing') -----
- ----- Method: MCDirectoryRepositoryTest>>directory (in category 'as yet unclassified') -----
  directory
  	directory ifNil:
  		[directory := FileDirectory default directoryNamed: 'mctest'.
  		directory assureExistence].
  	^ directory!

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

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

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!
- 			do: [:each | each removeFromSystem]!

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

Item was changed:
+ ----- Method: MCInitializationTest>>testWorkingCopy (in category 'tests') -----
- ----- Method: MCInitializationTest>>testWorkingCopy (in category 'as yet unclassified') -----
  testWorkingCopy
  	MczInstaller storeVersionInfo: self mockVersion.
  	MCWorkingCopy initialize.
  	MCWorkingCopy allManagers
  						detect: [:man | man package name = self mockPackage name]
  						ifNone: [self assert: false]!

Item was changed:
+ ----- Method: MCMczInstallerTest>>assertDict:matchesInfo: (in category 'asserting') -----
- ----- Method: MCMczInstallerTest>>assertDict:matchesInfo: (in category 'as yet unclassified') -----
  assertDict: dict matchesInfo: info
  	#(name id message date time author)
  		do: [:sel |  (info perform: sel) ifNotNil: [:i | dict at: sel ifPresent: [:d | self assert: i = d]]].
  	info ancestors 
  			with: (dict at: #ancestors) 
  			do: [:i :d | self assertDict: d matchesInfo: i]!

Item was changed:
+ ----- Method: MCMczInstallerTest>>assertNoChange (in category 'asserting') -----
- ----- Method: MCMczInstallerTest>>assertNoChange (in category 'as yet unclassified') -----
  assertNoChange
  	| actual |
  	actual := MCSnapshotResource takeSnapshot.
  	diff := actual patchRelativeToBase: expected snapshot.
  	self assert: diff isEmpty!

Item was changed:
+ ----- Method: MCMczInstallerTest>>assertVersionInfoPresent (in category 'asserting') -----
- ----- Method: MCMczInstallerTest>>assertVersionInfoPresent (in category 'as yet unclassified') -----
  assertVersionInfoPresent
  	| dict info |
  	dict := MczInstaller versionInfo at: self mockPackage name.
  	info := expected info.
  	self assertDict: dict matchesInfo: info.!

Item was changed:
+ ----- Method: MCMczInstallerTest>>defaultTimeout (in category 'accessing') -----
- ----- Method: MCMczInstallerTest>>defaultTimeout (in category 'as yet unclassified') -----
  defaultTimeout
  
  	^ super defaultTimeout * 10 "seconds"!

Item was changed:
+ ----- Method: MCMczInstallerTest>>deleteFile (in category 'actions') -----
- ----- Method: MCMczInstallerTest>>deleteFile (in category 'as yet unclassified') -----
  deleteFile
  	(FileDirectory default fileExists: self fileName)
  		ifTrue: [FileDirectory default deleteFileNamed: self fileName]!

Item was changed:
+ ----- Method: MCMczInstallerTest>>fileName (in category 'accessing') -----
- ----- Method: MCMczInstallerTest>>fileName (in category 'as yet unclassified') -----
  fileName
  	^ 'InstallerTest.mcz' asMCVersionName!

Item was changed:
+ ----- Method: MCMczInstallerTest>>fileStream (in category 'accessing') -----
- ----- Method: MCMczInstallerTest>>fileStream (in category 'as yet unclassified') -----
  fileStream
  	^ FileStream forceNewFileNamed: self fileName.!

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

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

Item was changed:
+ ----- Method: MCMczInstallerTest>>testInstallFromFile (in category 'testing') -----
- ----- Method: MCMczInstallerTest>>testInstallFromFile (in category 'as yet unclassified') -----
  testInstallFromFile
  	MCMczWriter fileOut: expected on: self fileStream.
  	MczInstaller installFileNamed: self fileName.
  	self assertNoChange.!

Item was changed:
+ ----- Method: MCMczInstallerTest>>testInstallFromStream (in category 'testing') -----
- ----- Method: MCMczInstallerTest>>testInstallFromStream (in category 'as yet unclassified') -----
  testInstallFromStream
  	| stream |
  	stream := RWBinaryOrTextStream on: String new.
  	MCMczWriter fileOut: expected on: stream.
  	MczInstaller installStream: stream reset.
  	self assertNoChange.
  	self assertVersionInfoPresent.
  	!

Item was changed:
  MCTestCase subclass: #MCMethodDefinitionTest
+ 	instanceVariableNames: 'navigation isModified overrideTimestamp extensionPackage'
- 	instanceVariableNames: 'navigation isModified overrideTimestamp'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tests-Monticello'!

Item was changed:
  ----- Method: MCMethodDefinitionTest>>setUp (in category 'running') -----
  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.
- 	(MCWorkingCopy forPackage: (MCPackage named: 'FooBarBaz')) unregister.
  	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
  !

Item was changed:
+ ----- Method: MCOrganizationTest>>testReordering (in category 'testing') -----
- ----- Method: MCOrganizationTest>>testReordering (in category 'as yet unclassified') -----
  testReordering
  	|dec cats newCats |
  	dec := MCOrganizationDefinition categories: #(A B C).
  	cats := #(X Y B Z C A Q).
  	newCats := dec reorderCategories: cats original: #(B C A).
  	self assert: newCats asArray = #(X Y A B C Z Q).!

Item was changed:
+ ----- Method: MCOrganizationTest>>testReorderingWithNoCategoriesInVersion (in category 'testing') -----
- ----- Method: MCOrganizationTest>>testReorderingWithNoCategoriesInVersion (in category 'as yet unclassified') -----
  testReorderingWithNoCategoriesInVersion
  	|dec cats newCats |
  	dec := MCOrganizationDefinition categories: #().
  	cats := #(X Y B Z C A Q).
  	newCats := dec reorderCategories: cats original: #().
  	self assert: newCats asArray = cats.!

Item was changed:
+ ----- Method: MCOrganizationTest>>testReorderingWithRemovals (in category 'testing') -----
- ----- Method: MCOrganizationTest>>testReorderingWithRemovals (in category 'as yet unclassified') -----
  testReorderingWithRemovals
  	|dec cats newCats |
  	dec := MCOrganizationDefinition categories: #(A B C).
  	cats := #(X Y B Z C A Q).
  	newCats := dec reorderCategories: cats original: #(Y B C A Q).
  	self assert: newCats asArray = #(X A B C Z).!

Item was changed:
+ ----- Method: MCPatchTest>>setUp (in category 'running') -----
- ----- Method: MCPatchTest>>setUp (in category 'as yet unclassified') -----
  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') -----
- ----- Method: MCPatchTest>>tearDown (in category 'as yet unclassified') -----
  tearDown
  
  	super tearDown.
  	self restoreMocks!

Item was changed:
+ ----- Method: MCPatchTest>>testPatchContents (in category 'testing') -----
- ----- Method: MCPatchTest>>testPatchContents (in category 'as yet unclassified') -----
  testPatchContents
  	self assert: patch operations size = 1.
  	self assert: patch operations first isModification.
  	self assert: patch operations first definition selector = #one.
  !

Item was changed:
  MCTestCase subclass: #MCRepositoryTest
+ 	instanceVariableNames: 'repository'
- 	instanceVariableNames: 'repository ancestors'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tests-Monticello'!
+ 
+ !MCRepositoryTest commentStamp: 'nice 12/7/2017 00:08' prior: 0!
+ Abstract superclass for Monticello Repository tests
+ 
+ Instance Variables
+ 	repository:		<MCRepository>
+ 
+ repository
+ 	- the instance of MCRepository subclass being tested
+ !

Item was changed:
+ ----- Method: MCSnapshotResource>>definitions (in category 'accessing') -----
- ----- Method: MCSnapshotResource>>definitions (in category 'as yet unclassified') -----
  definitions
  	^ snapshot definitions!

Item was changed:
+ ----- Method: MCSnapshotResource>>setUp (in category 'running') -----
- ----- Method: MCSnapshotResource>>setUp (in category 'as yet unclassified') -----
  setUp
  	snapshot := self class takeSnapshot.!

Item was changed:
+ ----- Method: MCSnapshotResource>>snapshot (in category 'accessing') -----
- ----- Method: MCSnapshotResource>>snapshot (in category 'as yet unclassified') -----
  snapshot
  	^ snapshot!

Item was changed:
+ ----- Method: MCStReaderTest>>commentWithStyle (in category 'accessing') -----
- ----- Method: MCStReaderTest>>commentWithStyle (in category 'as yet unclassified') -----
  commentWithStyle
  	^ '!!AEDesc commentStamp: ''<historical>'' prior: 0!!
  I represent an Apple Event Descriptor.  I am a low-level representation of Apple Event (and hence Applescript) information.  For further Information, see Apple''s Inside Macintosh: Interapplication Communications, at
  
  	http://developer.apple.com/techpubs/mac/IAC/IAC-2.html.
  
  Essentially, I represent a record comprising a one-word "string" (treating the word as fourbyte characters) representing a data type, followed by a pointer to a pointer (a handle) to the data I represent.  Care must be taken to assure that the Handle data is disposed after use, or memory leaks result.  At this time, I make no effort to do this automatically through finalization.!!
  ]style[(218 54 384)f1,f1Rhttp://developer.apple.com/techpubs/mac/IAC/IAC-2.html;,f1!!
  '!

Item was changed:
+ ----- Method: MCStReaderTest>>commentWithoutStyle (in category 'accessing') -----
- ----- Method: MCStReaderTest>>commentWithoutStyle (in category 'as yet unclassified') -----
  commentWithoutStyle
  	^ '
  CharacterScanner subclass: #CanvasCharacterScanner
  	instanceVariableNames: ''canvas fillBlt foregroundColor runX lineY ''
  	classVariableNames: ''''
  	poolDictionaries: ''''
  	category: ''Morphic-Support''!!
  
  !!CanvasCharacterScanner commentStamp: ''<historical>'' prior: 0!!
  A displaying scanner which draws its output to a Morphic canvas.!!
  
  !!CanvasCharacterScanner methodsFor: ''stop conditions'' stamp: ''ar 12/15/2001 23:27''!!
  setStopConditions
  	"Set the font and the stop conditions for the current run."
  
  	self setFont.
  	stopConditions
  		at: Space asciiValue + 1
  		put: (alignment = Justified ifTrue: [#paddedSpace])!! !!'!

Item was changed:
+ ----- Method: MCStReaderTest>>methodWithStyle (in category 'accessing') -----
- ----- Method: MCStReaderTest>>methodWithStyle (in category 'as yet unclassified') -----
  methodWithStyle
  	^ '!!EventHandler methodsFor: ''copying'' stamp: ''tk 1/22/2001 17:39''!!
  veryDeepInner: deepCopier
  	"ALL fields are weakly copied.  Can''t duplicate an object by duplicating a button that activates it.  See DeepCopier."
  
  	super veryDeepInner: deepCopier.
  	"just keep old pointers to all fields"
  	clickRecipient := clickRecipient.!!
  ]style[(25 108 10 111)f1b,f1,f1LDeepCopier Comment;,f1!! !!
  
  '!

Item was changed:
+ ----- Method: MCStReaderTest>>testCommentWithStyle (in category 'tests') -----
- ----- Method: MCStReaderTest>>testCommentWithStyle (in category 'as yet unclassified') -----
  testCommentWithStyle
  	| reader |
  	reader := MCStReader on: self commentWithStyle readStream.
  	reader definitions!

Item was changed:
+ ----- Method: MCStReaderTest>>testCommentWithoutStyle (in category 'tests') -----
- ----- Method: MCStReaderTest>>testCommentWithoutStyle (in category 'as yet unclassified') -----
  testCommentWithoutStyle
  	| reader |
  	reader := MCStReader on: self commentWithoutStyle readStream.
  	self assert: (reader definitions anySatisfy: [:ea | ea isMethodDefinition]).!

Item was changed:
+ ----- Method: MCStReaderTest>>testMethodWithStyle (in category 'tests') -----
- ----- Method: MCStReaderTest>>testMethodWithStyle (in category 'as yet unclassified') -----
  testMethodWithStyle
  	| reader |
  	reader := MCStReader on: self methodWithStyle readStream.
  	self assert: reader definitions first isMethodDefinition.!

Item was changed:
  TestCase subclass: #MCTestCase
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tests-Monticello'!
+ 
+ !MCTestCase commentStamp: 'nice 12/7/2017 00:11' prior: 0!
+ Abstract superclass for Monticello tests
+ Monticello is the distributed source code management system.!

Item was changed:
+ ----- Method: MCVersionNameTest>>allValidFixtures (in category 'accessing') -----
- ----- Method: MCVersionNameTest>>allValidFixtures (in category 'as yet unclassified') -----
  allValidFixtures
  	^ self standardFixtures , (self diffyFixtures pairsCollect: [:diffy :base | diffy])!

Item was changed:
+ ----- Method: MCVersionNameTest>>diffyBranchFixtures (in category 'accessing') -----
- ----- Method: MCVersionNameTest>>diffyBranchFixtures (in category 'as yet unclassified') -----
  diffyBranchFixtures
  	^ #( 'Package.branch-author.123(origAuthor.122)' 'Package.branch-origAuthor.122'
  		 'Package.branch-author.123(origAuthor.122).mcd' 'Package.branch-origAuthor.122.mcd'
  		 'Package.branch-author.123(122)' 'Package.branch-author.122'
  		 'Package.branch-author.123(@origPackage-origAuthor.122)' 'origPackage-origAuthor.122'
  		 'Package-author.123(@origPackage.branch-origAuthor.122)' 'origPackage.branch-origAuthor.122'
  	 ) collect:
  		[ : each | each asMCVersionName ]!

Item was changed:
+ ----- Method: MCVersionNameTest>>diffyFixtures (in category 'accessing') -----
- ----- Method: MCVersionNameTest>>diffyFixtures (in category 'as yet unclassified') -----
  diffyFixtures
  	^ #( 'Package-author.123(origAuthor.122)' 'Package-origAuthor.122'
  		 'Package-author.123(origAuthor.122).mcd' 'Package-origAuthor.122.mcd'
  		 'Package-author.123(122)' 'Package-author.122'
  		 'Package-author.123(@origPackage-origAuthor.122)' 'origPackage-origAuthor.122'
  	 ) collect:
  		[ : each | each asMCVersionName ]!

Item was changed:
+ ----- Method: MCVersionNameTest>>invalidFixtures (in category 'accessing') -----
- ----- Method: MCVersionNameTest>>invalidFixtures (in category 'as yet unclassified') -----
  invalidFixtures
  	^ {String empty. 'abc'. '123' } collect: [ : each | each asMCVersionName ]!

Item was changed:
+ ----- Method: MCVersionNameTest>>standardFixtures (in category 'accessing') -----
- ----- Method: MCVersionNameTest>>standardFixtures (in category 'as yet unclassified') -----
  standardFixtures
  	^ #('Package-author.123' 'Package-author.123.mcz' ) collect:
  		[ : each | each asMCVersionName ]!

Item was changed:
+ ----- Method: MCVersionNameTest>>verifyDiffy:base: (in category 'tests') -----
- ----- Method: MCVersionNameTest>>verifyDiffy:base: (in category 'as yet unclassified') -----
  verifyDiffy: diffyMCVersionName base: expectedBaseMCVersionName 
  	self
  		 assert: diffyMCVersionName baseVersionName = expectedBaseMCVersionName!

Item was changed:
+ ----- Method: MCVersionNameTest>>verifyPackageAuthorVersion: (in category 'tests') -----
- ----- Method: MCVersionNameTest>>verifyPackageAuthorVersion: (in category 'as yet unclassified') -----
  verifyPackageAuthorVersion: aMCFileName 
  	self
  		 assert: aMCFileName versionName = 'Package-author.123';
  		 assert: aMCFileName packageName = 'Package' ;
  		 assert: aMCFileName versionNumber = 123 ;
  		 assert: aMCFileName author = 'author' ;
  		 assert: aMCFileName isValid!



More information about the Packages mailing list