TestSuite.st
author Claus Gittinger <cg@exept.de>
Tue, 12 Sep 2006 11:40:46 +0200
changeset 140 d61c515f8a58
parent 137 b6e0d451b091
child 164 40ae3ba82e24
permissions -rw-r--r--
*** empty log message ***

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

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

TestSuite comment:'This is a Composite of Tests, either TestCases or other TestSuites. The common protocol is #run: aTestResult and the dependencies protocol'
!


!TestSuite class methodsFor:'Creation'!

named: aString

	^self new
		name: aString;
		yourself
			
! !

!TestSuite methodsFor:'accessing'!

addTest: aTest
	self tests add: aTest
			
!

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

defaultResources
	^self tests 
		inject: Set new
		into: [:coll :testCase | 
			coll
				addAll: testCase resources;
				yourself]
			
!

name

        ^ name ? 'a TestSuite'.
!

name: aString

	name := aString
			
!

nameOfTest
    ^ self name
!

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

resources: anObject
	resources := anObject
			
!

testName
    ^ self name

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

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

!TestSuite methodsFor:'dependencies'!

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

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

!TestSuite methodsFor:'queries'!

isTestCase
    ^ false
!

isTestSuite
    ^ true
! !

!TestSuite methodsFor:'running'!

run
        | result |

        self signalUnavailableResources.

        result := TestResult new.
        [self run: result] ensure: [self resources do: [:each | each reset]].
        ^result
!

run: aResult 
        self tests do: [:each | 
                self changed: each.
                each run: aResult]
!

run: aResult afterEachDo:block2
        self tests do: 
                [:each | 
                self changed: each.
                each run: aResult afterEachDo:block2.
"/                block2 value:each value:aResult
                ]

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

run: aResult beforeEachDo:block1 afterEachDo:block2
        self tests do: 
                [:each | 
                self changed: each.
                block1 value:each value:aResult.
                each run: aResult beforeEachDo:block1 afterEachDo:block2.
                "/ each run: aResult.
                block2 value:each value:aResult.
                ]
!

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

!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.16 2006-09-12 09:40:46 cg Exp $'
! !