MetricsReporter.st
author Stefan Vogel <sv@exept.de>
Tue, 23 Apr 2013 12:33:43 +0200
changeset 577 3dea1e941af7
parent 568 49eafe2c5ae8
child 584 aab981776647
permissions -rw-r--r--
class: TestResource added: #safeTearDown changed: #makeAvailable Take care of AbortOperationRequest being raised in Debugger in tearDown after an errornous test case.

"
 COPYRIGHT (c) 2012 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:goodies/sunit' }"

Object subclass:#MetricsReporter
	instanceVariableNames:'packages stream classMetricNames methodMetricNames
		packageMetricNames'
	classVariableNames:''
	poolDictionaries:''
	category:'SUnit-Report'
!

!MetricsReporter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2012 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.

"
!

documentation
"
    this is used as a last step in jenkins automated builds.

    Currently supported formats are:
        #xml_metrics      - a java metrics compatible format

    [author:]
        Claus Gittinger

    [see also:]
"
!

examples
"
                                                                               [exBegin]
    String streamContents:[:stream |
        MetricsReporter 
            reportPackages:{ 'stx:libjavascript' } 
            format:#xml_metrics 
            on:stream.
    ].
                                                                               [exEnd]
                                                                               [exBegin]
    String streamContents:[:stream |
        MetricsReporter 
            reportPackages:{ 'stx:libbasic' } 
            format:#xml_metrics 
            on:stream.
    ].
                                                                               [exEnd]
                                                                               [exBegin]
    String streamContents:[:stream |
        MetricsReporter 
            reportPackages:{ 'stx:libbasic*' } 
            format:#xml_metrics 
            on:stream.
    ].
                                                                               [exEnd]
                                                                               [exBegin]
    'metrics.xml' asFilename writingFileDo:[:stream |
        MetricsReporter 
            reportPackages:{ 'stx:libjavascript' } 
            format:#xml_metrics 
            on:stream.
    ].
                                                                               [exEnd]

                                                                               [exBegin]
    'metrics.xml' asFilename writingFileDo:[:stream |
        MetricsReporter 
                reportPackages:
                        { 
                            'exept:workflow' 
                            'exept:expecco' 
                            'exept:expecco/plugins/*' 
                        } 
                format:#xml_metrics 
                on:stream.
    ].
                                                                               [exEnd]

  package metrics only:
                                                                               [exBegin]
    MetricsReporter new
            stream: Transcript;
            packages:
                    { 
                        'exept:workflow' . 
                        'exept:expecco'  .
                    };
            classMetricNames: #();    
            methodMetricNames: #();    
            packageMetricNames: #( 'LOC' 'NOM' 'NOC');    
            reportXml_metrics.
                                                                               [exEnd]
                                                                               [exBegin]
    MetricsReporter new
            stream: Transcript;
            packages:
                    { 
                        'stx:libbasic' . 
                        'stx:libbasic2' . 
                        'stx:libbasic3' . 
                    };
            classMetricNames: #();    
            methodMetricNames: #();    
            packageMetricNames: #( 'LOC' 'NOM' 'NOC');    
            reportXml_metrics.
                                                                               [exEnd]
                                                                               [exBegin]
    MetricsReporter new
            stream: Transcript;
            packages:
                    { 
                        'stx:libbasic*' . 
                    };
            classMetricNames: #();    
            methodMetricNames: #();    
            packageMetricNames: #( 'LOC' 'NOM' 'NOC');    
            reportXml_metrics.
                                                                               [exEnd]
                                                                               [exBegin]
    MetricsReporter new
            stream: Transcript;
            packages:
                    { 
                        'stx:*' . 
                    };
            classMetricNames: #();    
            methodMetricNames: #();    
            packageMetricNames: #( 'LOC' 'NOM' 'NOC');    
            reportXml_metrics.
                                                                               [exEnd]
"
!

format_metrics
"
<?xml version=""1.0"" encoding=""UTF-8"" ?>

