reports/Builder__TestReportFormat.st
changeset 513 f50803f4bb59
parent 319 f525a38861f1
equal deleted inserted replaced
512:9d572c1caefa 513:f50803f4bb59
    61 
    61 
    62 writeTestCase: testcase outcome: outcome time: time exception: exception
    62 writeTestCase: testcase outcome: outcome time: time exception: exception
    63 
    63 
    64     | stacktrace |
    64     | stacktrace |
    65     exception isNil ifTrue:[
    65     exception isNil ifTrue:[
    66         stacktrace := nil.        
    66         stacktrace := nil.
    67     ] ifFalse:[
    67     ] ifFalse:[
    68         stacktrace :=
    68         stacktrace :=
    69             (String streamContents:[:s|
    69             (String streamContents:[:s|
    70                 self writeStackTrace: exception of: testcase on: s
    70                 self writeStackTrace: exception of: testcase on: s
    71             ])
    71             ])
    72     ].
    72     ].
    73 
    73 
    74     ^self writeTestCase: testcase outcome: outcome time: time exception: exception 
    74     ^self writeTestCase: testcase outcome: outcome time: time exception: exception
    75              stacktrace: stacktrace
    75              stacktrace: stacktrace
    76 
    76 
    77     "Created: / 03-08-2011 / 19:44:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    77     "Created: / 03-08-2011 / 19:44:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    78 !
    78 !
    79 
    79 
   107     context args keysAndValuesDo:[:idx :eachArg |
   107     context args keysAndValuesDo:[:idx :eachArg |
   108         s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '. eachArg printOn: s.s cr.
   108         s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '. eachArg printOn: s.s cr.
   109     ].
   109     ].
   110     s nextPutAll:'vars: '; cr.
   110     s nextPutAll:'vars: '; cr.
   111     context vars keysAndValuesDo:[:idx :eachVar |
   111     context vars keysAndValuesDo:[:idx :eachVar |
   112         s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '. 
   112         s nextPutAll:'  '. idx printOn: s. s nextPutAll:': '.
   113         eachVar isString ifTrue:[
   113         eachVar isString ifTrue:[
   114             eachVar storeOn: s.
   114             eachVar storeOn: s.
   115         ] ifFalse:[
   115         ] ifFalse:[
   116             eachVar printOn: s.
   116             eachVar printOn: s.
   117         ].
   117         ].
   118         s cr.
   118         s cr.
   119     ].
   119     ].
   120     s nextPutAll:'source: '; cr.    
   120     s nextPutAll:'source: '; cr.
   121 
   121 
   122     [
   122     [
   123     home := context methodHome.
   123     home := context methodHome.
   124     mthd := home method.
   124     mthd := home method.
   125     mthd isNil ifTrue:[
   125     mthd isNil ifTrue:[
   130     src isNil ifTrue:[
   130     src isNil ifTrue:[
   131         s nextPutAll: '** no source **'. s cr. s cr.
   131         s nextPutAll: '** no source **'. s cr. s cr.
   132         ^ self.
   132         ^ self.
   133     ].
   133     ].
   134     ] on: Error do:[:ex|
   134     ] on: Error do:[:ex|
   135         s 
   135         s
   136             nextPutAll: '** error when getting source: ';
   136             nextPutAll: '** error when getting source: ';
   137             nextPutAll:  ex description;
   137             nextPutAll:  ex description;
   138             nextPutAll: '**';
   138             nextPutAll: '**';
   139             cr; cr.
   139             cr; cr.
   140         ^ self.
   140         ^ self.
   243         nextPut:Character lf.
   243         nextPut:Character lf.
   244     stream
   244     stream
   245         nextPutAll:'<testsuite name="';
   245         nextPutAll:'<testsuite name="';
   246         nextPutAll:(Report encode:report name);
   246         nextPutAll:(Report encode:report name);
   247         nextPutAll:'" tests="';
   247         nextPutAll:'" tests="';
   248         print:report suite testCount;
   248         print:report suite countTests;
   249         nextPutAll:('" hostname="%1"' bindWith:OperatingSystem getHostName);
   249         nextPutAll:('" hostname="%1"' bindWith:OperatingSystem getHostName);
   250         nextPutAll:'>'.
   250         nextPutAll:'>'.
   251      "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."
   251      "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."
   252     position := stream stream position - 1.
   252     position := stream stream position - 1.
   253     stream
   253     stream
   264         nextPutLine:('    <property name="user.name" value="%1" />' bindWith:OperatingSystem getLoginName);
   264         nextPutLine:('    <property name="user.name" value="%1" />' bindWith:OperatingSystem getLoginName);
   265         nextPutLine:('    <property name="user.language" value="%1" />' bindWith:Smalltalk language).
   265         nextPutLine:('    <property name="user.language" value="%1" />' bindWith:Smalltalk language).
   266 "/    stream
   266 "/    stream
   267 "/        nextPutLine:('    <property name="smalltalk.libbasic.version" value="%1" />'bindWith:stx_libbasic versionString).
   267 "/        nextPutLine:('    <property name="smalltalk.libbasic.version" value="%1" />'bindWith:stx_libbasic versionString).
   268     stream
   268     stream
   269         nextPutLine: '  </properties>'.       
   269         nextPutLine: '  </properties>'.
   270 
   270 
   271     startTime := OperatingSystem getMillisecondTime.
   271     startTime := OperatingSystem getMillisecondTime.
   272 
   272 
   273     "Created: / 03-08-2011 / 19:14:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   273     "Created: / 03-08-2011 / 19:14:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   274     "Modified: / 06-06-2014 / 01:14:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   274     "Modified: / 06-06-2014 / 01:14:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   354 !TestReportFormat::JUnit methodsFor:'writing - utilities'!
   354 !TestReportFormat::JUnit methodsFor:'writing - utilities'!
   355 
   355 
   356 writeCDATA: string
   356 writeCDATA: string
   357     | start stop |
   357     | start stop |
   358 
   358 
   359     start := 1. 
   359     start := 1.
   360     stop := start.
   360     stop := start.
   361     [ (stop := (string indexOf: $] startingAt: stop)) ~~ 0 ] whileTrue:[
   361     [ (stop := (string indexOf: $] startingAt: stop)) ~~ 0 ] whileTrue:[
   362         ((stop < (string size - 1)) 
   362         ((stop < (string size - 1))
   363             and:[(string at: stop + 1) == $]
   363             and:[(string at: stop + 1) == $]
   364                 and:[(string at: stop + 2) == $>]]) ifTrue:[
   364                 and:[(string at: stop + 2) == $>]]) ifTrue:[
   365                     " Okay, found CDATA end token "
   365                     " Okay, found CDATA end token "
   366                     stream nextPutAll: string startingAt: start to: stop + 1.
   366                     stream nextPutAll: string startingAt: start to: stop + 1.
   367                     stream nextPutAll: ']]><!![CDATA[>'.
   367                     stream nextPutAll: ']]><!![CDATA[>'.
   369                 ] ifFalse:[
   369                 ] ifFalse:[
   370                     stop := stop + 1.
   370                     stop := stop + 1.
   371                 ].
   371                 ].
   372     ].
   372     ].
   373     start < string size ifTrue:[
   373     start < string size ifTrue:[
   374         stream nextPutAll: string startingAt: start to: string size.        
   374         stream nextPutAll: string startingAt: start to: string size.
   375     ].
   375     ].
   376 
   376 
   377     "
   377     "
   378     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:'ABCD']
   378     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:'ABCD']
   379     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:']]]]']         
   379     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:']]]]']
   380     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:'Some <[CDATA[ CDATA ]]> Some Text and stray terminator ]]> here']
   380     String streamContents:[:s | Builder::TestReportFormat::JUnit new report: nil stream: s; writeCDATA:'Some <[CDATA[ CDATA ]]> Some Text and stray terminator ]]> here']
   381     "
   381     "
   382 
   382 
   383     "Created: / 05-07-2013 / 16:54:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   383     "Created: / 05-07-2013 / 16:54:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   384 ! !
   384 ! !
   435     "
   435     "
   436     Example:
   436     Example:
   437     <test
   437     <test
   438         name='test_format_link_not_in_repos_with_line'
   438         name='test_format_link_not_in_repos_with_line'
   439         executed='exec-status'
   439         executed='exec-status'
   440       <result>  
   440       <result>
   441         <success passed='result-status' state='result-state'/>
   441         <success passed='result-status' state='result-state'/>
   442         <errorlog><!![CDATA[EXEMPLE OF ERROR LOG]]></errorlog>
   442         <errorlog><!![CDATA[EXEMPLE OF ERROR LOG]]></errorlog>
   443       </result>  
   443       </result>
   444     </test>  
   444     </test>
   445     "
   445     "
   446 
   446 
   447     |testClassName executionTime testName testDescription 
   447     |testClassName executionTime testName testDescription
   448      successPassed successState exceptionInfo
   448      successPassed successState exceptionInfo
   449      compilerName compilerVersion compilerConfiguration compilerVersionDate 
   449      compilerName compilerVersion compilerConfiguration compilerVersionDate
   450      timeUnit timeMeasure 
   450      timeUnit timeMeasure
   451      sysInfo osType osVersion cpuType|
   451      sysInfo osType osVersion cpuType|
   452 
   452 
   453     testClassName := testcase printString.
   453     testClassName := testcase printString.
   454     testName := testcase selector.
   454     testName := testcase selector.
   455 
   455 
   489         nextPutLine:('      <version><!![CDATA[%1]]></version>' bindWith:osVersion);
   489         nextPutLine:('      <version><!![CDATA[%1]]></version>' bindWith:osVersion);
   490         nextPutLine:'    </os>';
   490         nextPutLine:'    </os>';
   491         nextPutLine:('    <processor arch="%1">' bindWith:cpuType);
   491         nextPutLine:('    <processor arch="%1">' bindWith:cpuType);
   492         "/ nextPutLine:('      <frequency> unit="Mhz" cpufreq="%1" />' bindWith:cpuSpeed);
   492         "/ nextPutLine:('      <frequency> unit="Mhz" cpufreq="%1" />' bindWith:cpuSpeed);
   493         nextPutLine:'    </processor>';
   493         nextPutLine:'    </processor>';
   494         nextPutLine:('    <compiler name="%1" version="%2" versiondate="%3" configuration="%4" />' 
   494         nextPutLine:('    <compiler name="%1" version="%2" versiondate="%3" configuration="%4" />'
   495                             bindWith:compilerName with:compilerVersion 
   495                             bindWith:compilerName with:compilerVersion
   496                             with:compilerVersionDate with:compilerConfiguration);
   496                             with:compilerVersionDate with:compilerConfiguration);
   497         "/ nextPutLine:'    <environment />';
   497         "/ nextPutLine:'    <environment />';
   498         nextPutLine:'  </platform>';
   498         nextPutLine:'  </platform>';
   499         nextPutLine:'  <result>';
   499         nextPutLine:'  <result>';
   500         nextPutLine:('    <success passed="%1" state="100" />' 
   500         nextPutLine:('    <success passed="%1" state="100" />'
   501                             bindWith:successPassed with:successState);
   501                             bindWith:successPassed with:successState);
   502         "/ cg: in the perfPublisher documentation, I found "mesure".
   502         "/ cg: in the perfPublisher documentation, I found "mesure".
   503         "/ I am not sure, if that was a typo, or is actually what is expected...
   503         "/ I am not sure, if that was a typo, or is actually what is expected...
   504         "/ to be on the save side, I generate both a mesure and a measure attribute,
   504         "/ to be on the save side, I generate both a mesure and a measure attribute,
   505         "/ so it will work, even if they ever fix perfPublisher's xml parser.
   505         "/ so it will work, even if they ever fix perfPublisher's xml parser.
   506         nextPutLine:('    <executiontime unit="%1" mesure="%2" measure="%2" isRelevant="yes" />' 
   506         nextPutLine:('    <executiontime unit="%1" mesure="%2" measure="%2" isRelevant="yes" />'
   507                             bindWith:timeUnit with:timeMeasure).
   507                             bindWith:timeUnit with:timeMeasure).
   508 
   508 
   509     exceptionInfo notNil ifTrue:[
   509     exceptionInfo notNil ifTrue:[
   510         stream
   510         stream
   511             nextPutLine:'    <errorlog><!![CDATA[';
   511             nextPutLine:'    <errorlog><!![CDATA[';
   569 
   569 
   570     | testClassName result |
   570     | testClassName result |
   571 
   571 
   572     testClassName := testcase class printString.
   572     testClassName := testcase class printString.
   573 
   573 
   574     outcome result == TestResult statePass ifTrue:[ 
   574     outcome result == TestResult statePass ifTrue:[
   575         result := #success.
   575         result := #success.
   576     ] ifFalse:[ 
   576     ] ifFalse:[
   577         outcome result == TestResult stateFail ifTrue:[ 
   577         outcome result == TestResult stateFail ifTrue:[
   578             result := #failure.
   578             result := #failure.
   579         ] ifFalse:[ 
   579         ] ifFalse:[
   580             outcome result == TestResult stateError ifTrue:[ 
   580             outcome result == TestResult stateError ifTrue:[
   581                 result := #error.
   581                 result := #error.
   582             ] ifFalse:[ 
   582             ] ifFalse:[
   583                 outcome result == TestResult stateSkip ifTrue:[ 
   583                 outcome result == TestResult stateSkip ifTrue:[
   584                     result := #skip.
   584                     result := #skip.
   585                 ] ifFalse:[
   585                 ] ifFalse:[
   586                     self error: 'Invalid test result'.
   586                     self error: 'Invalid test result'.
   587                 ]
   587                 ]
   588             ].
   588             ].
   589         ].
   589         ].
   590     ].    
   590     ].
   591 
   591 
   592     stream
   592     stream
   593         nextPutAll:'<test duration="'; nextPutAll:time; nextPutLine:'"'; 
   593         nextPutAll:'<test duration="'; nextPutAll:time; nextPutLine:'"';
   594         tab; nextPutAll:'status="'; nextPutAll: result; nextPutLine:'"';
   594         tab; nextPutAll:'status="'; nextPutAll: result; nextPutLine:'"';
   595         tab; nextPutAll:'ficture="'; nextPutAll: testClassName; nextPutLine:'"';
   595         tab; nextPutAll:'ficture="'; nextPutAll: testClassName; nextPutLine:'"';
   596         tab; nextPutAll:'name="'; nextPutAll: testcase selector; nextPutLine:'"';
   596         tab; nextPutAll:'name="'; nextPutAll: testcase selector; nextPutLine:'"';
   597         "It seems that some tools requires the file attributes. So we supply one :-)"
   597         "It seems that some tools requires the file attributes. So we supply one :-)"
   598         tab; nextPutAll:'file="'; nextPutAll: testClassName , '.st'; nextPutLine:'">'.
   598         tab; nextPutAll:'file="'; nextPutAll: testClassName , '.st'; nextPutLine:'">'.
   643     "Modified: / 03-08-2011 / 20:05:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   643     "Modified: / 03-08-2011 / 20:05:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   644 !
   644 !
   645 
   645 
   646 writeHeader
   646 writeHeader
   647 
   647 
   648     stream nextPutAll: '1..'; nextPutAll: report suite testCount printString; cr.
   648     stream nextPutAll: '1..'; nextPutAll: report suite countTests printString; cr.
   649     index := 0
   649     index := 0
   650 
   650 
   651     "Modified: / 04-08-2011 / 13:49:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   651     "Modified: / 04-08-2011 / 13:49:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   652 !
   652 !
   653 
   653 
   654 writeTestCase:testcase outcome:outcome time:time exception:exception stacktrace:stacktrace
   654 writeTestCase:testcase outcome:outcome time:time exception:exception stacktrace:stacktrace
   655 
   655 
   656     | result testDescription statusString |
   656     | result testDescription statusString |
   657 
   657 
   658     index := index + 1.
   658     index := index + 1.
   659     outcome result == TestResult statePass ifTrue:[ 
   659     outcome result == TestResult statePass ifTrue:[
   660         result := #pass.
   660         result := #pass.
   661     ] ifFalse:[ 
   661     ] ifFalse:[
   662         outcome result == TestResult stateFail ifTrue:[ 
   662         outcome result == TestResult stateFail ifTrue:[
   663             result := #failure.
   663             result := #failure.
   664         ] ifFalse:[ 
   664         ] ifFalse:[
   665             outcome result == TestResult stateError ifTrue:[ 
   665             outcome result == TestResult stateError ifTrue:[
   666                 result := #error.
   666                 result := #error.
   667             ] ifFalse:[ 
   667             ] ifFalse:[
   668                 outcome result == TestResult stateSkip ifTrue:[ 
   668                 outcome result == TestResult stateSkip ifTrue:[
   669                     result := #skip.
   669                     result := #skip.
   670                 ] ifFalse:[
   670                 ] ifFalse:[
   671                     self error: 'Invalid test result'.
   671                     self error: 'Invalid test result'.
   672                 ]
   672                 ]
   673             ].
   673             ].
   674         ].
   674         ].
   675     ].    
   675     ].
   676 
   676 
   677     testDescription := '%1-%2 (%3ms)'
   677     testDescription := '%1-%2 (%3ms)'
   678                             bindWith:testcase printString
   678                             bindWith:testcase printString
   679                             with:testcase selector
   679                             with:testcase selector
   680                             with:time.
   680                             with:time.