reports/Builder__TestReportFormat.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 13 Jan 2012 11:06:33 +0100
changeset 67 73732acacfc1
child 86 29a8a74674f5
permissions -rw-r--r--
initial checkin

"{ Package: 'stx:goodies/builder/reports' }"

"{ NameSpace: Builder }"

ReportFormat subclass:#TestReportFormat
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Builder-Reports-Formats'
!

TestReportFormat subclass:#JUnit
	instanceVariableNames:'position failures errors startTime stopTime'
	classVariableNames:''
	poolDictionaries:''
	privateIn:TestReportFormat
!

TestReportFormat subclass:#PerfPublisher
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:TestReportFormat
!

TestReportFormat subclass:#PythonUnittest
	instanceVariableNames:'index'
	classVariableNames:''
	poolDictionaries:''
	privateIn:TestReportFormat
!

TestReportFormat subclass:#TAP
	instanceVariableNames:'index'
	classVariableNames:''
	poolDictionaries:''
	privateIn:TestReportFormat
!


!TestReportFormat class methodsFor:'testing'!

isAbstract

    ^self == TestReportFormat

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

!TestReportFormat methodsFor:'accessing - defaults'!

defaultFileSuffix
    "superclass HDReportFormat says that I am responsible to implement this method"

    ^ 'xml'

    "Modified: / 04-08-2011 / 12:48:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat methodsFor:'writing'!

writeTestCase: testcase outcome: outcome time: time exception: exception

    | stacktrace |
    exception isNil ifTrue:[
        stacktrace := nil.        
    ] ifFalse:[
        stacktrace :=
            (String streamContents:[:s|
                self writeStackTrace: exception of: testcase on: s
            ])
    ].

    ^self writeTestCase: testcase outcome: outcome time: time exception: exception 
             stacktrace: stacktrace

    "Created: / 03-08-2011 / 19:44:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

writeTestCase: testcase outcome: outcome time: time exception: exception stacktrace: stacktrace

    "Write an outcome of a given test.
     Argumments:
        testcase....the testcase
        outcome.....one of #pass, #failure, #error
        time........time taken to run the test in milliseconds
        exception...exception that caused error/failure or nil if N/A
        backtrace...stacktrace info or nil if N/A"

    self subclassResponsibility

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

!TestReportFormat methodsFor:'writing - utilities'!

writeContext: context on: s

    |home mthd src|
    [
    context printOn: s.
    s cr.
"
    s nextPutAll:'receiver: '. self print: context receiver on: s. s cr.
    s nextPutAll:'selector: '. self print:context selector on: s. s cr.
    s nextPutAll:'args: '; cr.
    context args keysAndValuesDo:[:idx :eachArg |
        s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '. self  print: eachArg on: s.s cr.
    ].
    s nextPutAll:'vars: '; cr.
    context vars keysAndValuesDo:[:idx :eachVar |
        s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '. self print: eachVar on: s.s cr.
    ].
    s nextPutAll:'source: '; cr.    

    [
    home := context methodHome.
    mthd := home method.
    mthd isNil ifTrue:[
         s nextPutAll: '** no source **'. s cr. s cr.
        ^ self.
    ].
    src := mthd source.
    src isNil ifTrue:[
        s nextPutAll: '** no source **'. s cr. s cr.
        ^ self.
    ].
    ] on: Error do:[:ex|
        s 
            nextPutAll: '** error when getting source: ';
            nextPutAll:  ex description;
            nextPutAll: '**';
            cr; cr.
        ^ self.
    ].
    src := src asCollectionOfLines.
    src keysAndValuesDo:[:lNr :line |
        lNr == context lineNumber ifTrue:[
            s nextPutAll:'>> '.
        ] ifFalse:[
            s nextPutAll:'   '.
        ].
        s nextPutAll: line; cr.
    ].
    s cr.
"
    ] on: Error do:[:ex|
        s   cr;
            nextPutAll:'!!!!!!ERROR WHEN GETTING STACK TRACE!!!!!!'; cr;
            nextPutAll: ex description; cr
    ]

    "Modified: / 01-04-2011 / 12:00:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 03-08-2011 / 14:53:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

