reports/Builder__LintReport.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 03 Mar 2013 12:50:54 +0100
changeset 119 318a202597cc
parent 118 7e93ef8c5417
child 141 9265bed28ff5
permissions -rw-r--r--
class: Builder::LintReport

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

"{ NameSpace: Builder }"

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

Object subclass:#SourceInfo
	instanceVariableNames:'klass filename offsets lineEnds'
	classVariableNames:''
	poolDictionaries:''
	privateIn:LintReport
!

Stream subclass:#LineCountingStream
	instanceVariableNames:'position lineEnds'
	classVariableNames:''
	poolDictionaries:''
	privateIn:LintReport::SourceInfo
!


!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
        | sourceInfo sourceName |
        sourceInfo := SourceInfo for: aClass.
        sourceName := self encodeFilename: (self sourceFilenameFor: aClass).

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

        format writeSource: sourceInfo contents to: sourceName

    "Created: / 06-10-2011 / 23:54:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-03-2013 / 17:59:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateClass: aClass selector: aSelector source: sourceInfo
        | matching |
        matching := rules select: [ :each | 
                (self isSelectorEnvironment: each result)
                        and: [ each result includesSelector: aSelector in: aClass ] ].
        self generateViolations: matching class: aClass selector: aSelector source: sourceInfo

    "Created: / 07-10-2011 / 11:04:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-03-2013 / 18:10:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateClass: aClass source: sourceInfo 

        | matching |
        (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: sourceInfo].
        (environment selectorsForClass: aClass) asSortedCollection
                do: [ :selector | self generateClass: aClass selector: selector source: sourceInfo]

    "Created: / 07-10-2011 / 10:29:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-03-2013 / 18:11:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateViolations: aCollection class: aClass selector: aSelector source: sourceInfo
    | method offset  |

    method := aClass compiledMethodAt: aSelector.
    offset := sourceInfo offsetOfMethod: method.
    aCollection do: [ :rule |
        | interval start stop |
    
        interval := (rule result selectionIntervalFor: method source) isNil ifTrue: [ 1 to: method source size ].
        start := sourceInfo lineAndColumnOfOffset: offset + interval first - 1.
        stop  := sourceInfo lineAndColumnOfOffset: offset + interval last - 1.

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

    "Created: / 01-03-2013 / 18:05:11 / 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 cls |

    cls := aClass theNonMetaclass.
    fn := cls package asString replaceAll:$: with:$_;replaceAll:$/ with:$_.
    fn := fn , '_' , (cls asString copyReplaceAll:$: with: $_), '.' , cls 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>"
    "Modified: / 01-03-2013 / 18:00:26 / 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::SourceInfo class methodsFor:'instance creation'!

for: aClass
    ^self new setClass: aClass

    "Created: / 01-03-2013 / 17:50:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo methodsFor:'initialization'!

setClass: aClass
    klass := aClass theNonMetaclass.
    self setup.

    "Created: / 01-03-2013 / 17:49:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setup
    "To be called after class is set"

    | stream |

    stream := LineCountingStream new.
    offsets := Dictionary new.

    [
        self fileOutOn: stream.
    ] on: AbstractSourceFileWriter methodSourceRewriteQuery do:[:rewriteQuery |
        | m |

        m := rewriteQuery method.
        offsets at: m put: stream position + 1.
        rewriteQuery proceed.
    ].
    lineEnds := stream lineEnds

    "
        SourceInfo for: Builder::ReportRunner
    "

    "Created: / 01-03-2013 / 17:30:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-03-2013 / 11:09:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo methodsFor:'queries'!

lineAndColumnOfOffset: offset
    | low high middle element line col |

    low := 1.
    high := lineEnds size.
    [low > high] whileFalse:[
        middle := (low + high) // 2.
        element := lineEnds at:middle.
        element < offset ifTrue:[
            "middleelement is smaller than object"
            low := middle + 1
        ] ifFalse:[
            high := middle - 1
        ]
    ].

    line := low.
    col := offset - (line > 1 ifTrue:[lineEnds at: line - 1] ifFalse:[0]).
    ^line @ col.

    "Created: / 03-03-2013 / 10:50:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

offsetOfMethod: aMethod
    ^offsets at: aMethod

    "Created: / 03-03-2013 / 10:49:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo methodsFor:'utilities'!

fileOutOn:aStream
    klass fileOutOn: aStream withTimeStamp:false

    "Created: / 01-03-2013 / 17:51:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo::LineCountingStream class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'accessing'!

contents
    "return the entire contents of the stream.
     For a readStream, that is the rest (i.e. upToEnd),
     for a writeStream, that is the collected data. As we do not know here,
     what we are, this is the responsibility of a subclass..."

    ^ self shouldNotImplement

    "Modified: / 01-03-2013 / 17:36:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lineEnds
    ^ lineEnds
!

position
    ^ position
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    position := 0.
    lineEnds := OrderedCollection new.

    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 01-03-2013 / 17:39:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'queries'!

isReadable
    "return true, if reading is supported by the recevier.
     This has to be redefined in concrete subclasses."

    ^ false

    "Modified: / 01-03-2013 / 17:36:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isWritable
    "return true, if writing is supported by the recevier.
     This has to be redefined in concrete subclasses."

    ^ true

    "Modified: / 01-03-2013 / 17:37:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

size
    "return the number of elements in the streamed collection."

    ^ self shouldImplement
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'reading'!

next
    "return the next element of the stream
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self shouldNotImplement

    "Modified: / 01-03-2013 / 17:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'testing'!

atEnd
    "return true if the end of the stream has been reached;
     - we do not know here how to do it, it must be redefined in subclass"

    ^ false

    "Modified: / 01-03-2013 / 17:37:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isEmpty
    "return true, if the contents of the stream is empty"

    ^ self shouldNotImplement

    "Modified: / 01-03-2013 / 17:37:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LintReport::SourceInfo::LineCountingStream methodsFor:'writing'!

nextPut:aCharacter
    "put the argument, anObject onto the receiver
     - we do not know here how to do it, it must be redefined in subclass"

     position := position + 1.
    aCharacter == Character cr ifTrue:[
        lineEnds add: position
    ].

    "Modified: / 01-03-2013 / 17:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!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!