TestCase.st
author Claus Gittinger <cg@exept.de>
Sun, 21 Aug 2011 15:06:47 +0200
changeset 421 9b8b2a70d775
parent 420 84e640399605
child 430 8347cb8a1b84
permissions -rw-r--r--
changed: #allTestSelectors

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

TestAsserter subclass:#TestCase
	instanceVariableNames:'testSelector'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit-Base'
!

TestCase class instanceVariableNames:'lastOutcomes'

"
 No other class instance variables are inherited by this class.
"
!


!TestCase class methodsFor:'initialization'!

initialize
    ResumableTestFailure autoload

    "
     self initialize
    "
!

postAutoload
    self projectDefinitionClass loadExtensions
! !

!TestCase class methodsFor:'instance creation'!

asTestCase
    ^ self

    "Created: / 02-08-2011 / 09:12:13 / cg"
!

debug: aSymbol

        ^(self selector: aSymbol) debug
!

run: aSymbol

        ^(self selector: aSymbol) run
!

selector: aSymbol

        ^self new setTestSelector: aSymbol
!

suite

        ^self buildSuite
! !

!TestCase class methodsFor:'accessing'!

allTestSelectors
    | answer pivotClass lookupRoot |

    answer := Set withAll: self testSelectors.
    self shouldInheritSelectors ifTrue:[
        pivotClass := self superclass.
        lookupRoot := self lookupHierarchyRoot.
        [pivotClass == lookupRoot] whileFalse:[
            answer addAll: pivotClass testSelectors.
            pivotClass := pivotClass superclass.
        ]
    ].
    ^answer asSortedCollection asOrderedCollection

    "Modified: / 21-08-2011 / 15:06:11 / cg"
!

forgetLastTestRunResult

    Smalltalk changed:#lastTestRunResult with:(Array with:self with:nil).
    self changed:#lastTestRunResult.

    "Modified: / 06-08-2006 / 11:40:07 / cg"
    "Modified: / 20-08-2011 / 15:10:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isTestSelector:aSelector

    ^aSelector notNil and:[aSelector startsWith:'test']

    "Created: / 06-08-2006 / 11:46:17 / cg"
    "Modified: / 05-12-2009 / 18:50:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-08-2011 / 17:46:51 / cg"
!

lastTestRunResultOrNil

    "Returns true if all tests passed, false if at least
     one failed/error  or nil if never run            
    "
    lastOutcomes isNil ifTrue:[^nil].
    lastOutcomes size ~= self testSelectors size ifTrue:[^nil].
    lastOutcomes do:[:outcome|
        outcome result == #pass ifFalse:[
            ^false
        ].
    ].
    ^true

    "Modified: / 20-08-2011 / 14:59:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lookupHierarchyRoot
        ^TestCase
!

rememberOutcome: outcome

    lastOutcomes isNil ifTrue:[
        lastOutcomes := OrderedCollection new.
    ].
    "Not a nice code, but portable..."
    1 to: lastOutcomes size do:[:i|
        | each |

        each := lastOutcomes at: i.
        (each testCase class == outcome testCase class and:
            [each testCase selector == outcome testCase selector]) ifTrue:[
                lastOutcomes at: i put: outcome.
                each result ~= outcome result ifTrue:[
                    self lastTestRunResultChanged: outcome selector. 
                ].
                ^self.                    
            ].
    ].
    lastOutcomes add: outcome.
    self lastTestRunResultChanged: outcome selector.
    ^self

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

rememberedOutcomeFor: selector

    lastOutcomes isNil ifTrue:[^nil].
    ^lastOutcomes 
        detect: [:outcome| outcome testCase selector == selector]
        ifNone:[nil].

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

resources

        ^#()
!

shouldFork

    ^false

    "Created: / 13-06-2011 / 16:46:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sunitVersion
        ^'4.0'
!

testSelector:selector result: result

    lastOutcomes isNil ifTrue:[^false].
    ^(lastOutcomes 
        detect:[:each|
            each testCase class == self
                and:[each testCase selector == selector
                    and:[each result == result]]
        ]
        ifNone: [nil]) notNil

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

