SmallSense__SmalltalkChecker.st
author Claus Gittinger <cg@exept.de>
Tue, 10 Dec 2019 14:59:54 +0100
branchcvs_MAIN
changeset 1115 2182c6e411dc
parent 1012 ec316e0316af
permissions -rw-r--r--
#BUGFIX by cg class: SmallSense::CompletionView changed: #keyPress:x:y:

"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
"{ Package: 'stx:goodies/smallsense' }"

"{ NameSpace: SmallSense }"

SmalllintChecker subclass:#SmalltalkChecker
	instanceVariableNames:''
	classVariableNames:'Errors UserDisabledRules'
	poolDictionaries:''
	category:'SmallSense-Smalltalk-Lint'
!

!SmalltalkChecker class methodsFor:'documentation'!

copyright
"
stx:goodies/smallsense - A productivity plugin for Smalltalk/X IDE
Copyright (C) 2013-2014 Jan Vrany

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
!

documentation
"
    SmallSenseChecker is customized SmalllintChecker used
    by SmallSense's checking services. Do not use it in your
    code, use SmalllintChecker instead.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]
        SmalllintChecker
        SmallSenseService

"
! !

!SmalltalkChecker class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    Errors := Dictionary new.

    "Modified: / 06-09-2012 / 14:18:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkChecker class methodsFor:'accessing'!

disableRule:aRuleClass
    "add a rule to the user-disabled rule set;
     These will also be skipped."

    UserDisabledRules isNil ifTrue:[
        UserDisabledRules := Set new.
    ].
    UserDisabledRules add:aRuleClass.
!

forceDisabledRules
    "Return a list of rule class names that
     are never run by SmallSense's checker - they
     are either buggy (i.e.. not ready to be run
     incrementally) or it does not make sense to run them
     Add with care!!!!!!
    "

    ^ #(
        RBLawOfDemeterRule          "/ Too many false positives, hard to fix
        RBImplementedNotSentRule    "/ Uses Context>>#computeLiterals whichs toooo slow.
        RBSentNotImplementedRule    "/ Uses Context>>#computeLiterals whichs toooo slow.
        RBUndeclaredReferenceRule   "/

        RBNilOrEmptyCollectionReplaceRule   "/ only for Squeak - I don't want people to rewrite ST/X code
        RBSTXSpecialCommentsRule            "/ a rewriter to be used only for porting
    )

    "Created: / 17-02-2012 / 13:10:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-09-2014 / 11:59:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isRuleDisabled:aRuleClass
    ^ UserDisabledRules notNil and:[ UserDisabledRules includes: aRuleClass ]
!

reEnableAllDisabledRules
    UserDisabledRules := nil
!

userDisabledRules
    "return the list of rules which the user disabled explicitly"

    ^ UserDisabledRules
! !

!SmalltalkChecker methodsFor:'private'!

checkClass: aClass 

    "Nothing to do, SmallSense checker checks only methods"
    context selectedClass: aClass.

    "Created: / 16-02-2012 / 16:12:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

checkMethodsForClass: aClass

    environment selectorsForClass: aClass do: [:sel|
        context selector: sel.
        context parseTree notNil ifTrue:[
            rule flattened do:[:eachRule|
                |ruleClass|

                ruleClass := eachRule class. 
                (SmalltalkChecker isRuleDisabled:ruleClass) ifTrue:[
                    Transcript show:'rule '; show:ruleClass name; showCR:' disabled'.
                ] ifFalse:[
                    [
                        (eachRule shouldIgnoreMethod:context) ifFalse:[
                            eachRule checkMethod: context.
                        ].    
                    ] on: Error do:[:ex|
                        SmalltalkLintService debugging ifTrue:[
                            SmalltalkLintService debugging: false.
                            ex pass.
                        ] ifFalse:[
                            Errors 
                                at: ruleClass 
                                ifAbsentPut:[  
                                    (context selectedClass compiledMethodAt: context selector) source 
                                ].
                        ]
                    ]
                ].
            ].
        ].
    ]

    "Modified: / 24-08-2010 / 21:32:39 / Jan Vrany"
    "Created: / 17-02-2012 / 00:50:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 16-10-2014 / 01:08:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SmalltalkChecker class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '$Id$'
! !


SmalltalkChecker initialize!