[squeak-dev] The Trunk: SUnit-ct.134.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 10 18:00:33 UTC 2022


Christoph Thiede uploaded a new version of SUnit to project The Trunk:
http://source.squeak.org/trunk/SUnit-ct.134.mcz

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

Name: SUnit-ct.134
Author: ct
Time: 10 January 2022, 7:00:31.749518 pm
UUID: 58075322-d9b6-f64f-aef1-38b6b31a20d9
Ancestors: SUnit-ct.122, SUnit-ct.128, SUnit-ct.131, SUnit-ct.132, SUnit-ct.133, SUnit-mt.125

Merge commit.

SUnit-ct.122:
	Add check for a TestCase whether it is still installed (that is, the test selector has not been removed).

SUnit-ct.128:
	Refactor & speed up timeout tests in SUnitTest (woohoo, reduced the total test runner time by 9 seconds!).

SUnit-ct.131:
	Don't save #lastStoredRun results into the source package. See also ReleaseBuilder class >>#discardUserObjects.

SUnit-ct.132:
	Refactors, completes, and tests equality assertions.
	
	Revision: Rename #description:with: to #failureDescription:with:. Rewrite new tests to make use of underrated #should:raise:withExceptionDo:. Thanks to Marcel (mt)!

SUnit-ct.133:
	Updates debugging logic of TestCase. Instead of abusing #halt, open a debugger directly on the entrypoint to run the case. Deprecates #openDebuggerOnFailingTestMethod.

One more thing:
	Polishes all test cases in this package to include proper sends to super when overriding #setUp/#tearDown.

=============== Diff against SUnit-mt.125 ===============