<!!ELEMENT metrics (project)* >
<!!ELEMENT project (name, measurement*, group*) >
<!!ELEMENT group (name, measurement*, class*) >
<!!ELEMENT class (name, measurement*, method*) >
<!!ELEMENT method (name, measurement*) >
<!!ELEMENT name (#PCDATA) >
<!!ELEMENT measurement (short-name, long-name, value, (members? | (minimum, median, average, standard-deviation, maximum, sum, nb-data-points))) >
<!!ELEMENT short-name (#PCDATA) >
<!!ELEMENT long-name (#PCDATA) >
<!!ELEMENT value (#PCDATA) >
<!!ELEMENT members (member*) >
<!!ELEMENT minimum (#PCDATA) >
<!!ELEMENT median (#PCDATA) >
<!!ELEMENT average (#PCDATA) >
<!!ELEMENT standard-deviation (#PCDATA) >
<!!ELEMENT maximum (#PCDATA) >
<!!ELEMENT sum (#PCDATA) >
<!!ELEMENT nb-data-points (#PCDATA) >
<!!ELEMENT member (#PCDATA) >
"
! !

!MetricsReporter class methodsFor:'queries'!

supportedFormats
   "return a list of formats and short-info-string, as per supported format symbol"

    ^ #(
        (#'xml_metrics'       'xml format')
    )

    "Created: / 30-07-2011 / 10:18:18 / cg"
! !

!MetricsReporter class methodsFor:'reporting'!

reportPackages: aCollectionOfPackages format: format on: stream
    self new 
        reportPackages: aCollectionOfPackages format: format on: stream
! !

!MetricsReporter methodsFor:'accessing'!

classMetricNames
    ^ classMetricNames ? #( 'NOM' 'LOC' )
!

classMetricNames:something
    classMetricNames := something.
!

methodMetricNames
    ^ methodMetricNames ? #( "'LOC'" )
!

methodMetricNames:something
    methodMetricNames := something.
!

packageMetricNames
    ^ packageMetricNames ? #( 'LOC' )
!

packageMetricNames:something
    packageMetricNames := something.
!

packages:something
    packages := something.
!

stream:something
    stream := something.
! !

!MetricsReporter methodsFor:'metric generation'!

classMetricValue:metricName for:aClass
    |metric|

    metric := OOM::ClassMetrics type:metricName for:aClass.
    ^ self metricInfoFor:metric
!

methodMetricValue:metricName for:aMethod
    |metric|

    metric := OOM::MethodMetrics type:metricName for:aMethod.
    ^ self metricInfoFor:metric
!

metricInfoFor:metric
    ^ { metric class shortName . metric class descriptiveName . metric metricValue }
!

packageMetricValue:metricName for:aPackageIDOrPattern
    |overAllInfo|

    aPackageIDOrPattern includesMatchCharacters ifTrue:[
        Smalltalk allProjectIDs do:[:eachPackageID |
            |thisInfo|

            (eachPackageID matches:aPackageIDOrPattern) ifTrue:[
                thisInfo := self metricInfoFor:(OOM::PackageMetrics type:metricName for:eachPackageID).
                overAllInfo isNil ifTrue:[
                    overAllInfo := thisInfo
                ] ifFalse:[
                    "/ kludge: only works with accumulative metrics (i.e. not with averages etc.)
                    overAllInfo at:(overAllInfo size) put:(overAllInfo last + thisInfo last).   
                ].
            ].
        ].
        ^ overAllInfo
    ] ifFalse:[
        ^ self metricInfoFor:(OOM::PackageMetrics type:metricName for:aPackageIDOrPattern).
    ].
! !

!MetricsReporter methodsFor:'reporting'!

reportPackages: aCollectionOfPackages format: aSymbol on: aStream

    packages := aCollectionOfPackages.
    stream := aStream.
    self report: aSymbol
! !

!MetricsReporter methodsFor:'reporting - xml-metrics'!

generateClassMetricsFor:aClass
    ^ self classMetricNames collect:[:metricName |
        self classMetricValue:metricName for:aClass.
    ].
!

generateMethodMetricsFor:aMethod
    ^ self methodMetricNames collect:[:metricName |
        self methodMetricValue:metricName for:aMethod.
    ].
!

generatePackageMetricsFor:aPackageIDOrPattern
    ^ self packageMetricNames collect:[:metricName |
        self packageMetricValue:metricName for:aPackageIDOrPattern.
    ].
!

reportXml_metricValues:metricValues
    |metricShortName metricLongName metricValue|

    metricValues do:[:eachTuple |
        metricShortName := eachTuple first.
        metricLongName := eachTuple second.
        metricValue := eachTuple third.

        stream nextPutLine: '    <measurement>'.
        stream nextPutLine: ('      <short-name>%1</short-name>' bindWith:metricShortName).
        stream nextPutLine: ('      <long-name>%1</long-name>' bindWith:metricLongName).
        stream nextPutLine: ('      <value>%1</value>' bindWith:metricValue).
        stream nextPutLine: '    </measurement>'.
    ]
!

reportXml_metrics
    "
        self new
            stream:Transcript;
            packages:#( 'exept:workflow' );
            reportXml_metrics
    "

    "/ need the exept-metrics package
    (Smalltalk loadPackage:'exept:programming/oom') ifFalse:[
        self error:'cannot load oom package'.
    ].

    stream nextPutLine: '<?xml version="1.0"?>';
           nextPutLine: '<metrics>'.

    packages do:[:eachPackageID |
        "/ if the package is a matchPattern, generate metrics for all loaded packages
        "/ which match that pattern.
        "/ Otherwise, make sure that this package is loaded and generate metrics for that
        "/ one only.
        eachPackageID includesMatchCharacters ifFalse:[
            Smalltalk loadPackage:eachPackageID.
        ].
        self reportXml_metricsForPackage:eachPackageID
    ].
    stream nextPutLine: '</metrics>'.
!

reportXml_metricsForClass:aClass
    stream nextPutLine: '    <class>'.
    stream nextPutLine: ('      <name>%1</name>' bindWith:aClass name).

    self methodMetricNames notEmptyOrNil ifTrue:[
        aClass instAndClassMethodsDo:[:eachMethod |
            self reportXml_metricsForMethod:eachMethod
        ].
    ].

    self classMetricNames notEmptyOrNil ifTrue:[
        self reportXml_metricValues:(self generateClassMetricsFor:aClass).
    ].

    stream nextPutLine: '    </class>'.
!

reportXml_metricsForMethod:aMethod
    stream nextPutLine: '      <method>'.
    stream nextPutLine:('        <name>%1</name>' bindWith:aMethod selector).

    self reportXml_metricValues:(self generateMethodMetricsFor:aMethod).

    stream nextPutLine: '      </method>'.
!

reportXml_metricsForPackage:aPackageIDOrPattern
    |genMetricsForClass|

    genMetricsForClass :=
        [:aClass |
            Autoload autoloadFailedSignal handle:[:ex |
            ] do:[
                aClass autoload.
                self reportXml_metricsForClass:aClass
            ]
        ].

    stream nextPutLine: '  <project>'.
    stream nextPutLine: ('    <name>%1</name>' bindWith:aPackageIDOrPattern).

    (self classMetricNames notEmptyOrNil 
    or:[self methodMetricNames notEmptyOrNil]) ifTrue:[
        aPackageIDOrPattern includesMatchCharacters ifTrue:[
            Smalltalk allClasses do:[:eachClass |
                (eachClass package matches:aPackageIDOrPattern) iftrue:[ 
                    genMetricsForClass value:eachClass
                ].
            ].
        ] ifFalse:[
            Smalltalk allClassesInPackage:aPackageIDOrPattern do:genMetricsForClass.
        ].
    ].

    self reportXml_metricValues:(self generatePackageMetricsFor:aPackageIDOrPattern).

    stream nextPutLine: '  </project>'.
! !

!MetricsReporter methodsFor:'reporting-private'!

report:formatSymbol
    "currently supported formatSymbols:
            xml_metrics"

    |reportFormatSelector|

    reportFormatSelector := self reportFormatSelector:formatSymbol.
    (self respondsTo: reportFormatSelector)
        ifTrue:[self perform: reportFormatSelector]
        ifFalse:[self error:'Unsupported format: ', formatSymbol].

    "Modified (comment): / 03-08-2011 / 12:57:54 / cg"
!

reportFormatSelector:format
    ^ ('report' , format asString capitalized) asSymbol
! !

!MetricsReporter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/sunit/MetricsReporter.st,v 1.6 2013-04-16 18:09:01 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/MetricsReporter.st,v 1.6 2013-04-16 18:09:01 cg Exp $'
! !