codechecker/SmalllintReportGenerator.st
author Claus Gittinger <cg@exept.de>
Sun, 07 Aug 2011 11:30:17 +0200
changeset 36 2c0987f7230d
child 37 0a356190f3f3
permissions -rw-r--r--
initial checkin

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

Object subclass:#SmalllintReportGenerator
	instanceVariableNames:'rules environment'
	classVariableNames:''
	poolDictionaries:''
	category:'Refactory-Lint'
!

!SmalllintReportGenerator class methodsFor:'documentation'!

documentation
"
    a standalone smallint runner.
    Generates an xml report compatible to pmd, to be processed by hudson.

    [author:]
        Claus Gittinger
"
!

examples
"
    |checker|

    checker := self new.
    checker addPackage:'exept:workflow'.
    checker performChecks.
    checker generateReportAs:'checkstyle.xml'
"
! !

!SmalllintReportGenerator class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!SmalllintReportGenerator methodsFor:'checking'!

performChecks
    rules withIndexDo:[:rule :index|
       Stdout showCR:('Checking: ', rule name).
       (SmalllintChecker runRule: rule onEnvironment: environment)
    ].

    "Created: / 07-08-2011 / 01:10:00 / cg"
! !

!SmalllintReportGenerator methodsFor:'initialization'!

initialize
    self setupRules.
    self setupEnvironment

    "Modified: / 07-08-2011 / 01:14:51 / cg"
! !

!SmalllintReportGenerator methodsFor:'reporting'!

generateReportAs:aFilename
    aFilename asFilename writingFileDo:[:s | self generateReportOn:s].

    "Created: / 07-08-2011 / 01:17:46 / cg"
!

generateReportOn:aStream
    aStream nextPutLine: '<?xml version="1.0"?>'.
    aStream nextPutLine: '<pmd>'.
    rules do:[:eachRule | 
        eachRule problemCount > 0 ifTrue:[
            eachRule failedMethods do:[:method |
                |class classFileName s selector fullSource 
                 charPos lineNumber ruleName rationale|

                class := method mclass.
                s := class localSourceStreamFor:class theNonMetaclass classFilename.
                s notNil ifTrue:[
                    classFileName := s pathName.
                    s close.
                ] ifFalse:[
                    classFileName := class sourceFilename.
                ].
                fullSource := class source.
                charPos := method sourcePosition ? 1.
                "/ q&d hack - editor knows
                lineNumber := (TextView new contents:fullSource)
                                lineOfCharacterPosition:charPos.
                ruleName := eachRule name.
                rationale := eachRule rationale.

    aStream nextPutLine:('  <file name="%1">' bindWith:classFileName).
    aStream nextPutLine:('    <violation line="%1" rule="%2">' bindWith:lineNumber with:ruleName).
    aStream nextPutLine:('%1' bindWith:rationale).
    aStream nextPutLine: '    </violation>'.
    aStream nextPutLine: '  </file>'.

            ].
        ]
    ].
    aStream nextPutLine: '</pmd>'.

    "Created: / 07-08-2011 / 01:17:00 / cg"
! !

!SmalllintReportGenerator methodsFor:'setup'!

addClass:aClass
    environment addClass: aClass.

    "Created: / 07-08-2011 / 01:11:33 / cg"
!

addPackage:aPackage
    Smalltalk loadPackage:aPackage.
    Smalltalk allClassesInPackage:aPackage do:[:cls | self addClass:cls]

    "Created: / 07-08-2011 / 01:12:31 / cg"
!

setupEnvironment
    environment := ClassEnvironment new.

    "Created: / 07-08-2011 / 01:10:56 / cg"
!

setupRules
    | allRule checks|

    allRule := RBCompositeLintRule allRules.
    checks := allRule rules detect:[ :each | each name = 'Lint checks' ].
    checks rules: (checks rules reject: [ :each | each name = 'Squeak bugs' ]).

    rules := allRule flattened.

    "Created: / 07-08-2011 / 01:08:56 / cg"
! !

!SmalllintReportGenerator class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !