TestAsserter.st
author vrany
Tue, 02 Aug 2011 18:57:10 +0200
changeset 295 f41960a0ee97
parent 291 ca207bd1546d
child 317 81d237f7ac0c
permissions -rw-r--r--
added: #asTestCase

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

Object subclass:#TestAsserter
	instanceVariableNames:'startTime endTime backtrace exceptionInfoString'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit-Base'
!

TestAsserter comment:''
!


!TestAsserter class methodsFor:'asserting'!

assert: aBoolean description: aString
	"Minimal clone of the instance-side assert protocol so that class-side methods can use it."

	aBoolean ifFalse:
		[self logFailure: aString.
		TestResult failure sunitSignalWith: aString].
! !

!TestAsserter class methodsFor:'logging'!

failureLog
	^SUnitNameResolver defaultLogDevice
!

isLogging
	"By default, we're not logging failures. Override in subclasses as desired."

	^false
!

logFailure: aString
	self isLogging ifTrue:
		[self failureLog cr; nextPutAll: aString; flush].
! !

!TestAsserter class methodsFor:'queries'!

coveredClassNames
    "should be redefined to return a collection of classes which are tested by
     this suite/case. These classes can be instrumented for coverage analysis,
     before running the suite"

    ^ #()

    "Created: / 06-07-2011 / 21:27:03 / cg"
!

coveredClasses
    "return a collection of classes which are tested by this suite/case. 
     These classes can be instrumented for coverage analysis,
     before running the suite"

    ^ self coveredClassNames collect:[:each | Smalltalk classNamed:each]

    "Created: / 04-07-2011 / 18:16:08 / cg"
! !

!TestAsserter methodsFor:'accessing'!

endTime
    "the end time as timestamp; nil if not yet executed or not yet finished"

    ^ endTime

    "Created: / 02-08-2011 / 17:43:11 / cg"
!

exceptionInfoString
    "the stack backtrace as a string (but only if executed and not passed).
     (I guess, there is no standard format for context information among
      the smalltalks, so a string containing the backtrace is the best we can
      do to keep things portable AND be able to present the backtrace in a hudson page)"

    ^ exceptionInfoString

    "Modified: / 01-08-2011 / 16:52:51 / cg"
    "Created: / 02-08-2011 / 18:13:16 / cg"
!

executionTime
    "the execution time in millis; nil if not yet executed"

    startTime isNil ifTrue:[
        "/ not yet executed
        ^ nil
    ].
    ^ (endTime deltaFrom:startTime) getMilliseconds

    "Modified: / 01-08-2011 / 16:52:51 / cg"
!

startTime
    "the start time as timestamp; nil if not yet executed"

    ^ startTime

    "Created: / 30-07-2011 / 10:06:05 / cg"
! !

!TestAsserter methodsFor:'asserting'!

assert: aBoolean

    <resource: #skipInDebuggersWalkBack>

    aBoolean ifFalse:
	[self logFailure: 'Assertion failed'.
	TestResult failure sunitSignalWith: 'Assertion failed'].

    "Modified: / 05-12-2009 / 18:14:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

assert:aBoolean description:aString
    <resource: #skipInDebuggersWalkBack>

    ^self assert:aBoolean description:aString resumable: false.

    "Modified: / 06-08-2006 / 22:56:27 / cg"
    "Modified: / 11-09-2010 / 15:34:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

assert: aBoolean description: aString resumable: resumableBoolean

    <resource: #skipInDebuggersWalkBack>
    | exception |
    aBoolean ifFalse:
	[self logFailure: aString.
		exception := resumableBoolean
			ifTrue: [TestResult resumableFailure]
			ifFalse: [TestResult failure].
		exception sunitSignalWith: aString].

    "Modified: / 05-12-2009 / 18:15:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

deny: aBoolean

    <resource: #skipInDebuggersWalkBack>

    self assert: aBoolean not.

    "Modified: / 05-12-2009 / 18:16:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

deny: aBoolean description: aString

    <resource: #skipInDebuggersWalkBack>
    self assert: aBoolean not description: aString.

    "Modified: / 05-12-2009 / 18:17:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

deny: aBoolean description: aString resumable: resumableBoolean

    <resource: #skipInDebuggersWalkBack>

    self assert: aBoolean not description: aString resumable: resumableBoolean.

    "Modified: / 05-12-2009 / 18:17:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

should: aBlock raise: anExceptionalEvent

    <resource: #skipInDebuggersWalkBack>

    self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent).

    "Modified: / 05-12-2009 / 18:18:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

should: aBlock raise: anExceptionalEvent description: aString

    <resource: #skipInDebuggersWalkBack>

    self
	assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent)
	description: aString.

    "Modified: / 05-12-2009 / 18:18:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

should: aBlock raise: anExceptionalEvent suchThat: condBlock

    <resource: #skipInDebuggersWalkBack>

    self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent suchThat: condBlock).

    "Created: / 05-05-2011 / 20:14:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

should: aBlock raise: anExceptionalEvent suchThat: condBlock description: description

    <resource: #skipInDebuggersWalkBack>

    self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent suchThat: condBlock)
	 description: description

    "Created: / 05-05-2011 / 20:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

shouldnt: aBlock raise: anExceptionalEvent

    <resource: #skipInDebuggersWalkBack>

    self
	assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) not.

    "Modified: / 05-12-2009 / 18:18:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

shouldnt: aBlock raise: anExceptionalEvent description: aString

    <resource: #skipInDebuggersWalkBack>

    self
	assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) not
	description: aString.

    "Modified: / 05-12-2009 / 18:18:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestAsserter methodsFor:'convenience'!

assert: anObject equals: anotherObject
	self assert: anObject = anotherObject
		description: anObject printString, ' is not equal to ', anotherObject printString.
! !

!TestAsserter methodsFor:'logging'!

exceptionInfoString:exceptionInfoStringArg
    "remember the exception info, a string containing the stack backtrace
     (I guess, there is no standard format for context information among
      the smalltalks, so a string containing the backtrace is the best we can
      do to keep things portable AND be able to present the backtrace in a hudson page. 
      It is the caller's responsibility to generate something human readable)"

    exceptionInfoString := exceptionInfoStringArg

    "Created: / 02-08-2011 / 17:57:16 / cg"
!

logFailure: aString
	self class logFailure: aString.
! !

!TestAsserter methodsFor:'private'!

executeShould: execBlock inScopeOf: exceptionalEvent

    <resource: #skipInDebuggersWalkBack>

    ^ self
	executeShould: execBlock
	inScopeOf: exceptionalEvent
	suchThat: [:ex | true ]

    "Modified: / 05-05-2011 / 20:23:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

executeShould: execBlock inScopeOf: exceptionalEvent suchThat: conditionBlock
	^[execBlock value.
	false]
		sunitOn: exceptionalEvent
		do:
		    [:ex |
		    ex sunitExitWith:(conditionBlock value: ex)]

    "Created: / 05-05-2011 / 20:08:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestAsserter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestAsserter.st,v 1.9 2011-08-02 16:14:37 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestAsserter.st,v 1.9 2011-08-02 16:14:37 cg Exp $'
!

version_SVN
    ^ '§Id: TestAsserter.st 217 2011-05-05 19:33:11Z vranyj1 §'
! !