Hi:

While stepping through bytecodes, I noticed a slightly annoying inefficiency in 
the SUnit implementation.
The description string in #assert:equals: is always computed, even if it is not 
necessary.

While that might not be a performance problem, I find it rather distracting 
when I have to debug on the bytecode/VM level.

Since there seem to be only 127 senders or so in the image, you will probably 
not notice a big performance gain.
The change to compute the string only when necessary is below.

Best regards
Stefan

PS: This is a resend, because the original mail seemed to have been lost, while 
the mailing list was down.


!TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:41'!
assert: aBooleanOrBlock description: aStringOrBlock
        aBooleanOrBlock value ifFalse: [
                | aString |
                aString := aStringOrBlock value.
                self logFailure: aString.
                TestResult failure signal: aString]
                        ! !

!TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:40'!
assert: aBooleanOrBlock description: aStringOrBlock resumable: resumableBoolean 
        | exception |
        aBooleanOrBlock value
                ifFalse: 
                        [|aString|
                        aString := aStringOrBlock value.
                        self logFailure: aString.
                        exception := resumableBoolean
                                                ifTrue: [TestResult 
resumableFailure]
                                                ifFalse: [TestResult failure].
                        exception signal: aString]
                        ! !

!TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:40'!
assert: expected equals: actual
        ^ self
                assert: (expected = actual)
                description: [self comparingStringBetween: actual and: expected]
! !


-- 
Stefan Marr
Software Languages Lab
Vrije Universiteit Brussel
Pleinlaan 2 / B-1050 Brussels / Belgium
http://soft.vub.ac.be/~smarr
Phone: +32 2 629 2974
Fax:   +32 2 629 3525


Reply via email to