Skip to content

Commit

Permalink
Merge pull request #11878 from Ducasse/11877-Cleaning-Replace-Calls-T…
Browse files Browse the repository at this point in the history
…ransformation

fix #11877
  • Loading branch information
Ducasse committed Nov 10, 2022
2 parents 0893b39 + c8529cc commit 068c54b
Show file tree
Hide file tree
Showing 6 changed files with 181 additions and 61 deletions.
11 changes: 11 additions & 0 deletions src/Calypso-SystemTools-Core/SycReplaceMessageCommand.extension.st
@@ -1,5 +1,16 @@
Extension { #name : #SycReplaceMessageCommand }

{ #category : #'*Calypso-SystemTools-Core' }
SycReplaceMessageCommand class >> canBeExecutedInContext: aToolContext [

self flag: #Enh.
"The following commented piece controls the fact that the replace can be invoked from without the code pane.
Now the asRefactoring method should have access to the class from such context and we did not find how.
For now we removed the menu item from the list. Less working is better than more not working"
^ "aToolContext isMessageSelected |"
aToolContext isMethodSelected
]

{ #category : #'*Calypso-SystemTools-Core' }
SycReplaceMessageCommand class >> methodContextMenuActivation [
<classAnnotation>
Expand Down
26 changes: 21 additions & 5 deletions src/Refactoring-Core/RBConjunctiveCondition.class.st
Expand Up @@ -3,7 +3,23 @@ I am a refactoring condition combining two other conditions by a boolean AND.
I am created by sending the binary message #& to another condition (left) with another condition (right) as its argument.
Checking this conditions holds true, if my left and my right condition is true.
Checking this condition holds true, if my left and my right condition is true.
Note that the first failing condition stops the condition evaluation. See testCheckFailEarlyAndDoesNotCoverEveryConditions
### Implementation
The following method is key as it shows that as soon as a check fails the second one is not checked.
```
check
left check ifFalse: [
failed := #leftFailed.
^ false ].
right check ifFalse: [
failed := #rightFailed.
^ false ].
^ true
```
"
Class {
#name : #RBConjunctiveCondition,
Expand Down Expand Up @@ -44,10 +60,10 @@ RBConjunctiveCondition >> errorMacro [
]

{ #category : #private }
RBConjunctiveCondition >> errorStringFor: aBoolean [
^aBoolean
ifTrue: [self neitherFailed]
ifFalse: [self perform: failed]
RBConjunctiveCondition >> errorStringFor: aBoolean [
^ aBoolean
ifTrue: [ self neitherFailed ]
ifFalse: [ self perform: failed ]
]

{ #category : #initialization }
Expand Down
@@ -1,15 +1,16 @@
"
I'm a refactoring operation for replace one method call by another one.
I'm a transformation replaces one message send by another one.
As such I cannot garantee anything about behavior preservation.
The new method's name can have a different number of arguments than the original method, if it has more arguments a list of initializers will be needed for them.
The new method's name can have a different number of arguments than the original method,
if it has more arguments a list of initializers will be needed for them.
All senders of this method are changed by the other.
Example
-------
Script:
### Example
```
(RBReplaceMethodRefactoring
(RBReplaceMessageSendTransformation
model: model
replaceMethod: #anInstVar:
in: RBBasicLintRuleTestData
Expand All @@ -19,7 +20,7 @@ Script:
```
"
Class {
#name : #RBReplaceMethodRefactoring,
#name : #RBReplaceMessageSendTransformation,
#superclass : #RBChangeMethodNameRefactoring,
#instVars : [
'replaceInAllClasses',
Expand All @@ -28,8 +29,14 @@ Class {
#category : #'Refactoring-Core-Refactorings'
}

{ #category : #accessing }
RBReplaceMessageSendTransformation class >> kind [

^ 'Transformation'
]

{ #category : #'instance creation' }
RBReplaceMethodRefactoring class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap [
RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap [
^ self new
model: aRBSmalltalk;
replaceCallMethod: aSelector
Expand All @@ -40,7 +47,7 @@ RBReplaceMethodRefactoring class >> model: aRBSmalltalk replaceMethod: aSelector
]

{ #category : #'instance creation' }
RBReplaceMethodRefactoring class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [
RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [
^ self new
model: aRBSmalltalk;
replaceCallMethod: aSelector
Expand All @@ -52,7 +59,7 @@ RBReplaceMethodRefactoring class >> model: aRBSmalltalk replaceMethod: aSelector
]

{ #category : #'instance creation' }
RBReplaceMethodRefactoring class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap [
RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap [
^self new
replaceCallMethod: aSelector
in: aClass
Expand All @@ -61,7 +68,7 @@ RBReplaceMethodRefactoring class >> replaceCallMethod: aSelector in: aClass to:
]

{ #category : #'instance creation' }
RBReplaceMethodRefactoring class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [
RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [
^self new
replaceCallMethod: aSelector
in: aClass
Expand All @@ -71,19 +78,20 @@ RBReplaceMethodRefactoring class >> replaceCallMethod: aSelector in: aClass to:
]

{ #category : #accessing }
RBReplaceMethodRefactoring >> initializers [
RBReplaceMessageSendTransformation >> initializers [

^ initializers ifNil: [ initializers := { } ]
]

{ #category : #accessing }
RBReplaceMethodRefactoring >> initializers: anObject [
RBReplaceMessageSendTransformation >> initializers: anObject [

initializers := anObject
]

{ #category : #private }
RBReplaceMethodRefactoring >> newSelectorString [
RBReplaceMessageSendTransformation >> newSelectorString [

| stream keywords |
stream := WriteStream on: String new.
permutation ifEmpty: [ stream nextPutAll: newSelector ].
Expand All @@ -107,62 +115,59 @@ RBReplaceMethodRefactoring >> newSelectorString [
]

{ #category : #transforming }
RBReplaceMethodRefactoring >> parseTreeRewriter [
RBReplaceMessageSendTransformation >> parseTreeRewriter [

| rewriteRule oldString newString |
rewriteRule := self parseTreeRewriterClass new.
oldString := self buildSelectorString: oldSelector.
newString := self newSelectorString.
rewriteRule replace: '``@object ' , oldString
rewriteRule
replace: '``@object ' , oldString
with: '``@object ' , newString.
^rewriteRule
^ rewriteRule
]

{ #category : #preconditions }
RBReplaceMethodRefactoring >> preconditions [
|conditions|

conditions := (RBCondition withBlock: [ oldSelector numArgs < newSelector numArgs ifTrue: [
(oldSelector numArgs + self initializers size) = newSelector numArgs
ifFalse: [ self refactoringFailure: 'You don''t have the necessary initializers to replace senders.' ] ]. true ])
&(RBCondition definesSelector: oldSelector in: class )
& (RBCondition definesSelector: newSelector in: class ).

^ conditions & (RBCondition withBlock:
[ |senders|
senders := self replaceInAllClasses
ifTrue: [ self model allReferencesTo: oldSelector ]
ifFalse: [ self model allReferencesTo: oldSelector in: {class} ].
senders size > 1
ifTrue:
[self refactoringWarning: ('This will modify all <1p> senders.<n>Proceed anyway?'
expandMacrosWith: senders size)].
true])
RBReplaceMessageSendTransformation >> preconditions [

| conditions |
conditions := (RBCondition withBlock: [
oldSelector numArgs < newSelector numArgs ifTrue: [
oldSelector numArgs + self initializers size
= newSelector numArgs ifFalse: [
self refactoringFailure:
'You don''t have the necessary initializers to replace senders.' ] ].
true ])
& (RBCondition definesSelector: oldSelector in: class)
& (RBCondition definesSelector: newSelector in: class).
"This is unclear that the targeting method should already be defined."

^ conditions
]

{ #category : #initialization }
RBReplaceMethodRefactoring >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap [
RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap [

oldSelector := aSelector asSymbol.
newSelector := newSel asSymbol.
class := self classObjectFor: aClass.
permutation := aMap.
]

{ #category : #initialization }
RBReplaceMethodRefactoring >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap inAllClasses: aBoolean [
oldSelector := aSelector asSymbol.
newSelector := newSel asSymbol.
class := self classObjectFor: aClass.
permutation := aMap.
RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap inAllClasses: aBoolean [

self replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap.
replaceInAllClasses := aBoolean.
]

{ #category : #accessing }
RBReplaceMethodRefactoring >> replaceInAllClasses [
RBReplaceMessageSendTransformation >> replaceInAllClasses [
^ replaceInAllClasses ifNil: [ replaceInAllClasses := false ]
]

{ #category : #transforming }
RBReplaceMethodRefactoring >> transform [
RBReplaceMessageSendTransformation >> transform [
self replaceInAllClasses
ifTrue: [ self renameMessageSends ]
ifFalse: [ self renameMessageSendsIn: {class} ]
Expand Down
63 changes: 63 additions & 0 deletions src/Refactoring-Tests-Core/RBConditionTest.class.st
Expand Up @@ -4,6 +4,23 @@ Class {
#category : #'Refactoring-Tests-Core-Base'
}

{ #category : #tests }
RBConditionTest >> testCheckFailEarlyAndDoesNotCoverEveryConditions [

| falseCase trueCase composition |
falseCase := RBCondition
withBlock: [ false ]
errorString: 'The false case'.
trueCase := RBCondition
withBlock: [ false ]
errorString: 'The second false case'.
composition := falseCase & trueCase.
self deny: composition check.
self
assert: composition errorString
equals: 'The false case'
]

{ #category : #tests }
RBConditionTest >> testCheckInvalidMethodName [
"Usually used to validate input."
Expand All @@ -23,6 +40,52 @@ RBConditionTest >> testCheckInvalidMethodName [
self deny: (RBCondition checkMethodName: 'foo:agr')
]

{ #category : #tests }
RBConditionTest >> testCheckThatAndIsWorking [

| falseCase trueCase composition |
falseCase := RBCondition
withBlock: [ false ]
errorString: 'The false case'.
trueCase := RBCondition
withBlock: [ true ]
errorString: 'The true case'.
composition := falseCase & trueCase.
self deny: composition check
]

{ #category : #tests }
RBConditionTest >> testCheckThatOnlyFailingConditionErrorIsReported [

| falseCase trueCase composition |
falseCase := RBCondition
withBlock: [ false ]
errorString: 'The false case'.
trueCase := RBCondition
withBlock: [ true ]
errorString: 'The true case'.
composition := falseCase & trueCase.
self deny: composition check.
self assert: composition errorString equals: 'The false case'.
]

{ #category : #tests }
RBConditionTest >> testCheckThatOnlyFailingConditionErrorIsReportedTrueCaseFirst [

| falseCase trueCase composition |
trueCase := RBCondition
withBlock: [ true ]
errorString: 'The true case'.
falseCase := RBCondition
withBlock: [ false ]
errorString: 'The false case'.
composition := trueCase & falseCase.
self deny: composition check.
self
assert: composition errorString
equals: 'The false case'
]

{ #category : #tests }
RBConditionTest >> testCheckValidMethodName [
"Usually used to validate input."
Expand Down
Expand Up @@ -7,7 +7,7 @@ Class {
{ #category : #tests }
RBReplaceSendersMethodParametrizedTest class >> testParameters [
^ ParametrizedTestMatrix new
addCase: { #rbClass -> RBReplaceMethodRefactoring };
addCase: { #rbClass -> RBReplaceMessageSendTransformation };
yourself
]

Expand Down

0 comments on commit 068c54b

Please sign in to comment.