MetricsReporter.st
author Claus Gittinger <cg@exept.de>
Wed, 07 Nov 2012 22:04:55 +0100
changeset 521 e7687d9473d7
parent 520 211f1ded0586
child 522 3582d5e59c14
permissions -rw-r--r--
class: MetricsReporter added: #classMetricNames: #methodMetricNames: #packageMetricNames:

"
 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]
    '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]
"
!

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:aPackageID
    |metric|

    metric := OOM::PackageMetrics type:metricName for:aPackageID.
    ^ self metricInfoFor:metric
! !

!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:aPackage
    ^ self packageMetricNames collect:[:metricName |
        self packageMetricValue:metricName for:aPackage.
    ].
!

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
    "

    Smalltalk loadPackage:'exept:programming/oom'.

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

    packages do:[:eachPackageID |
        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:aPackageID
    stream nextPutLine: '  <project>'.
    stream nextPutLine: ('    <name>%1</name>' bindWith:aPackageID).

    (self classMetricNames notEmptyOrNil 
    or:[self methodMetricNames notEmptyOrNil]) ifTrue:[
        Smalltalk allClassesInPackage:aPackageID do:[:eachClass |
            Autoload autoloadFailedSignal handle:[:ex |
            ] do:[
                eachClass autoload.
                self reportXml_metricsForClass:eachClass
            ].
        ].
    ].

    self reportXml_metricValues:(self generatePackageMetricsFor:aPackageID).

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

!MetricsReporter methodsFor:'reporting-private'!

report:formatSymbol
    "currently supported formatSymbols:
            xml_cobertura"

    |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.4 2012-11-07 21:04:55 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/sunit/MetricsReporter.st,v 1.4 2012-11-07 21:04:55 cg Exp $'
! !