testSelectorError:selector

    ^self testSelector: selector result: #error

    "Created: / 15-03-2010 / 19:44:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testSelectorFailed:selector

    ^self testSelector: selector result: #fail

    "Modified: / 20-08-2011 / 16:16:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testSelectorPassed:selector

   ^self testSelector: selector result: #pass

    "Created: / 15-03-2010 / 17:58:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestCase class methodsFor:'building suites'!

buildSuite
        | suite |
        ^self isAbstract
                ifTrue:
                        [suite := self suiteClass named: self name asString.
                        self allSubclasses
                                do: [:each | each isAbstract ifFalse: [suite addTest: each buildSuiteFromSelectors]].
                        suite]
                ifFalse: [self buildSuiteFromSelectors]
!

buildSuiteFromMethods: testMethods

        ^testMethods
                inject: (self suiteClass named: self name asString)
                into: [:suite :selector |
                        suite
                                addTest: (self selector: selector);
                                yourself]
!

buildSuiteFromSelectors
        ^self buildSuiteFromMethods: self allTestSelectors
!

suiteClass
        ^TestSuite
! !

!TestCase class methodsFor:'misc ui support'!

iconInBrowserSymbol
    <resource: #programImage>

    |lastResult|

    self theNonMetaclass isAbstract ifTrue:[^ super iconInBrowserSymbol].

    lastResult := self lastTestRunResultOrNil.
    lastResult == true ifTrue:[
        ^ #testCasePassedIcon
    ].
    lastResult == false ifTrue:[
        ^ #testCaseFailedIcon
    ].
    ^ #testCaseClassIcon
! !

!TestCase class methodsFor:'private'!

addSelector: selector to: collection

    "Adds given selector from collection. Answers
     true iff selector was really added"

    ^(collection includes: selector)
        ifTrue:[false]
        ifFalse:[collection add: selector. true]

    "Created: / 15-03-2010 / 18:06:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-04-2010 / 23:19:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lastTestRunResultChanged: selector

    Smalltalk changed:#lastTestRunResult with:(Array with:self with:selector).
    self changed:#lastTestRunResult with:selector.

    "Created: / 15-03-2010 / 19:15:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testSelectors
        "The API method is allTestSelectors which now includes #shouldInheritSelectors and so handles all cases.  Unlike that method, this does not guarantee to return a sorted ordered collection."

        ^self sunitSelectors select: [:each | 'test*' sunitMatch: each]
! !

!TestCase 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"
! !

!TestCase class methodsFor:'quick testing'!

assert: aBoolean
    ^ self new assert: aBoolean

    "
     TestCase assert: true
    "
!

should: aBlock raise: anError
    ^ self new should: aBlock raise: anError

    "
     TestCase should:[ self error ] raise: Error
    "
! !

!TestCase class methodsFor:'testing'!

isAbstract
        "Override to true if a TestCase subclass is Abstract and should not have
        TestCase instances built from it"

        ^self sunitName = #TestCase
!

isTestCaseLike

    ^true

    "Created: / 06-03-2011 / 00:16:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

rememberResult:result

    result outcomesDo:[:outcome|self rememberOutcome: outcome].

    "Created: / 05-08-2006 / 12:33:08 / cg"
    "Modified: / 20-08-2011 / 14:02:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

runTests

    ^self suite run

    "Modified: / 30-07-2011 / 09:26:11 / cg"
    "Modified: / 20-08-2011 / 16:14:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

shouldInheritSelectors
        "I should inherit from an Abstract superclass but not from a concrete one by default, unless I have no testSelectors in which case I must be expecting to inherit them from my superclass.  If a test case with selectors wants to inherit selectors from a concrete superclass, override this to true in that subclass."

        ^self ~~ self lookupHierarchyRoot
                and: [self superclass isAbstract
                        or: [self testSelectors isEmpty]]
! !

!TestCase methodsFor:'accessing'!

resources
        "We give TestCase this instance-side method so that methods polymorphic with TestSuite can be code-identical.  Having this instance-side method also helps when writing tests of resource behaviour. Except for such tests, it is rare to override this method and should not be done without thought.  If there were a good reason why a single test case needed to share tests requiring different resources, it might be legitimate."

        ^self class resources
