TestSuite.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Jul 2011 17:45:47 +0200
changeset 238 384805dcb5dd
parent 222 8e6f482297fa
child 243 cbce69b15370
permissions -rw-r--r--
added: #runBeforeEachDo:afterEachDo: #version_CVS

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

Object subclass:#TestSuite
	instanceVariableNames:'tests resources name'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit-Base'
!

TestSuite comment:''
!


!TestSuite class methodsFor:'instance creation'!

named: aString

	^self new
		name: aString;
		yourself
! !

!TestSuite class methodsFor:'others'!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuite.st,v 1.20 2011-07-05 15:45:47 cg Exp $'
! !

!TestSuite methodsFor:'accessing'!

addTest: aTest
	self tests add: aTest
!

addTests: aCollection
	aCollection do: [:eachTest | self addTest: eachTest]
!

defaultResources
	^self tests
		inject: OrderedCollection new
		into:
			[:coll :testCase |
			testCase resources do:
				[:each |
				(coll includes: each) ifFalse: [coll add: each]].
			coll]
!

getTestName
    ^self name

    "Created: / 12-09-2006 / 11:38:09 / cg"
!

name

	^name
!

name: aString

	name := aString
!

nameOfTest
    ^ self name
!

resources
	resources isNil ifTrue: [resources := self defaultResources].
	^resources
!

resources: someOrderedTestResourceClasses
	"The parameter should understand reverseDo: and should not contain duplicates."

	resources := someOrderedTestResourceClasses
!

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

!TestSuite methodsFor:'dependencies'!

addDependentToHierachy: anObject
	self sunitAddDependent: anObject.
	self tests do: [ :each | each addDependentToHierachy: anObject]
!

removeDependentFromHierachy: anObject
	self sunitRemoveDependent: anObject.
	self tests do: [ :each | each removeDependentFromHierachy: anObject]
! !

!TestSuite methodsFor:'queries'!

isTestCase
    ^ false
!

isTestSuite
    ^ true
! !

!TestSuite methodsFor:'running'!

run
	| result |
	result := TestResult new.
	[self run: result]
		"sunitEnsure: [self resources reverseDo: [:each | each reset]]."
			sunitEnsure: [TestResource resetResources: self resources].
	^result

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

run:aResult

    aResult name:name.
    self tests do:[:each |
	self sunitChanged:each.
	each run:aResult
    ]

    "Modified: / 19-03-2010 / 08:03:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run: aResult afterEachDo:block2

    aResult name: name.
    self tests do:
	[:each |
	self changed: each.
	each run: aResult afterEachDo:block2]

    "Modified: / 21-06-2000 / 10:14:01 / Sames"
    "Modified: / 19-03-2010 / 08:01:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run:aResult beforeEachDo:block1 afterEachDo:block2
    |class|

    aResult name: name.
    class := name ifNotNil:[ Smalltalk classNamed:name ] ifNil:[ nil ].
    class ifNotNil:[ class perform:#setUp ifNotUnderstood:nil ].
    [
	self tests do:[:each |
	    self sunitChanged:each.
	    block1 value:each value:aResult.
	    each
		run:aResult
		beforeEachDo:block1
		afterEachDo:block2.

	    "/ each run: aResult.

	    block2 value:each value:aResult.
	].
    ] ensure:[
	self resources do:[:e |
	    e reset
	]
    ].
    class ifNotNil:[ class perform:#tearDown ifNotUnderstood:nil ]

    "Modified: / 19-03-2010 / 08:02:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run:aResult beforeEachTestCaseDo:block1 afterEachTestCaseDo:block2

    aResult name: name.
    self tests do:[:each |
	self changed:each.
	each
	    run:aResult
	    beforeEachTestCaseDo:block1
	    afterEachTestCaseDo:block2.
    ]

    "Modified: / 19-03-2010 / 08:02:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

runAfterEachDo: aBlock
	| result |
	result := TestResult new.
	result name: name.
	[self run: result afterEachDo: aBlock]
		sunitEnsure: [self resources reverseDo: [:each | each reset]].
	^result

    "Created: / 15-03-2010 / 20:36:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-03-2010 / 08:02:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

runBeforeEachDo:block1 afterEachDo: block2
        | result |
        result := TestResult new.
        result name: name.
        [self run: result beforeEachDo:block1 afterEachDo: block2]
                sunitEnsure: [self resources reverseDo: [:each | each reset]].
        ^result

    "Modified: / 19-03-2010 / 08:02:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 05-07-2011 / 16:51:25 / cg"
! !

!TestSuite methodsFor:'testing'!

areAllResourcesAvailable
	^self resources
		inject: true
		into: [:total :each | each isAvailable & total]
!

signalUnavailableResources

    self resources do:[:res |
	res isAvailable ifFalse:[
	    ^ res signalInitializationError
	]
    ].
! !

!TestSuite class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuite.st,v 1.20 2011-07-05 15:45:47 cg Exp $'
!

version_SVN
    ^ '§Id: TestSuite.st 203 2010-09-11 14:49:03Z vranyj1 §'
! !