TestCase.st
author Claus Gittinger <cg@exept.de>
Wed, 25 Oct 2000 17:51:59 +0200
changeset 0 9365d5753f11
child 1 4dbe2da8c7e6
permissions -rw-r--r--
*** empty log message ***

'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:32 pm'                 !

"{ Package: 'stx:goodies/sunit' }"

Object subclass:#TestCase
	instanceVariableNames:'testSelector'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit'
!

!TestCase class methodsFor:'Instance Creation'!

debug: aSymbol
	^(self selector: aSymbol) debug!

run: aSymbol
	^(self selector: aSymbol) run!

selector: aSymbol
	^self new setTestSelector: aSymbol!

suite
	| testSelectors result |
	testSelectors := self sunitSelectors select: [:each | 'test*' sunitMatch: each].
	result := TestSuite new.
	testSelectors do: [:each | result addTest: (self selector: each)].
	^result

    "Modified: / 21.6.2000 / 10:05:24 / Sames"
! !

!TestCase methodsFor:'Accessing'!

assert: aBoolean
	aBoolean ifFalse: [self signalFailure: 'Assertion failed']

    "Modified: / 21.6.2000 / 10:00:05 / Sames"
!

deny: aBoolean
	self assert: aBoolean not!

should: aBlock
	self assert: aBlock value!

should: aBlock raise: anExceptionalEvent 
	^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent)

    "Modified: / 21.6.2000 / 10:01:08 / Sames"
!

shouldnt: aBlock
	self deny: aBlock value!

shouldnt: aBlock raise: anExceptionalEvent 
	^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) not

    "Modified: / 21.6.2000 / 10:01:16 / Sames"
!

signalFailure: aString
	TestResult failure sunitSignalWith: aString

    "Modified: / 21.6.2000 / 10:01:34 / Sames"
! !

!TestCase methodsFor:'Dependencies'!

addDependentToHierachy: anObject 
	"an empty method. for Composite compability with TestSuite"!

removeDependentFromHierachy: anObject 
	"an empty method. for Composite compability with TestSuite"! !

!TestCase methodsFor:'Printing'!

printOn: aStream
	aStream nextPutAll: self class name.
	aStream nextPutAll: '>>'.
	aStream nextPutAll: testSelector

    "Modified: / 4.4.2000 / 18:59:53 / Sames"
! !

!TestCase methodsFor:'Private'!

executeShould: aBlock inScopeOf: anExceptionalEvent 
	[[aBlock value]
		sunitOn: anExceptionalEvent
		do: [:ex | ^true]]
			sunitOn: TestResult error
			do: [:ex | ^false].
	^false.

    "Modified: / 21.6.2000 / 10:03:03 / Sames"
!

setTestSelector: aSymbol
	testSelector := aSymbol! !

!TestCase methodsFor:'Running'!

debug
	(self class selector: testSelector) runCase!

debugAsFailure
	(self class selector: testSelector) runCaseAsFailure!

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.
	self perform: testSelector sunitAsSymbol

    "Modified: / 21.6.2000 / 10:03:37 / Sames"
!

run
	| result |
	result := TestResult new.
	self run: result.
	^result!

run: aResult
	aResult runCase: self!

runCase
	self setUp.
	[self perform: testSelector sunitAsSymbol] sunitEnsure: [self tearDown]

    "Modified: / 21.6.2000 / 10:04:18 / Sames"
!

runCaseAsFailure
	self setUp.
	[[self openDebuggerOnFailingTestMethod] sunitEnsure: [self tearDown]] fork

    "Modified: / 21.6.2000 / 10:04:33 / Sames"
!

setUp!

tearDown! !