!

selector
        ^testSelector
!

shouldFork

    ^self class shouldFork

    "Created: / 13-06-2011 / 16:45:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testCount

    ^1

    "Created: / 04-08-2011 / 13:03:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestCase methodsFor:'accessing & queries'!

unfinished

        "indicates an unfinished test"
! !

!TestCase methodsFor:'assertions'!

assert:aBlock completesInSeconds:aNumber
    "fail, if aBlock does not finish its work in aNumber seconds"

    <resource: #skipInDebuggersWalkBack>

    |done process semaphore|

    done := false.
    semaphore := Semaphore new.
    process := [
        aBlock value.
        done := true.
        semaphore signal
    ] fork.
    semaphore waitWithTimeout: aNumber.
    process terminate.
    self assert: done

    "
     self new assert:[Delay waitForSeconds:2] completesInSeconds:1
    "
    "
     self new assert:[Delay waitForSeconds:1] completesInSeconds:2
    "
!

assert: aBoolean message:messageIfFailing

    ^self assert: aBoolean description: messageIfFailing

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

assertFalse:aBoolean
    <resource: #skipInDebuggersWalkBack>

    ^ self assert:aBoolean not
!

assertFalse:aBoolean named:testName
    <resource: #skipInDebuggersWalkBack>

    ^ self assert:aBoolean not
!

assertTrue:aBoolean
    <resource: #skipInDebuggersWalkBack>

    ^ self assert:aBoolean
!

assertTrue:aBoolean named:testName
    <resource: #skipInDebuggersWalkBack>

    ^ self assert:aBoolean
! !

!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:'deprecated'!

should: aBlock
        self assert: aBlock value
!

should: aBlock description: aString
        self assert: aBlock value description: aString
!

shouldnt: aBlock
        self deny: aBlock value
!

shouldnt: aBlock description: aString
        self deny: aBlock value description: aString
!

signalFailure: aString
        TestResult failure sunitSignalWith: aString.
! !

!TestCase methodsFor:'printing'!

getTestName

    ^testSelector.

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

name
        ^ self class name.
!

printOn: aStream

        aStream
                nextPutAll: self class printString;
                nextPutAll: '>>#';
                nextPutAll: testSelector
! !

!TestCase methodsFor:'private'!

executeShould: aBlock inScopeOf: anExceptionalEvent
"/        ^[aBlock value.
"/        false] sunitOn: anExceptionalEvent
"/                do: [:ex | ex sunitExitWith: true]

"/        [[aBlock value]
"/                on: anExceptionalEvent
"/                do: [:ex | ^true]]
"/                        on: TestResult exError
"/                        do: [:ex | ^false].
        [aBlock value]
                on: anExceptionalEvent
                do: [:ex | ^true].

        ^false.
!

performTest
    self perform: testSelector sunitAsSymbol
!

setTestSelector: aSymbol
        testSelector := aSymbol
!

signalFailure:aString resumable:isResumable
    "/        TestResult failure sunitSignalWith: aString

    <resource: #skipInDebuggersWalkBack>

    isResumable ifTrue:[
        TestResult resumableFailure
            raiseRequestWith:nil
            errorString:aString
            in:thisContext sender sender
    ] ifFalse:[
        TestResult failure
            raiseErrorString:aString
            in:thisContext sender sender
    ].

    "Modified: / 06-08-2006 / 22:55:55 / cg"
!

signalUnavailableResources

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

!TestCase methodsFor:'queries'!

isTestCase
    ^ true
!

isTestCaseLike
    ^ true

    "Created: / 29-06-2011 / 20:37:57 / cg"
!

isTestSuite
    ^ false
! !

!TestCase methodsFor:'running'!

debug

    | testCase outcome |

    [
        (testCase := self class selector: testSelector) runCase.
        outcome := TestCaseOutcome new.
        outcome testCase: testCase.
        outcome result: #pass.
        outcome remember.
    ] sunitEnsure: [
        TestResource resetResources: self resources
    ].

    "Modified: / 07-07-2011 / 11:10:50 / jv"
    "Modified: / 07-07-2011 / 11:34:08 / Jan Vrany <jan.vrant@fit.cvut,cz>"
    "Modified: / 20-08-2011 / 14:15:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

debugAsFailure
        | semaphore |
        semaphore := Semaphore new.
        [semaphore wait. TestResource resetResources: self resources] fork.
        (self class selector: testSelector) runCaseAsFailure: semaphore.
!

debugUsing:aSymbol
    self signalUnavailableResources.
    [
        "/ used to be:
        "/  (self class selector:testSelector) perform:aSymbol
        "/ which is bad for subclasses which need more arguments.
        "/ why not use:
        "/  self copy perform:aSymbol
        "/ or even
        "/  self perform:aSymbol
        "/ (self class selector:testSelector) perform:aSymbol
        self perform:aSymbol
    ] ensure:[
        self resources do:[:each |
            each reset
        ]
    ]









!

failureLog
        ^SUnitNameResolver class >> #defaultLogDevice
!

isLogging
        "By default, we're not logging failures. If you override this in
        a subclass, make sure that you override #failureLog"
        ^false

!

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

!

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;
                performTest

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

run

    ^self run: TestResult new

    "Modified: / 29-07-2011 / 12:07:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run: aResult

    ^self run: aResult beforeEachDo: [:test :result|] afterEachDo: [:test :result|]

    "Modified: / 29-07-2011 / 12:07:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run: aResult afterEachDo:block2

    ^self run: aResult beforeEachDo: [:test :result|] afterEachDo:block2

    "Modified: / 29-07-2011 / 12:07:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run: aResult beforeEachDo:block1 afterEachDo:block2

    ^self run: aResult beforeEachDo:block1 afterEachDo:block2 resetResources: true

    "Modified: / 29-07-2011 / 12:06:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

run: result beforeEachDo: before afterEachDo: after resetResources: reset

    "Workhorse for running a testcase. If reset is true, then
     the resources are reset, otherwise not"

    "1. Execute before block"
    "This code is ugly in Smalltalk/X but it is so because
     it is more portable - numArgs in ANSI (?)"
    before numArgs == 2 ifTrue:[
        before value: self value: result                
    ] ifFalse:[
        before numArgs == 1 ifTrue:[
            before value: self
        ] ifFalse:[
            before value.
        ]
    ].

    "2. Run the testcase"
    reset ifTrue:[
        [
            result runCase: self
        ] sunitEnsure: [
            TestResource resetResources: self resources
        ].
    ] ifFalse:[
        result runCase: self
    ].

    "3. Execute after block"
    "This code is ugly in Smalltalk/X but it is so because
     it is more portable - numArgs in ANSI (?)"
    after numArgs == 2 ifTrue:[
        after value: self value: result                
    ] ifFalse:[
        after numArgs == 1 ifTrue:[
            after value: self
        ] ifFalse:[
            after value.
        ]
    ].
    ^result

    "Created: / 29-07-2011 / 12:04:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-08-2011 / 10:22:09 / cg"
!

run: aResult beforeEachTestCaseDo:block1 afterEachTestCaseDo:block2

    <resource: #obsolete>
    self obsoleteMethodWarning: 'Use #run:beforeEachDo:afterEachDo: instead'.

    ^self run: aResult beforeEachDo:block1 afterEachDo:block2

    "Modified: / 29-07-2011 / 12:06:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

runCase
    self resources do: [:each | each availableFor: self].

    [
        self setUp.
        self performTest.
    ] sunitEnsure: [
        self tearDown
    ]

    "Modified (comment): / 18-08-2011 / 20:35:20 / cg"
!

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

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

runCaseAsFailure: aSemaphore
        [self resources do: [:each | each availableFor: self].
        [self setUp.
        self openDebuggerOnFailingTestMethod]
                sunitEnsure: [self tearDown]]
                        sunitEnsure: [aSemaphore signal].
!

setUp
!

tearDown
! !

!TestCase class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestCase.st,v 1.81 2011-08-21 13:06:47 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestCase.st,v 1.81 2011-08-21 13:06:47 cg Exp $'
!

version_SVN
    ^ '§Id: TestCase.st 218 2011-06-13 15:45:06Z vranyj1 §'
! !

TestCase initialize!