Item was removed:
- ----- Method: ClassFactoryForTestCaseTest class>>lastStoredRun (in category 'history') -----
- lastStoredRun
- 	^ ((Dictionary new) add: (#passed->((Set new) add: #testDefaultCategoryCleanUp; add: #testPackageCleanUp; add: #testSingleClassCreation; add: #testClassCreationInDifferentCategories; add: #testClassFastCreationInDifferentCategories; add: #testMultipleClassCreation; add: #testSingleClassFastCreation; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)!

Item was changed:
  ----- Method: ClassFactoryForTestCaseTest>>tearDown (in category 'running') -----
  tearDown
+ 	
+ 	[factory cleanUp]
+ 		ensure: [super tearDown].!
- 	super tearDown.
- 	factory cleanUp!

Item was changed:
  ----- Method: LongTestCaseTest>>setUp (in category 'running') -----
  setUp
  
+ 	super setUp.
+ 	
  	preferenceValue := LongTestCase shouldRun!

Item was changed:
  ----- Method: LongTestCaseTest>>tearDown (in category 'running') -----
  tearDown
  
+ 	[LongTestCase shouldRun: preferenceValue]
+ 		ensure: [super tearDown].!
- 	LongTestCase shouldRun: preferenceValue!

Item was removed:
- ----- Method: ResumableTestFailureTestCase class>>lastStoredRun (in category 'history') -----
- lastStoredRun
- 	^ ((Dictionary new) add: (#passed->((Set new) add: #testResumable; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)!

Item was removed:
- ----- Method: SUnitExtensionsTest class>>lastStoredRun (in category 'history') -----
- lastStoredRun
- 	^ ((Dictionary new) add: (#passed->((Set new) add: #testNoExceptionWithMatchingString; add: #testNoExceptionWithNoMatchingString; add: #testExceptionWithMatchingString; add: #testExceptionWithoutMatchingString; add: #testValidShouldNotTakeMoreThan; add: #testInvalidShouldNotTakeMoreThanMilliseconds; add: #testDifferentExceptionInShouldRaiseWithExceptionDo; add: #testShouldRaiseWithExceptionDo; add: #testShouldFix; add: #testAssertionFailedInRaiseWithExceptionDo; add: #testAutoDenyFalse; add: #testAutoDenyTrue; add: #testAutoAssertFalse; add: #testAutoAssertTrue; add: #testValidShouldNotTakeMoreThanMilliseconds; add: #testErrorInRaiseWithExceptionDo; add: #testNoExceptionInShouldRaiseWithExceptionDo; add: #testInvalidShouldNotTakeMoreThan; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)!

Item was removed:
- ----- Method: SUnitTest class>>lastStoredRun (in category 'history') -----
- lastStoredRun
- 	^ ((Dictionary new) add: (#passed->((Set new) add: #testWithExceptionDo; add: #testRan; add: #testAssert; add: #testRanOnlyOnce; add: #testDialectLocalizedException; add: #testFail; add: #testDefects; add: #testIsNotRerunOnDebug; add: #testResult; add: #testRunning; add: #testError; add: #testException; add: #testShould; add: #testSuite; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)!

Item was added:
+ ----- Method: SUnitTest>>defaultTimeout (in category 'accessing') -----
+ defaultTimeout
+ 
+ 	self selector = #testTestTimeout ifTrue: [
+ 		^ 0.3 "seconds"].
+ 	^ super defaultTimeout!

Item was changed:
  ----- Method: SUnitTest>>setUp (in category 'running') -----
  setUp
+ 
+ 	super setUp.
+ 	
+ 	hasSetup := true.!
- 	hasSetup := true
- 			!

Item was added:
+ ----- Method: SUnitTest>>testAssertEquals (in category 'tests') -----
+ testAssertEquals
+ 
+ 	| a b |
+ 	a := 'foo'.
+ 	b := 'bar'.
+ 	
+ 	self shouldnt: [self assert: a equals: a copy] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self assert: a equals: b]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			| error |
+ 			error := ex messageText.
+ 			self
+ 				assert: (error includesSubstring: a)
+ 				description: 'Error message doesn''t include the expected value'.
+ 			self
+ 				assert: (error includesSubstring: b)
+ 				description: 'Error message doesn''t include the actual value'].!

Item was added:
+ ----- Method: SUnitTest>>testAssertEqualsDescription (in category 'tests') -----
+ testAssertEqualsDescription
+ 
+ 	| a b called |
+ 	a := 'foo'.
+ 	b := 'bar'.
+ 	
+ 	self shouldnt: [self assert: a equals: a copy description: 'A description42'] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self assert: a equals: b description: 'A description42']
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A description42')
+ 				description: 'Error message doesn''t give you the description'].
+ 	
+ 	called := false.
+ 	self shouldnt: [self assert: a equals: a description: [called := true]] raise: TestFailure.
+ 	self deny: called description: 'Description block was evaluated prematurely'.
+ 	
+ 	self
+ 		should: [self assert: a equals: b description: ['A generated description' asUppercase]]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A generated description' asUppercase)
+ 				description: 'Error message doesn''t give you the generated description'].!

Item was changed:
  ----- Method: SUnitTest>>testAssertIdentical (in category 'tests') -----
  testAssertIdentical
+ 
  	| a b |
  	a := 'foo'.
  	b := 'bar'.
+ 	
+ 	self shouldnt: [self assert: a identical: a] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self assert: a identical: b]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			| error |
+ 			error := ex messageText.
+ 			self
+ 				assert: (error includesSubstring: a)
+ 				description: 'Error message doesn''t include the expected value'.
+ 			self
+ 				assert: (error includesSubstring: b)
+ 				description: 'Error message doesn''t include the actual value'].!
- 	self should: [self assert: a identical: b] raise: TestFailure.
- 	[self assert: a identical: b] on: TestFailure do: [:e | |error|
- 		error := e messageText.
- 		self assert: (error includesSubstring: a) description: 'Error message doesn''t include the expected value'.
- 		self assert: (error includesSubstring: b) description: 'Error message doesn''t include the expected value'].!

Item was changed:
  ----- Method: SUnitTest>>testAssertIdenticalDescription (in category 'tests') -----
  testAssertIdenticalDescription
+ 
+ 	| a b called |
- 	| a b |
  	a := 'foo'.
  	b := a copy.
