TestResult.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Jul 2011 18:24:33 +0200
changeset 242 708d1d633192
parent 222 8e6f482297fa
child 270 edb137bd861e
permissions -rw-r--r--
added: #version_CVS

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

Object subclass:#TestResult
	instanceVariableNames:'name timestamp failures errors passed'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit-Base'
!

TestResult comment:''
!


!TestResult class methodsFor:'instance creation'!

new
	^super new initialize
! !

!TestResult class methodsFor:'exceptions'!

error
	^self exError
!

exError
	^SUnitNameResolver errorObject
!

failure
	^TestFailure
!

resumableFailure
	^ResumableTestFailure
!

signalErrorWith: aString
	self error sunitSignalWith: aString
!

signalFailureWith: aString
	self failure sunitSignalWith: aString
! !

!TestResult class methodsFor:'others'!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResult.st,v 1.21 2011-07-05 16:24:33 cg Exp $'
! !

!TestResult methodsFor:'accessing'!

defects
	^OrderedCollection new
		addAll: self errors;
		addAll: self failures; yourself
!

errorCount

	^self errors size
!

errors
	errors isNil ifTrue: [errors := OrderedCollection new].
	^errors
!

failureCount

	^self failures size
!

failures
	"We use a Set, not an OrderedCollection as #errors and #passed do, because a resumable test failure in a loop can raise many failures against the same test.  In current Sunit UIs, this could result in bizarre test count reporting (-27 tests run, and suchlike).  This will be reviewed."

	failures isNil ifTrue: [failures := Set new].
	^failures
!

name
    ^ name
!

name:aString
    name := aString.
!

passed
	passed isNil ifTrue: [passed := OrderedCollection new].
	^passed
!

passedCount

	^self passed size
!

runCount

	^self passedCount + self failureCount + self errorCount
!

tests

	^(OrderedCollection new: self runCount)
		addAll: self passed;
		addAll: self errors;
		addAll: self failures;
		yourself
!

timestamp
    ^ timestamp
! !

!TestResult methodsFor:'adding'!

addError: aTestCase
	aTestCase class rememberErrorTest: aTestCase selector.
	^self errors add: aTestCase

    "Modified: / 11-09-2010 / 17:19:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addFailure: aTestCase
	aTestCase class rememberFailedTest: aTestCase selector.
	^self failures add: aTestCase

    "Modified: / 11-09-2010 / 17:18:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addPass: aTestCase
	aTestCase class rememberPassedTest: aTestCase selector.
	^self passed add: aTestCase

    "Modified: / 11-09-2010 / 17:19:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestResult methodsFor:'deprecated'!

correctCount
	"deprecated - use #passedCount"

	^self passedCount
! !

!TestResult methodsFor:'initialize-release'!

initialize
! !

!TestResult methodsFor:'printing'!

printOn: aStream

	aStream
		nextPutAll: self runCount printString;
		nextPutAll: ' run, ';
		nextPutAll: self correctCount printString;
		nextPutAll: ' passed, ';
		nextPutAll: self failureCount printString;
		nextPutAll: ' failed, ';
		nextPutAll: self errorCount printString;
		nextPutAll: ' error'.

	self errorCount ~= 1
		ifTrue: [aStream nextPut: $s]
! !

!TestResult methodsFor:'running'!

runCase: aTestCase
	[aTestCase runCase.
	self addPass: aTestCase]
		sunitOn: self class failure , self class error
		do: [:ex | ex sunitAnnounce: aTestCase toResult: self].
! !

!TestResult methodsFor:'testing'!

hasErrors

	^self errors size > 0
!

hasFailures

	^self failures size > 0
!

hasPassed

	^self hasErrors not and: [self hasFailures not]
!

isError: aTestCase

	^self errors includes: aTestCase
!

isFailure: aTestCase
	^self failures includes: aTestCase
!

isPassed: aTestCase

	^self passed includes: aTestCase
! !

!TestResult class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResult.st,v 1.21 2011-07-05 16:24:33 cg Exp $'
!

version_SVN
    ^ '§Id: TestResult.st 205 2010-09-11 15:23:01Z vranyj1 §'
! !