diff --git a/src/Refactoring-Critics/PharoCriticRules.class.st b/src/Refactoring-Critics/PharoCriticRules.class.st index 1ad1497511c..933906d46fd 100644 --- a/src/Refactoring-Critics/PharoCriticRules.class.st +++ b/src/Refactoring-Critics/PharoCriticRules.class.st @@ -11,15 +11,15 @@ Class { PharoCriticRules class >> pharoHardLintRules [ "These rules are used by the CI monkey to check code before its integration into Pharo" ^ { - RBUndeclaredReferenceRule. + ReUndeclaredVariableRule. ReDefinesEqualNotHashRule. ReEquivalentSuperclassMethodsRule. ReJustSendsSuperRule. ReSubclassResponsibilityNotDefinedRule. "RBTempVarOverridesInstVarRule. gotta wait for a fix" - RBVariableNotDefinedRule. + ReUndeclaredVariableRule. ReEqualNotUsedRule. - RBOnlyReadOrWrittenTemporaryRule. + ReTemporaryNeitherReadNorWrittenRule. RePrecedenceRule. SendsDeprecatedMethodToGlobalRule. ReSizeCheckRule. @@ -27,18 +27,10 @@ PharoCriticRules class >> pharoHardLintRules [ ReUnoptimizedToDoRule. ReBetweenAndRule. ReCodeCruftLeftInMethodsRule. - RBPharoBootstrapRule + PharoBootstrapRule } ] -{ #category : #accessing } -PharoCriticRules class >> pharoIntegrationLintRule [ - "A set of rules used by the CI monkey to check code before its integration into Pharo" - ^ (RBCompositeLintRule rules: (self pharoHardLintRules collect: [:each | each new])) - name: 'Pharo integration rules'; - yourself -] - { #category : #'default rules' } PharoCriticRules class >> pharoSoftLintRules [ "skiped for now" diff --git a/src/Refactoring-Critics/RBArchitectureLintRule.class.st b/src/Refactoring-Critics/RBArchitectureLintRule.class.st deleted file mode 100644 index 87e40bc9985..00000000000 --- a/src/Refactoring-Critics/RBArchitectureLintRule.class.st +++ /dev/null @@ -1,35 +0,0 @@ -" -I represent an architectural rule. -I work at the package level and check dependencies among packages. -" -Class { - #name : #RBArchitectureLintRule, - #superclass : #RBBasicLintRule, - #category : #'Refactoring-Critics-ArchitectureRules' -} - -{ #category : #testing } -RBArchitectureLintRule class >> isVisible [ - ^ self name ~= #RBArchitectureLintRule -] - -{ #category : #accessing } -RBArchitectureLintRule class >> uniqueIdentifierName [ - "This number should be unique and should change only when the rule completely change semantics" - ^ 'ArchitectureLintRule' -] - -{ #category : #accessing } -RBArchitectureLintRule >> group [ - ^ 'Architecture' -] - -{ #category : #testing } -RBArchitectureLintRule >> isArchitecturalRule [ - ^ true -] - -{ #category : #accessing } -RBArchitectureLintRule >> resultClass [ - ^ RBPackageEnvironment -] diff --git a/src/Refactoring-Critics/RBOnlyReadOrWrittenTemporaryRule.class.st b/src/Refactoring-Critics/RBOnlyReadOrWrittenTemporaryRule.class.st deleted file mode 100644 index 41bb1a3f46b..00000000000 --- a/src/Refactoring-Critics/RBOnlyReadOrWrittenTemporaryRule.class.st +++ /dev/null @@ -1,28 +0,0 @@ -" -Checks that all temporary variables are both read and written. If an temporary variable is only read, you can replace all of the reads with nil, since it couldn''t have been assigned a value. If the variable is only written, then we don''t need to store the result since we never use it. -" -Class { - #name : #RBOnlyReadOrWrittenTemporaryRule, - #superclass : #RBParseTreeLintRule, - #category : #'Refactoring-Critics-ParseTreeRules' -} - -{ #category : #testing } -RBOnlyReadOrWrittenTemporaryRule class >> isVisible [ - - self flag: 'The functionality was moved to TemporaryNeitherReadNorWrittenRule, but as this rule is used by Monkey, and Monkey is not using Renraku model yet, the rule is hidden'. - ^ false -] - -{ #category : #'as yet unclassified' } -RBOnlyReadOrWrittenTemporaryRule class >> new [ - - ^ ReTemporaryNeitherReadNorWrittenRule asRBRule -] - -{ #category : #accessing } -RBOnlyReadOrWrittenTemporaryRule class >> uniqueIdentifierName [ - "This number should be unique and should change only when the rule completely change semantics" - - ^'OnlyReadOrWrittenTemporaryRule' -] diff --git a/src/Refactoring-Critics/RBOnlyReadOrWrittenVariableRule.class.st b/src/Refactoring-Critics/RBOnlyReadOrWrittenVariableRule.class.st deleted file mode 100644 index d8aaa3ac7aa..00000000000 --- a/src/Refactoring-Critics/RBOnlyReadOrWrittenVariableRule.class.st +++ /dev/null @@ -1,28 +0,0 @@ -" -This smell arises when an instance variable is not both read and written. If an instance variable is only read, the reads can be replaced by nil, since it could not have been assigned a value. If the variable is only written, then it does not need to store the result since it is never used. This check does not work for the data model classes since they use the #instVarAt:put: messages to set instance variables. -" -Class { - #name : #RBOnlyReadOrWrittenVariableRule, - #superclass : #RBBlockLintRule, - #category : #'Refactoring-Critics-BlockRules' -} - -{ #category : #testing } -RBOnlyReadOrWrittenVariableRule class >> isVisible [ - - self flag: 'The functionality was moved to GRIvarNeitherReadNorWrittenRule, but as this rule is used by Monkey, and Monkey is not using Renraku model yet, the rule is hidden'. - ^ false -] - -{ #category : #'instance creation' } -RBOnlyReadOrWrittenVariableRule class >> new [ - - ^ ReIvarNeitherReadNorWrittenRule asRBRule -] - -{ #category : #accessing } -RBOnlyReadOrWrittenVariableRule class >> uniqueIdentifierName [ - "This number should be unique and should change only when the rule completely change semantics" - - ^'OnlyReadOrWrittenVariableRule' -] diff --git a/src/Refactoring-Critics/RBPharoBootstrapRule.class.st b/src/Refactoring-Critics/RBPharoBootstrapRule.class.st deleted file mode 100644 index 7123208456c..00000000000 --- a/src/Refactoring-Critics/RBPharoBootstrapRule.class.st +++ /dev/null @@ -1,26 +0,0 @@ -" -I check that packages constituing the Pharo Bootstrap do not depend on any other package. -" -Class { - #name : #RBPharoBootstrapRule, - #superclass : #RBArchitectureLintRule, - #category : #'Refactoring-Critics-ArchitectureRules' -} - -{ #category : #testing } -RBPharoBootstrapRule class >> isVisible [ - - self flag: 'The functionality was moved to PharoBootstrapRule, but as this rule is used by Monkey, and Monkey is not using Renraku model yet, the rule is hidden'. - ^ false -] - -{ #category : #testing } -RBPharoBootstrapRule class >> new [ - - ^ PharoBootstrapRule asRBRule -] - -{ #category : #accessing } -RBPharoBootstrapRule class >> uniqueIdentifierName [ - ^ 'PharoBootstrapRul' -] diff --git a/src/Refactoring-Critics/RBUndeclaredReferenceRule.class.st b/src/Refactoring-Critics/RBUndeclaredReferenceRule.class.st deleted file mode 100644 index a7e9c0f3c28..00000000000 --- a/src/Refactoring-Critics/RBUndeclaredReferenceRule.class.st +++ /dev/null @@ -1,28 +0,0 @@ -" -Checks for references to variables in the Undeclared dictionary. If you remove a referenced variable from a class, you will create an undeclared variable reference for those methods that accessed the variable. -" -Class { - #name : #RBUndeclaredReferenceRule, - #superclass : #RBBlockLintRule, - #category : #'Refactoring-Critics-BlockRules' -} - -{ #category : #testing } -RBUndeclaredReferenceRule class >> isVisible [ - - self flag: 'The functionality was moved to ReUndeclaredVariableRule, but as this rule is used by Monkey, and Monkey is not using Renraku model yet, the rule is hidden'. - ^ false -] - -{ #category : #'instance creation' } -RBUndeclaredReferenceRule class >> new [ - - ^ ReUndeclaredVariableRule asRBRule -] - -{ #category : #accessing } -RBUndeclaredReferenceRule class >> uniqueIdentifierName [ - "This number should be unique and should change only when the rule completely change semantics" - - ^'UndeclaredReferenceRule' -] diff --git a/src/Refactoring-Critics/RBVariableNotDefinedRule.class.st b/src/Refactoring-Critics/RBVariableNotDefinedRule.class.st deleted file mode 100644 index e2b3edf68ad..00000000000 --- a/src/Refactoring-Critics/RBVariableNotDefinedRule.class.st +++ /dev/null @@ -1,28 +0,0 @@ -" -This check is similar to the ""References an undeclared variable"" check, but it looks for variables that are not defined in the class or in the undeclared dictionary. You probably had to work hard to get your code in this state. -" -Class { - #name : #RBVariableNotDefinedRule, - #superclass : #RBBlockLintRule, - #category : #'Refactoring-Critics-BlockRules' -} - -{ #category : #testing } -RBVariableNotDefinedRule class >> isVisible [ - - self flag: 'The functionality was moved to ReUndeclaredVariableRule, but as this rule is used by Monkey, and Monkey is not using Renraku model yet, the rule is hidden'. - ^ false -] - -{ #category : #'instance creation' } -RBVariableNotDefinedRule class >> new [ - - ^ ReUndeclaredVariableRule asRBRule -] - -{ #category : #accessing } -RBVariableNotDefinedRule class >> uniqueIdentifierName [ - "This number should be unique and should change only when the rule completely change semantics" - - ^'VariableNotDefinedRule' -]