+ 	
+ 	self shouldnt: [self assert: a identical: a description: 'A description42'] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self assert: a identical: b description: 'A description42']
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A description42')
+ 				description: 'Error message doesn''t give you the description'].
+ 	
+ 	called := false.
+ 	self shouldnt: [self assert: a identical: a description: [called := true]] raise: TestFailure.
+ 	self deny: called description: 'Description block was evaluated prematurely'.
+ 	
+ 	self
+ 		should: [self assert: a identical: b description: ['A generated description' asUppercase]]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A generated description' asUppercase)
+ 				description: 'Error message doesn''t give you the generated description'].!
- 	self should: [self assert: a identical: b description: 'A desciption'] raise: TestFailure.
- 	[self assert: a identical: b description: 'A desciption'] on: TestFailure do: [:e | |error|
- 		error := e messageText.
- 		self assert: (error includesSubstring: 'A desciption') description: 'Error message doesn''t give you the description'].!

Item was changed:
  ----- Method: SUnitTest>>testAssertIdenticalWithEqualObjects (in category 'tests') -----
  testAssertIdenticalWithEqualObjects
+ 
  	| a b |
  	a := 'foo'.
  	b := a copy.
+ 	
+ 	self
+ 		should: [self assert: a identical: b]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'not identical')
+ 				description: 'Error message doesn''t say the two things aren''t identical'].!
- 	self should: [self assert: a identical: b] raise: TestFailure.
- 	[self assert: a identical: b] on: TestFailure do: [:e | |error|
- 		error := e messageText.
- 		self assert: (error includesSubstring: 'not identical') description: 'Error message doesn''t say the two things aren''t identical'].!

Item was added:
+ ----- Method: SUnitTest>>testDenyEquals (in category 'tests') -----
+ testDenyEquals
+ 
+ 	| a b |
+ 	a := 'foo'.
+ 	b := 'bar'.
+ 	
+ 	self shouldnt: [self deny: a equals: b] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self deny: a equals: a copy]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: a)
+ 				description: 'Error message doesn''t include the unexpected value'].!

Item was added:
+ ----- Method: SUnitTest>>testDenyEqualsDescription (in category 'tests') -----
+ testDenyEqualsDescription
+ 
+ 	| a b called |
+ 	a := 'foo'.
+ 	b := 'bar'.
+ 	
+ 	self shouldnt: [self deny: a equals: b description: 'A description42'] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self deny: a equals: a copy description: 'A description42']
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A description42')
+ 				description: 'Error message doesn''t give you the description'].
+ 	
+ 	called := false.
+ 	self shouldnt: [self deny: a equals: b description: [called := true]] raise: TestFailure.
+ 	self deny: called description: 'Description block was evaluated prematurely'.
+ 	
+ 	self
+ 		should: [self deny: a equals: a description: ['A generated description' asUppercase]]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A generated description' asUppercase)
+ 				description: 'Error message doesn''t give you the generated description'].!

Item was added:
+ ----- Method: SUnitTest>>testDenyIdentical (in category 'tests') -----
+ testDenyIdentical
+ 
+ 	| a b |
+ 	a := 'foo'.
+ 	b := 'bar'.
+ 	self shouldnt: [self deny: a identical: b] raise: TestFailure.
+ 	self
+ 		should: [self deny: a identical: a]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: a)
+ 				description: 'Error message doesn''t include the unexpected value'].!

Item was added:
+ ----- Method: SUnitTest>>testDenyIdenticalDescription (in category 'tests') -----
+ testDenyIdenticalDescription
+ 
+ 	| a b called |
+ 	a := 'foo'.
+ 	b := a copy.
+ 	
+ 	self shouldnt: [self deny: a identical: b description: 'A description42'] raise: TestFailure.
+ 	
+ 	self
+ 		should: [self deny: a identical: a description: 'A description42']
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A description42')
+ 				description: 'Error message doesn''t give you the description'].
+ 	
+ 	called := false.
+ 	self shouldnt: [self deny: a identical: b description: [called := true]] raise: TestFailure.
+ 	self deny: called description: 'Description block was evaluated prematurely'.
+ 	
+ 	self
+ 		should: [self deny: a identical: a description: ['A generated description' asUppercase]]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'A generated description' asUppercase)
+ 				description: 'Error message doesn''t give you the description'].!

