reports/Builder__LintReport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 01 Mar 2013 10:42:50 +0100
changeset 117 d7f87303b984
parent 84 77e12dbe97d3
child 118 7e93ef8c5417
permissions -rw-r--r--
class: Builder::LintReport added: #cmdlineOptionRuleset #setupRulesFrom: changed: #setUp category of:

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

"{ NameSpace: Builder }"

Report subclass:#LintReport
	instanceVariableNames:'environment rules'
	classVariableNames:''
	poolDictionaries:''
	category:'Builder-Reports'
!


!LintReport class methodsFor:'class initialization'!

initialize

    Smalltalk loadPackage: 'stx:goodies/refactoryBrowser/lint'.

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

!LintReport methodsFor:'accessing - defaults'!

defaultFileSuffix

    ^ 'Lint'

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

defaultFormat
    "raise an error: must be redefined in concrete subclass(es)"

    ^ LintReportFormat::PMD new

    "Modified: / 25-11-2011 / 22:06:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

defaultName

    environment isNil ifTrue:[^super defaultName].
    ^environment label

    "Modified: / 25-11-2011 / 22:06:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 13-01-2012 / 12:43:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'command line options'!

cmdlineOptionRuleset

    ^CmdLineOption new
        short: $s;
        long: 'ruleset';
        description: 'Rule set ';
        action:[:option |
            self setupRulesFrom: option.
        ];
        yourself

    "Created: / 28-02-2013 / 23:13:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'generating'!

generateClass: aClass
        | sourceStream sourceName |
        sourceStream := WriteStream on: String new.
        sourceName := self encodeFilename: (self sourceFilenameFor: aClass).

        format writeFile: sourceName with: [
            self generateClass: aClass source: sourceStream.
            self generateClass: aClass class source: sourceStream.
        ].

        format writeSource: sourceStream contents to: sourceName

    "Created: / 06-10-2011 / 23:54:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateClass: aClass selector: aSelector source: sourceStream
        | offset source matching |
        offset := self
                lineAndColumn: sourceStream contents
                at: sourceStream position.
        sourceStream
                nextPutAll: (source := self convert: (aClass sourceCodeAt: aSelector));
                nextPut: Character lf; nextPut: Character lf.
        matching := rules select: [ :each | 
                (self isSelectorEnvironment: each result)
                        and: [ each result includesSelector: aSelector in: aClass ] ].
        self generateViolations: matching class: aClass selector: aSelector source: source offset: offset

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

generateClass: aClass source: sourceStream 

        | offset source matching |
        offset := self
                lineAndColumn: sourceStream contents
                at: sourceStream position.
        sourceStream
                nextPutAll: (source := self convert: aClass definition);
                nextPut: Character lf; nextPut: Character lf.
        (environment definesClass: aClass) ifTrue: [
                matching := rules select: [ :rule |
                        (self isClassEnvironment: rule result)
                                and: [ rule result includesClass: aClass ] ].
                self generateViolations: matching class: aClass selector: nil  source: source offset: offset ].
        (environment selectorsForClass: aClass) asSortedCollection
                do: [ :selector | self generateClass: aClass selector: selector source: sourceStream]

    "Created: / 07-10-2011 / 10:29:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateViolations: aCollection class: aClass selector: aSelector source: aString offset: aPoint

    aCollection do: [ :rule |
        | interval start stop |
    
        interval := (rule result selectionIntervalFor: aString) ifNil: [ 1 to: aString size ].
        start := self lineAndColumn: aString at: interval first.
        stop  := self lineAndColumn: aString at: interval last.

        format writeViolation: rule
                   class: aClass selector: aSelector
               startLine: aPoint x + start x column: aPoint y + start y - 1
                stopLine: aPoint x + stop x  column: aPoint y + stop  y - 1.
    ]

    "Created: / 25-11-2011 / 22:23:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'initialization'!

setupForClasses: classes

    environment := BrowserEnvironment new forClasses: classes.
    environment label: name

    "Created: / 04-08-2011 / 14:40:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setupForPackages: packages

    packages isEmpty ifTrue:[^self].
    environment := PackageEnvironment 
                    onEnvironment: BrowserEnvironment new
                    packageNames: packages.
    name isNil ifTrue:[
        packages size > 1 ifTrue:[
            name :=  packages size printString , ' packages'.
        ] ifFalse:[
            name :=  packages anElement
        ]
    ].

    environment label: name.

    "
        LintReport runPackage:'stx:goodies/monticello'.
        LintReport runPackage:'stx:libjava'
    "

    "Created: / 04-08-2011 / 14:40:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'private'!

lineAndColumn: aString at: anInteger
	| line last stream |
	line := 1.
	last := 0.
	stream := aString readStream.
	[ (stream nextLine isNil or: [ anInteger <= stream position ])
		ifTrue: [ ^ line @ (anInteger - last) ].
	last := stream position.
	line := line + 1 ]
		repeat
!

sourceFilenameFor: aClass

    | fn |

    fn := aClass package asString replaceAll:$: with:$_;replaceAll:$/ with:$_.
    fn := fn , '_' , (aClass asString copyReplaceAll:$: with: $_), '.' , aClass programmingLanguage sourceFileSuffix.
    
    ^self encodeFilename: fn.

    "
        Builder::LintReportFormat::CheckStyle basicNew
            sourceFilenameFor: Class

        Builder::LintReportFormat::CheckStyle basicNew
            sourceFilenameFor: Builder::LintReportFormat
    "

    "Created: / 07-10-2011 / 09:06:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'running'!

runReport
    | wasTryLocalSources |

    [
        wasTryLocalSources := Class tryLocalSourceFirst.
        Class tryLocalSourceFirst: true.
        SmalllintChecker 
            runRule: (RBCompositeLintRule rules: rules)
            onEnvironment: environment.

        (environment classes asSortedCollection: [ :a :b | a name <= b name ])
            do: [ :class | self generateClass: class].
    ] ensure:[
        Class tryLocalSourceFirst: wasTryLocalSources 
    ]

    "Modified: / 23-01-2012 / 09:04:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setUp

    super setUp.
    rules isNil ifTrue:[
        rules := (RBCompositeLintRule rulesFor: RBBasicLintRule)
                 reject: [ :each | each class name endsWith: 'SpellingRule' ]
    ].

    "Created: / 04-08-2011 / 14:35:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-02-2013 / 23:18:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setupRulesFrom: filename
    | file |    
    file := filename asFilename.
    file readingFileDo:[:s|
        | spec |
        spec := Parser parseLiteralArray: s.
        rules := spec decodeAsLiteralArray rules.
    ]

    "Created: / 28-02-2013 / 23:17:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport methodsFor:'testing'!

isClassEnvironment: anEnvironment
	^ #(CategoryEnvironment ClassEnvironment VariableEnvironment) includes: anEnvironment class name
!

isSelectorEnvironment: anEnvironment
	^ #(SelectorEnvironment ParseTreeEnvironment VariableEnvironment) includes: anEnvironment class name
! !

!LintReport class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '§Id: Builder__LintReport.st 293 2011-11-25 21:42:31Z vranyj1 §'
! !


LintReport initialize!