TestAsserter.st
author Claus Gittinger <cg@exept.de>
Sun, 01 Jul 2018 12:52:19 +0200
changeset 719 2c96860ad5cb
parent 718 b37f66696d9b
child 721 c11e3a43a1b4
permissions -rw-r--r--
#FEATURE by cg class: TestCase::Should class definition added: #assertSelector #beInstanceOf: #equal: #not #raise: changed: #be:

"{ Encoding: utf8 }"

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

"{ NameSpace: Smalltalk }"

Object subclass:#TestAsserter
	instanceVariableNames:''
	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
        ].

    "Modified (format): / 13-07-2017 / 15:03:51 / cg"
! !

!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].
!

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

!TestAsserter class methodsFor:'private'!

comparingCollectionBetween: left and: right
    "helper to generate a nice description, if 
     a collection is not the expected one."
     
    | additionalLeft additionalRight sortBlock|

    "use a very slow sort block"
    sortBlock := [ :a :b | a asString <= b asString ].
    additionalLeft := (left difference: right) sorted: sortBlock.
    additionalRight := (right difference: left) sorted: sortBlock. 

    ^ String 
        streamContents: [:stream |
            stream
                nextPutAll: 'Given Collections do not match.'; lf;
                tab; nextPutAll: 'Got left := '; print: left; nextPut: $.; lf;
                nextPutAll: ' instead of '; lf;
                tab; nextPutAll: 'right :='; print: right; nextPut: $.; lf.

            left size = right size ifFalse: [ 
                stream 
                    nextPutAll: 'Collection size does not match: left='; 
                    print: left size;
                    nextPutAll: ' vs. right=';
                    print: right size; lf 
            ].
            additionalLeft notEmpty ifTrue:[
                  stream
                      nextPutAll:'Got ';
                      print:additionalLeft size;
                      nextPutAll:' additional element(s) in the left collection: ';
                      tab;
                      print:additionalLeft
            ].
            additionalRight notEmpty ifTrue:[
                  stream
                      nextPutAll:'Got ';
                      print:additionalRight size;
                      nextPutAll:' additional element(s) in the right collection: ';
                      tab;
                      print:additionalRight
            ]
        ]

    "
     self basicNew comparingCollectionBetween:#(1 2 3) and:#(1 2 3 4)
    "

    "Modified: / 13-07-2017 / 14:13:15 / cg"
! !

!TestAsserter methodsFor:'asserting'!

assert: aBooleanOrBlock
    "fail the testcase if aBooleanOrBlock evaluates to false"

    <resource: #skipInDebuggersWalkBack>

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

    "Modified: / 05-12-2009 / 18:14:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-07-2017 / 13:50:13 / cg"
    "Modified (comment): / 13-07-2017 / 15:05:33 / cg"
!

assert:aBooleanOrBlock description:aString
    "fail the testCase if aBooleanOrBlock evaluates to false, 
     and report aStringOrBlock's value as failure-description."

    <resource: #skipInDebuggersWalkBack>

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

    "Modified: / 11-09-2010 / 15:34:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 09-11-2017 / 10:03:58 / cg"
!

assert:aBooleanOrBlock description:aStringOrBlock resumable:resumableBoolean
    "fail the testCase if aBooleanOrBlock evaluates to false, 
     and report aStringOrBlock's value as failure-description.
     If resumableBoolean is true, the test can be resumed in the debugger (if it was started by 'Debug')"

    <resource: #skipInDebuggersWalkBack>

    | exception |

    aBooleanOrBlock value ifFalse:[
        |string|

        string := aStringOrBlock value.
        self logFailure: string.
        exception := resumableBoolean
                        ifTrue: [TestResult resumableFailure]
                        ifFalse: [TestResult failure].
        exception sunitSignalWith: string
    ].

    "Modified: / 05-12-2009 / 18:15:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-07-2017 / 13:49:38 / cg"
    "Modified (comment): / 13-07-2017 / 15:07:33 / cg"
!

deny: aBooleanOrBlock
    "fail the testcase if aBooleanOrBlock evaluates to true"

    <resource: #skipInDebuggersWalkBack>

    self assert:(aBooleanOrBlock value not).

    "Modified: / 05-12-2009 / 18:16:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 13-07-2017 / 15:06:17 / cg"
!

deny: aBooleanOrBlock description: aString
    "fail the testCase if aBooleanOrBlock evaluates to true, 
     and report aStringOrBlock's value as failure-description."

    <resource: #skipInDebuggersWalkBack>

    self assert:(aBooleanOrBlock value not) description:aString.

    "Modified: / 05-12-2009 / 18:17:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 13-07-2017 / 15:06:30 / cg"
!