Item was added:
+ ----- Method: SUnitTest>>testDenyIdenticalWithEqualObjects (in category 'tests') -----
+ testDenyIdenticalWithEqualObjects
+ 
+ 	| a b |
+ 	a := 'foo'.
+ 	b := a copy.
+ 	self
+ 		should: [self deny: a identical: a]
+ 		raise: TestFailure
+ 		withExceptionDo: [:ex |
+ 			self
+ 				assert: (ex messageText includesSubstring: 'identical')
+ 				description: 'Error message doesn''t say the two things are identical'].!

Item was changed:
  ----- Method: SUnitTest>>testRunning (in category 'tests') -----
  testRunning
  
+ 	0.2 seconds wait.
- 	(Delay forSeconds: 2) wait
  			!

Item was changed:
  ----- Method: SUnitTest>>testTestTimeout (in category 'tests') -----
  testTestTimeout
+ 
+ 	self
+ 		shouldnt: [(self timeoutForTest / 2) seconds wait]
+ 		raise: TestFailure.
+ 	self
+ 		should: [(self timeoutForTest / 2 + 0.1) seconds wait]
+ 		raise: TestFailure.!
- 	self should:[(Delay forSeconds: (self timeoutForTest + 1)) wait] raise: TestFailure.
- !

Item was changed:
  ----- Method: SUnitTest>>testTestTimeoutLoop (in category 'tests') -----
  testTestTimeoutLoop
+ 	<timeout: 0.1 "seconds">
+ 	self
+ 		should: [[] repeat]
+ 		raise: TestFailure.
- 	<timeout: 1>
- 	self should:[[] repeat] raise: TestFailure.
  !

Item was added:
+ ----- Method: SUnitTest>>testTestTimeoutPragma (in category 'tests') -----
+ testTestTimeoutPragma
+ 	<timeout: 0.1 "seconds">
+ 	self
+ 		shouldnt: [0.05 seconds wait]
+ 		raise: TestFailure.
+ 	self
+ 		should: [0.05 seconds wait]
+ 		raise: TestFailure.
+ !

Item was removed:
- ----- Method: SUnitTest>>testTestTimeoutTag (in category 'tests') -----
- testTestTimeoutTag
- 	<timeout: 1>
- 	self should:[(Delay forSeconds: 3) wait] raise: TestFailure.
- !

