Skip to content

Commit

Permalink
add ReStatementsAfterReturnConditionalRule
Browse files Browse the repository at this point in the history
this PR is a proposition for a new rule for "Method returning in conditional but still having statements". #6326
  • Loading branch information
Hely authored and AngelHely committed May 13, 2024
1 parent 54f2c69 commit f3cd169
Show file tree
Hide file tree
Showing 2 changed files with 78 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
Class {
#name : 'ReStatementsAfterReturnConditionalRuleTest',
#superclass : 'ReAbstractRuleTestCase',
#category : 'General-Rules-Tests-Migrated',
#package : 'General-Rules-Tests',
#tag : 'Migrated'
}

{ #category : 'tests' }
ReStatementsAfterReturnConditionalRuleTest >> testRule [

| critiques |
self class
compile: 'method 1 = 1 ifTrue: [ ^ 1 ] ifFalse: [ ^ 2 ]. 2'
classified: 'test-helper'.
[
critiques := self myCritiquesOnMethod: self class >> #method.
self assert: critiques size equals: 1 ] ensure: [
(self class >> #method) removeFromSystem ]
]

{ #category : 'tests' }
ReStatementsAfterReturnConditionalRuleTest >> testRuleNotViolated [

| critiques |
self class
compile: 'method 1 = 1 ifTrue: [ ^ 1 ] ifFalse: [ ^ 2 ].'
classified: 'test-helper'.
[
critiques := self myCritiquesOnMethod: self class >> #method.
self assertEmpty: critiques ] ensure: [
(self class >> #method) removeFromSystem ]
]
45 changes: 45 additions & 0 deletions src/General-Rules/ReStatementsAfterReturnConditionalRule.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
"
This smell arise when statements are written after a condition that return within 2 branch.
For exemple :
method
1 = 1
fTrue: [ ^ 1 ] ifFalse: [ ^ 2 ].
2
"
Class {
#name : 'ReStatementsAfterReturnConditionalRule',
#superclass : 'ReNodeBasedRule',
#category : 'General-Rules-Migrated',
#package : 'General-Rules',
#tag : 'Migrated'
}

{ #category : 'running' }
ReStatementsAfterReturnConditionalRule >> basicCheck: aNode [

aNode isMessage ifFalse: [ ^ false ].
(self selectorList includes: aNode selector) ifFalse: [ ^ false ].
aNode arguments do: [ :arg |
(arg isBlock and: [ arg statements last isReturn ]) ifFalse: [ ^ false ] ].
^ aNode ~= aNode methodNode statements last
]

{ #category : 'accessing' }
ReStatementsAfterReturnConditionalRule >> group [

^ 'Potential Bugs'
]

{ #category : 'accessing' }
ReStatementsAfterReturnConditionalRule >> name [

^ 'statements written after conditional return'
]

{ #category : 'utilities' }
ReStatementsAfterReturnConditionalRule >> selectorList [

^ #(#ifTrue:ifFalse: #ifFalse:ifTrue: #ifNil:ifNotNil: #ifNotNil:ifNil: #ifEmpty:ifNotEmpty: #ifNotEmpty:ifEmpty: #ifExists:ifAbsent:)
]

0 comments on commit f3cd169

Please sign in to comment.