deny:aBooleanOrBlock description:aString resumable:resumableBoolean
    "fail the testCase if aBooleanOrBlock evaluates to true, 
     and report aStringOrBlock's value as failure-description.
     If resumableBoolean is true, the test can be resumed in the debugger (if it was started by 'Debug')"

    <resource: #skipInDebuggersWalkBack>

    self assert:(aBooleanOrBlock value not) description:aString resumable:resumableBoolean.

    "Modified: / 05-12-2009 / 18:17:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 13-07-2017 / 15:07:38 / cg"
!

should: aBlock raise: anExceptionalEvent
    "during the execution of aBlock, the anExceptionalEvent should be raised"

    <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
    "during the execution of aBlock, the anExceptionalEvent should be raised.
     If not, report aString as failure-description."

    <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
    "during the execution of aBlock, the anExceptionalEvent should be raised,
     and condBlock should return true on the exception instance"

    <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
    "during the execution of aBlock, the anExceptionalEvent should be raised,
     and condBlock should return true on the exception instance.
     If not, report aString as failure-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>"
!

should: aBlock raise: anExceptionalEvent whoseDescriptionIncludes: aStringFragment
    "during the execution of aBlock, the anExceptionalEvent should be raised,
     and aStringFragment should be contained in the exception-instances description."

    <resource: #skipInDebuggersWalkBack>

    ^ self should: aBlock 
           raise: anExceptionalEvent
           suchThat:[:ex | ex description includesString: aStringFragment]
!

should:aBlock raise:anExceptionalEvent whoseDescriptionIncludes:aStringFragment description:aString
    "during the execution of aBlock, the anExceptionalEvent should be raised,
     and aStringFragment should be contained in the exception-instances description.
     If not, report aString as failure-description."

    <resource: #skipInDebuggersWalkBack>

    ^ self should: aBlock 
           raise: anExceptionalEvent
           suchThat:[:ex | ex description includesString: aStringFragment]
           description: aString.
!

should:aBlock raise:anExceptionalEvent withExceptionDo:exCheckAction
    "during the execution of aBlock, the anExceptionalEvent should be raised,
     then exCheckAction is evaluated on the exception (which usually includes more checks).
     If not, report aString as failure-description."

    <resource: #skipInDebuggersWalkBack>

    ^ self should: aBlock 
           raise: anExceptionalEvent
           suchThat:[:ex | exCheckAction value:ex. true]

    "should fail:
    
         self new
            should:[ 1 / Float zero]
            raise:ZeroDivide
            withExceptionDo:[:ex |
                ex description should equal:'hello world'
            ].

     should fail:   
         self new
            should:[ 1 / Float zero]
            raise:ZeroDivide
            withExceptionDo:[:ex |
                ex description should equal:'hello world'
            ].

     should pass:   
         self new
            should:[ 1 / Float zero]
            raise:ZeroDivide
            withExceptionDo:[:ex |
                ex description should equal:'hello world'
            ].
    "

    "Created: / 01-07-2018 / 12:18:18 / Claus Gittinger"
!

shouldnt: aBlock raise: anExceptionalEvent
    "during the execution of aBlock, the anExceptionalEvent should NOT be raised"

    <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
    "during the execution of aBlock, the anExceptionalEvent should NOT be raised.
     If not, report aString as failure-description."

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

skip
    "skip this test"
    
    self skipIf:true description:'Test Skipped'.
!

skip:messageString
    "skip this test"
    
    self skipIf:true description:messageString

    "Modified (format): / 12-02-2017 / 22:44:11 / cg"
!

skipIf:aCondition description:messageString
    "skip this test, if some condition is met"
    
    aCondition value ifTrue: [
        self logSkipped: 'Skipped - ',messageString.
        TestResult skipped sunitSignalWith: messageString
    ].

    "Modified (format): / 12-02-2017 / 22:44:17 / cg"
! !

!TestAsserter methodsFor:'convenience'!

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

    "Modified: / 13-07-2017 / 15:12:26 / cg"
!

assertCollection:actual equals:expected
    "specialized test method that generates a proper error message for collection"

    ^ self 
        assert:(expected = actual)
        description:[ self class comparingCollectionBetween:actual and:expected ]

    "
     self basicNew assertCollection:#(1 2 3) equals:#(1 2 3)
     self basicNew assertCollection:#(1 2 3) equals:#(1 2 3 4)
    "

    "Created: / 13-07-2017 / 13:46:51 / cg"
    "Modified (comment): / 13-07-2017 / 15:03:28 / cg"
! !

!TestAsserter methodsFor:'logging'!

logFailure: aString
	self class logFailure: aString.
!

logSkipped: aString
        self class logSkipped: 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$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '$Id$'
! !