Item was removed:
- ----- Method: SimpleTestResourceTestCase class>>lastStoredRun (in category 'history') -----
- lastStoredRun
- 	^ ((Dictionary new) add: (#passed->((Set new) add: #testResourceInitRelease; add: #testResourcesCollection; add: #testRan; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)!

Item was changed:
  ----- Method: SimpleTestResourceTestCase>>setUp (in category 'running') -----
  setUp
+ 
+ 	super setUp.
+ 	
  	resource := SimpleTestResource current
  			!

Item was changed:
  ----- Method: TestCase class>>generateLastStoredRunMethod (in category 'history') -----
  generateLastStoredRunMethod
  
  	self shouldGenerateLastStoredRunMethod ifTrue: [
  		self class
  			compile: (self lastRunMethodNamed: #lastStoredRun)
+ 			classified: '*autogenerated-history' ]!
- 			classified: 'history' ]!

Item was changed:
  ----- Method: TestCase class>>lastRunMethodNamed: (in category 'history') -----
  lastRunMethodNamed: aSelector
  	
+ 	^ String streamContents: [:stream |
+ 		stream
+ 			nextPutAll: aSelector asString;
+ 			crtab; nextPutAll: ('<autogenerated> "See {1}"' format: {thisContext home});
+ 			crtab; nextPutAll: '^ ', (self lastRun) storeString]
- 	^ String streamContents: [:str |
- 		str nextPutAll: aSelector asString ;cr.
- 		str tab; nextPutAll: '^ ', (self lastRun) storeString]
  !

Item was changed:
  ----- Method: TestCase>>assert:equals: (in category 'asserting') -----
  assert: expected equals: actual
  
+ 	^ self
+ 		assert: expected
+ 		equals: actual
+ 		description: nil
- 	^self
- 		assert: expected = actual
- 		description: [ self comparingStringBetween: expected and: actual ]
  !

Item was changed:
  ----- Method: TestCase>>assert:equals:description: (in category 'asserting') -----
+ assert: expected equals: actual description: aStringOrBlock
- assert: expected equals: actual description: aString
  
+ 	^ self
- 	^self
  		assert: expected = actual
+ 		description: [self
+ 			failureDescription: aStringOrBlock
+ 			with: (self comparingStringBetween: expected and: actual)]!
- 		description: [ aString , ': ', (self comparingStringBetween: expected and: actual) ]!

Item was changed:
  ----- Method: TestCase>>assert:identical: (in category 'asserting') -----
  assert: expected identical: actual
  
+ 	^ self
+ 		assert: expected
+ 		identical: actual
+ 		description: nil!
- 	^self
- 		assert: expected == actual
- 		description: [ self comparingStringBetweenIdentical: expected and: actual ]
- !

Item was changed:
  ----- Method: TestCase>>assert:identical:description: (in category 'asserting') -----
+ assert: expected identical: actual description: aStringOrBlock
- assert: expected identical: actual description: aString
  
+ 	^ self
- 	^self
  		assert: expected == actual
+ 		description: [self
+ 			failureDescription: aStringOrBlock
+ 			with: (self comparingStringBetween: expected andIdentical: actual)]!
- 		description: [ aString , ': ', (self comparingStringBetweenIdentical: expected and: actual) ]!

Item was added:
+ ----- Method: TestCase>>assureResourcesDuring: (in category 'private') -----
+ assureResourcesDuring: aBlock
+ 
+ 	| resources |
+ 	resources := self resources.
+ 	resources do: [:resource |
+ 		resource isAvailable ifFalse: [
+ 			resource signalInitializationError]].
+ 	^ aBlock ensure: [
+ 		resources do: [:resource |
+ 			resource reset]].!

Item was changed:
  ----- Method: TestCase>>comparingStringBetween:and: (in category 'private') -----
  comparingStringBetween: expected and: actual
+ 
+ 	^ 'Expected {1} but was {2}.' translated
+ 		format: {
+ 			expected printStringLimitedTo: 10.
+ 			actual printStringLimitedTo: 10 }!
- 	^ String streamContents: [:stream |
- 		stream
- 			nextPutAll: 'Expected ';
- 			nextPutAll: (expected printStringLimitedTo: 10);
- 			nextPutAll: ' but was ';
- 			nextPutAll: (actual printStringLimitedTo: 10);
- 			nextPutAll: '.'
- 		]!

Item was added:
+ ----- Method: TestCase>>comparingStringBetween:andIdentical: (in category 'private') -----
+ comparingStringBetween: expected andIdentical: actual
+ 
+ 	^ 'Expected {1} and actual {2} are not identical.' translated
+ 		format: {
+ 			expected printStringLimitedTo: 10.
+ 			actual printStringLimitedTo: 10 }!

Item was removed:
- ----- Method: TestCase>>comparingStringBetweenIdentical:and: (in category 'private') -----
- comparingStringBetweenIdentical: expected and: actual
- 	^ 'Expected {1} and actual {2} are not identical.' format: {
- 		expected printStringLimitedTo: 10.
- 		actual printStringLimitedTo: 10.
- 	}!

Item was added:
+ ----- Method: TestCase>>comparingStringBetweenUnexpected:and: (in category 'private') -----
+ comparingStringBetweenUnexpected: unexpected and: actual
+ 
+ 	^ 'Did not expect {1} but was {2}.' translated
+ 		format: {
+ 			unexpected printStringLimitedTo: 10.
+ 			actual printStringLimitedTo: 10 }!

Item was added:
+ ----- Method: TestCase>>comparingStringBetweenUnexpected:andIdentical: (in category 'private') -----
+ comparingStringBetweenUnexpected: expected andIdentical: actual
+ 
+ 	^ 'Unexpected {1} and actual {2} are identical.' translated
+ 		format: {
+ 			expected printStringLimitedTo: 10.
+ 			actual printStringLimitedTo: 10 }!

Item was changed:
  ----- Method: TestCase>>debug (in category 'running') -----
  debug
+ 	"Run the receiver and open a debugger on the first failure or error."
+ 
+ 	^ self assureResourcesDuring: [self runCaseWithoutTimeout]!
- 	self resources do:
- 		[ : res | res isAvailable ifFalse: [ ^ res signalInitializationError ] ].
- 	[ self runCase ] ensure:
- 		[ self resources do:
- 			[ : each | each reset ] ]!

Item was changed:
  ----- Method: TestCase>>debugAsFailure (in category 'running') -----
  debugAsFailure
+ 	"Spawn a debugger that is ready to debug the receiver."
+ 
+ 	(Process
+ 		forBlock: [self debug]
+ 		runUntil: [:context | context isClosureContext "navigate the process directly to the point where it is about to send #setUp"
+ 			and: [context selector = #runCaseWithoutTimeout]])
+ 				debug.!
- 	| semaphore |
- 	semaphore := Semaphore new.
- 	self resources do: [:res | 
- 		res isAvailable ifFalse: [^res signalInitializationError]].
- 	[semaphore wait. self resources do: [:each | each reset]] fork.
- 	(self class selector: testSelector) runCaseAsFailure: semaphore.!

Item was changed:
  ----- Method: TestCase>>deny:equals: (in category 'asserting') -----
  deny: unexpected equals: actual
  
+ 	^ self
+ 		deny: unexpected
+ 		equals: actual
+ 		description: nil!
- 	^self
- 		deny: unexpected = actual
- 		description: 'Actual equals unexpected'
- !

Item was added:
+ ----- Method: TestCase>>deny:equals:description: (in category 'asserting') -----
+ deny: unexpected equals: actual description: aStringOrBlock
+ 
+ 	^ self
+ 		deny: unexpected = actual
+ 		description: [self
+ 			failureDescription: aStringOrBlock
+ 			with: (self comparingStringBetweenUnexpected: unexpected and: actual)]!

Item was added:
+ ----- Method: TestCase>>deny:identical: (in category 'asserting') -----
+ deny: unexpected identical: actual
+ 
+ 	^ self
+ 		deny: unexpected
+ 		identical: actual
+ 		description: nil!

Item was added:
+ ----- Method: TestCase>>deny:identical:description: (in category 'asserting') -----
+ deny: unexpected identical: actual description: aStringOrBlock
+ 
+ 	^ self
+ 		deny: unexpected == actual
+ 		description: [self
+ 			failureDescription: aStringOrBlock
+ 			with: (self comparingStringBetweenUnexpected: unexpected andIdentical: actual)]!

Item was added:
+ ----- Method: TestCase>>failureDescription:with: (in category 'private') -----
+ failureDescription: aStringOrBlock with: reason
+ 
+ 	| description |
+ 	description := aStringOrBlock value.
+ 	^ description
+ 		ifNil: [reason]
+ 		ifNotNil: ['{1}: {2}' format: {description. reason}]!

Item was added:
+ ----- Method: TestCase>>isInstalled (in category 'testing') -----
+ isInstalled
+ 
+ 	^ self respondsTo: testSelector!

Item was removed:
- ----- Method: TestCase>>openDebuggerOnFailingTestMethod (in category 'running') -----
- openDebuggerOnFailingTestMethod
- 	"SUnit has halted one step in front of the failing test method. Step over the 'self halt' and 
- 	 send into 'self perform: testSelector' to see the failure from the beginning"
- 
- 	self
- 		halt;
- 		performTest!

Item was removed:
- ----- Method: TestCase>>runCaseAsFailure: (in category 'running') -----
- runCaseAsFailure: aSemaphore
- 	[self setUp.
- 	self openDebuggerOnFailingTestMethod] ensure: [
- 		self tearDown.
- 		aSemaphore signal]!

Item was added:
+ ----- Method: TestCase>>runCaseWithoutTimeout (in category 'running') -----
+ runCaseWithoutTimeout
+ 
+ 	[self setUp.
+ 	self performTest]
+ 		ensure: [self tearDown].!



More information about the Squeak-dev mailing list