writeStackTrace:err of:aTestCase on: str

    |context|

    context := err signalerContext.
    
    [ context isNil 
        or:[ (context receiver == aTestCase and:[ context selector == #runCase ])
            or: [ context receiver == self and:[ context selector == #setUp ] ] ] ] whileFalse:
                [ self writeContext: context on: str.
                context := context sender ]

    "Created: / 03-08-2011 / 14:53:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::JUnit class methodsFor:'accessing'!

symbolicNames
    ^ #( #junit #junit40 )

    "Created: / 04-08-2011 / 11:45:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::JUnit class methodsFor:'documentation'!

version_SVN
    ^ '§Id: Builder__TestReportFormat.st 282 2011-11-07 08:51:43Z vranyj1 §'
! !

!TestReportFormat::JUnit methodsFor:'initialization'!

initialize

    super initialize.
    errors := 0.
    failures := 0.

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

!TestReportFormat::JUnit methodsFor:'writing'!

writeFooter
    stopTime := OperatingSystem getMillisecondTime.
    stream
        tab;
        nextPutAll:'<system-out><!![CDATA[]]></system-out>';
        nextPut:Character lf.
    stream
        tab;
        nextPutAll:'<system-err><!![CDATA[]]></system-err>';
        nextPut:Character lf.
    stream nextPutAll:'</testsuite>'.
    stream stream position:position.
    stream
        nextPutAll:' failures="';
        print:failures;
        nextPutAll:'" errors="';
        print:errors;
        nextPutAll:'" time="';
        print:(Time milliseconds:stopTime since:startTime) / 1000.0;
        nextPutAll:'">'.
    stream close.

    "Created: / 03-08-2011 / 14:22:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

writeHeader
    stream
        nextPutAll:'<?xml version="1.0" encoding="UTF-8"?>';
        nextPut:Character lf.
    stream
        nextPutAll:'<testsuite name="';
        nextPutAll:(Report encode:report name);
        nextPutAll:'" tests="';
        print:report suite testCount;
        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."
    position := stream stream position - 1.
    stream
        nextPutAll:(String new:100 withAll:$ );
        nextPut:Character lf.
    startTime := OperatingSystem getMillisecondTime.

    "Created: / 03-08-2011 / 19:14:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

writeTestCase:testcase outcome:outcome time:time exception: exception stacktrace:stacktrace

    outcome == #failure ifTrue:[failures := failures + 1].
    outcome == #error ifTrue:[errors := errors + 1].

    stream tab; 
            nextPutAll: '<testcase classname="'; 
            nextPutAll: (self encode: testcase nameForHDTestReport); 
            nextPutAll: '" name="'; 
            nextPutAll: (self encode: testcase selectorForHDTestReport); 
            nextPutAll: '" time="'; print: (time ? 0) / 1000.0; nextPutAll: '">'; cr.

    outcome ~~ #pass ifTrue:[
        | type message |

        exception isNil ifTrue:[
            type := 'unknown exception'.
            message := 'unknown exception occured (no exception details available)'
        ] ifFalse:[
            type := exception class name.
            message := exception messageText ifNil:[ exception description ].
        ].
        

        stream tab; tab;
            nextPut:$<; nextPutAll: outcome;
            nextPutAll:' type="';
            nextPutAll:(self encode:type);
            nextPutAll:'" message="';
            nextPutAll:(self encode: message);
            nextPutAll:'">';
            nextPutAll:(self encode:stacktrace ? 'stacktrace not available');
            nextPutAll:'</'; nextPutAll: outcome; nextPutAll:'>';
            nextPut:Character lf
    ].
    stream tab; 
            nextPutAll: '</testcase>'; cr.


    stream flush

    "Created: / 03-08-2011 / 19:42:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::PerfPublisher class methodsFor:'accessing'!

symbolicNames
    "Returns a collection of symbolic names for this format"

    ^ #(perfPublisher)

    "Modified: / 04-08-2011 / 11:52:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::PerfPublisher class methodsFor:'documentation'!

version_SVN
    ^ '§Id: Builder__TestReportFormat.st 282 2011-11-07 08:51:43Z vranyj1 §'
! !

!TestReportFormat::PerfPublisher methodsFor:'writing'!

writeFooter

    stream nextPutLine: '</report>'

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

writeHeader

    |reportName reportCategory testClass|

    reportName := report suite name.
    reportCategory := 'uncategorized'.  "/ it is a required attribute; so what should we use ?

    (testClass := Smalltalk at:reportName asSymbol) isBehavior ifTrue:[
        reportCategory := testClass category.  "/ at least, something to show
    ].

    stream
        nextPutLine: '<?xml version="1.0"?>';
        nextPutLine:('<report name="%1" categ="%2">' bindWith:reportName with:reportCategory);
        nextPutLine:('  <start>');
        nextPutLine:('    <date format="YYYYMMDD" val="%1" />' bindWith:(Date today printStringFormat:'%y%m%d'));
        nextPutLine:('    <time format="HHMMSS" val="%1" />' bindWith:(Time now printStringFormat:'%h%m%s'));
        nextPutLine:('  </start>').

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

writeTestCase:testcase outcome:outcome time:time exception:exception stacktrace:stacktrace

    "
    Example:
    <test
        name='test_format_link_not_in_repos_with_line'
        executed='exec-status'
      <result>  
        <success passed='result-status' state='result-state'/>
        <errorlog><!![CDATA[EXEMPLE OF ERROR LOG]]></errorlog>
      </result>  
    </test>  
    "

    |testClassName executionTime testName testDescription 
     successPassed successState exceptionInfo
     compilerName compilerVersion compilerConfiguration compilerVersionDate 
     timeUnit timeMeasure 
     sysInfo osType osVersion cpuType|

    testClassName := testcase printString.
    testName := testcase selector.

    "most tests do not know, and return nil here!!"
    executionTime := time.    "/ millis
    testDescription := '%1-%2' bindWith:testClassName with:testName.

    successPassed := (outcome == #pass) ifTrue:['yes'] ifFalse:['no'].
    outcome ~~ #pass ifTrue:[
        exceptionInfo := stacktrace ? 'No stacktrace available'.
    ].

    successState := 'foo'.

    "/ caveat: the following needs to be made dialect-specific
    compilerName := 'Smalltalk/X'.
    compilerVersion := Smalltalk versionString.
    compilerConfiguration := Smalltalk configuration.
    compilerVersionDate := Smalltalk versionDate.

    sysInfo := OperatingSystem getSystemInfo.
    osType := (sysInfo at:#osType ifAbsent:'?').
    osVersion := (sysInfo at:#release ifAbsent:'?').

    cpuType := (sysInfo at:#cpuType ifAbsent:'?').
    "/ cpuSpeed := (sysInfo at:#cpuSpeed ifAbsent:'?').

    timeUnit := 'ms'.
    timeMeasure := executionTime.

    stream
        nextPutLine:('<test name="%1" executed="yes">' bindWith: testName);
        nextPutLine:('  <description><!![CDATA[%1]]></description>' bindWith: testDescription);
        nextPutLine:'  <platform>';
        nextPutLine:'    <os>';
        nextPutLine:('      <type><!![CDATA[%1]]></type>' bindWith:osType);
        nextPutLine:('      <version><!![CDATA[%1]]></version>' bindWith:osVersion);
        nextPutLine:'    </os>';
        nextPutLine:('    <processor arch="%1">' bindWith:cpuType);
        "/ nextPutLine:('      <frequency> unit="Mhz" cpufreq="%1" />' bindWith:cpuSpeed);
        nextPutLine:'    </processor>';
        nextPutLine:('    <compiler name="%1" version="%2" versiondate="%3" configuration="%4" />' 
                            bindWith:compilerName with:compilerVersion 
                            with:compilerVersionDate with:compilerConfiguration);
        "/ nextPutLine:'    <environment />';
        nextPutLine:'  </platform>';
        nextPutLine:'  <result>';
        nextPutLine:('    <success passed="%1" state="100" />' 
                            bindWith:successPassed with:successState);
        "/ cg: in the perfPublisher documentation, I found "mesure".
        "/ I am not sure, if that was a typo, or is actually what is expected...
        "/ to be on the save side, I generate both a mesure and a measure attribute,
        "/ so it will work, even if they ever fix perfPublisher's xml parser.
        nextPutLine:('    <executiontime unit="%1" mesure="%2" measure="%2" isRelevant="yes" />' 
                            bindWith:timeUnit with:timeMeasure).

    exceptionInfo notNil ifTrue:[
        stream
            nextPutLine:'    <errorlog><!![CDATA[';
            nextPutAll:exceptionInfo;
            nextPutLine:']]></errorlog>'.
        ].
    stream
        nextPutLine:'  </result>'.

    stream nextPutLine:'</test>'.

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

!TestReportFormat::PythonUnittest class methodsFor:'accessing'!

symbolicNames
    "Returns a collection of symbolic names for this format"

    ^ #(python python-unittest)

    "Modified: / 04-08-2011 / 11:52:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::PythonUnittest class methodsFor:'documentation'!

version_SVN
    ^ '§Id: Builder__TestReportFormat.st 282 2011-11-07 08:51:43Z vranyj1 §'
! !

!TestReportFormat::PythonUnittest methodsFor:'writing'!

writeFooter

    stream
        nextPutLine: '</unittest-results>'

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

writeHeader

    stream
        nextPutLine: '<?xml version="1.0"?>';
        nextPutLine: '<unittest-results>'.

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

writeTestCase:testcase outcome:outcome time:time exception:exception stacktrace:stacktrace

    "
    Example:
    <test
        duration='0.0188629627228'
        status='error'
        fixture='bitten.tests.web_ui.SourceFileLinkFormatterTestCase'
        name='test_format_link_not_in_repos_with_line'
        file='/usr/src/trac-bitten-0.6b2.dfsg/bitten/tests/web_ui.py'>
    "

    | testClassName status |

    testClassName := testcase class printString.

    status := outcome == #pass ifTrue:[#success] ifFalse:[outcome].

    stream
        nextPutAll:'<test duration="'; nextPutAll:time; nextPutLine:'"'; 
        tab; nextPutAll:'status="'; nextPutAll: status; nextPutLine:'"';
        tab; nextPutAll:'ficture="'; nextPutAll: testClassName; nextPutLine:'"';
        tab; nextPutAll:'name="'; nextPutAll: testcase selector; nextPutLine:'"';
        "It seems that some tools requires the file attributes. So we supply one :-)"
        tab; nextPutAll:'file="'; nextPutAll: testClassName , '.st'; nextPutLine:'">'.

    outcome == #pass ifFalse:[
        stream nextPutLine:'<traceback><!![CDATA['.
        stream nextPutAll: stacktrace ? 'No stacktrace available'.
        stream nextPutLine:']]></traceback>'.
    ].

    stream nextPutLine:'</test>'.

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

!TestReportFormat::TAP class methodsFor:'accessing'!

symbolicNames
    "Returns a collection of symbolic names for this format"

    ^ #(tap TAP)

    "Modified: / 04-08-2011 / 11:52:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::TAP class methodsFor:'documentation'!

version_SVN
    ^ '§Id: Builder__TestReportFormat.st 282 2011-11-07 08:51:43Z vranyj1 §'
! !

!TestReportFormat::TAP methodsFor:'accessing - defaults'!

defaultFileSuffix
    "superclass HDReportFormat says that I am responsible to implement this method"

    ^ 'tap'

    "Modified: / 04-08-2011 / 12:47:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TestReportFormat::TAP methodsFor:'writing'!

writeFooter

    "nothing to do"

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

writeHeader

    stream nextPutAll: '1..'; nextPutAll: report suite testCount printString; cr.
    index := 0

    "Modified: / 04-08-2011 / 13:49:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

writeTestCase:testcase outcome:outcome time:time exception:exception stacktrace:stacktrace

    | testDescription statusString|

    index := index + 1.

    testDescription := '%1-%2 (%3ms)'
                            bindWith:testcase printString
                            with:testcase selector
                            with:time.

    statusString := (outcome == #pass)
                        ifTrue:['ok']
                        ifFalse:['not ok'].

    stream nextPutLine:('%1 %2 - %3'
                            bindWith:statusString
                            with:index
                            with:testDescription).

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

!TestReportFormat class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '§Id: Builder__TestReportFormat.st 282 2011-11-07 08:51:43Z vranyj1 §'
! !