SystemOrganization addCategory: #HudsonBuildTools!
Object subclass: #HDTestReport
instanceVariableNames: 'suite stream suitePosition suiteTime suiteFailures suiteErrors'
classVariableNames: ''
poolDictionaries: ''
category: 'HudsonBuildTools'!
!HDTestReport class methodsFor: 'running' stamp: 'lr 1/10/2010 01:30'!
runCategories: aCollectionOfStrings
aCollectionOfStrings do: [ :each | self runCategory: each ]! !
!HDTestReport class methodsFor: 'running' stamp: 'lr 1/10/2010 01:30'!
runCategory: aString
self runClasses: (Smalltalk organization classesInCategory: aString) named: aString! !
!HDTestReport class methodsFor: 'running' stamp: 'lr 3/15/2010 12:02'!
runClasses: aCollectionOfClasses named: aString
| suite classes |
suite := TestSuite named: aString.
classes := (aCollectionOfClasses
select: [ :each | (each includesBehavior: TestCase) and: [ each isAbstract not ] ])
asSortedCollection: [ :a :b | a name <= b name ].
classes isEmpty
ifTrue: [ ^ self ].
classes
do: [ :each | each addToSuiteFromSelectors: suite ].
self runSuite: suite! !
!HDTestReport class methodsFor: 'running' stamp: 'lr 1/10/2010 01:31'!
runPackage: aString
^ self runClasses: (PackageInfo named: aString) classes named: aString! !
!HDTestReport class methodsFor: 'running' stamp: 'lr 1/10/2010 01:31'!
runPackages: aCollectionOfStrings
aCollectionOfStrings do: [ :each | self runPackage: each ]! !
!HDTestReport class methodsFor: 'running' stamp: 'TestRunner 1/10/2010 00:58'!
runSuite: aTestSuite
self new
initializeOn: aTestSuite;
run! !
!HDTestReport methodsFor: 'private' stamp: 'lr 1/10/2010 01:07'!
encode: aString
^ ((aString asString
copyReplaceAll: '&' with: '&')
copyReplaceAll: '"' with: '"')
copyReplaceAll: '<' with: '<'! !
!HDTestReport methodsFor: 'initialization' stamp: 'lr 1/10/2010 10:22'!
initializeOn: aTestSuite
suite := aTestSuite.
suitePosition := suiteTime := suiteFailures := suiteErrors := 0! !
!HDTestReport methodsFor: 'running' stamp: 'lr 1/22/2010 10:03'!
run
Author ifUnknownAuthorUse: 'hudson' during: [
[ self setUp.
suiteTime := [ self runAll ]
timeToRun ]
ensure: [ self tearDown ] ]! !
!HDTestReport methodsFor: 'running' stamp: 'lr 1/10/2010 15:22'!
run: aTestCase
| error time stack |
time := [ [ aTestCase runCase ]
on: Error , TestFailure
do: [ :err |
error := err.
stack := String streamContents: [ :str |
| context |
context := err signalerContext.
[ context isNil or: [ context receiver == aTestCase and: [ context methodSelector == #runCase ] ] ] whileFalse: [
str print: context; cr.
context := context sender ] ] ] ]
timeToRun.
stream tab; nextPutAll: ''; cr.
(error isNil or: [ aTestCase expectedFailures includes: aTestCase selector ]) ifFalse: [
(error isKindOf: TestFailure)
ifTrue: [
suiteFailures := suiteFailures + 1.
stream tab; tab; nextPutAll: ''; nextPutAll: (self encode: stack); nextPutAll: ''; cr ]
ifFalse: [
suiteErrors := suiteErrors + 1.
stream tab; tab; nextPutAll: ''; nextPutAll: (self encode: stack); nextPutAll: ''; cr ] ].
stream tab; nextPutAll: ''; cr! !
!HDTestReport methodsFor: 'running' stamp: 'lr 1/10/2010 01:27'!
runAll
suite tests do: [ :each | self run: each ]! !
!HDTestReport methodsFor: 'running' stamp: 'lr 1/10/2010 15:21'!
setUp
stream := StandardFileStream forceNewFileNamed: suite name , '.xml'.
stream nextPutAll: ''; cr.
stream nextPutAll: ''.
"Now this is ugly. We want to update the time and the number of failures and errors, but still at the same time stream a valid XML. So remember this position and add some whitespace, that we can fill later."
suitePosition := stream position - 1.
stream nextPutAll: (String new: 100 withAll: $ ); cr.
"Initialize the test resources."
suite resources do: [ :each |
each isAvailable
ifFalse: [ each signalInitializationError ] ]! !
!HDTestReport methodsFor: 'running' stamp: 'lr 1/10/2010 15:22'!
tearDown
suite resources
do: [ :each | each reset ].
stream tab; nextPutAll: ''; cr.
stream tab; nextPutAll: ''; cr.
stream nextPutAll: ''.
stream position: suitePosition.
stream nextPutAll: ' failures="'; print: suiteFailures; nextPutAll:'" errors="'; print: suiteErrors; nextPutAll: '" time="'; print: suiteTime / 1000.0; nextPutAll: '">'.
stream close! !