Skip to content

Commit dd3a2b2

Browse files
authored
Merge pull request #18965 from AlexisCnockaert/Refactoring/newdriver
[Refactoring] Driver improvement for temp to instance variable
2 parents 15add4d + bd969c3 commit dd3a2b2

11 files changed

+335
-73
lines changed

src/Refactoring-Core/RBCondition.class.st

Lines changed: 0 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -56,25 +56,6 @@ RBCondition class >> checkInstanceVariableName: aName in: aClass [
5656
^ OCScanner isVariable: string
5757
]
5858

59-
{ #category : 'instance creation' }
60-
RBCondition class >> checkNotMultipleTemporaryDefinitionsOf: aString in: aClass [
61-
62-
| condition |
63-
condition := self new.
64-
condition
65-
block: [
66-
| methods |
67-
methods := self multipleMethodsDefiningTemporary: aString in: aClass ignore: [ :class :selector | false ].
68-
methods size > 1
69-
ifTrue: [
70-
condition errorMacro:
71-
'More than one method defines temporary variable ' , aString , ': ' , (methods collect: [ :m | m selector ]) asString.
72-
false ]
73-
ifFalse: [ true ] ]
74-
errorString: aClass printString , ' <1?:does not >define<1?s:> temporary variable ' , aString.
75-
^ condition
76-
]
77-
7859
{ #category : 'instance creation' }
7960
RBCondition class >> definesClassVariable: aString in: aClass [
8061
^self new
@@ -374,25 +355,6 @@ RBCondition class >> methodDefiningTemporary: aString in: aClass ignore: aBlock
374355
^ nil
375356
]
376357

377-
{ #category : 'utilities' }
378-
RBCondition class >> multipleMethodsDefiningTemporary: aString in: aClass ignore: aBlock [
379-
380-
| searcher methods method |
381-
searcher := OCParseTreeSearcher new.
382-
methods := Set new.
383-
method := nil.
384-
385-
searcher matches: aString do: [ :aNode :answer | methods add: method ].
386-
aClass withAllSubclasses do: [ :class |
387-
class selectors do: [ :each |
388-
(aBlock value: class value: each) ifFalse: [
389-
| parseTree |
390-
method := class methodFor: each.
391-
parseTree := class parseTreeForSelector: each.
392-
parseTree ifNotNil: [ searcher executeTree: parseTree ] ] ] ].
393-
^ methods
394-
]
395-
396358
{ #category : 'instance creation' }
397359
RBCondition class >> referencesClassVariable: aString in: aClass [
398360

src/Refactoring-Core/RBTemporaryToInstanceVariableRefactoring.class.st

Lines changed: 30 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -114,17 +114,9 @@ RBTemporaryToInstanceVariableRefactoring >> applicabilityPreconditions [
114114
RBTemporaryToInstanceVariableRefactoring >> breakingChangePreconditions [
115115

116116
^ {
117-
(RBCondition withBlock: [
118-
(class allSubclasses anySatisfy: [ :cls | cls definesInstanceVariable: temporaryVariableName asString ]) ifTrue: [
119-
self refactoringWarning:
120-
('One or more subclasses of <1p> already defines an<n>instance variable with the same name. Proceed anyway?'
121-
expandMacrosWith: class name) ].
122-
true ]).
123-
(RBCondition checkNotMultipleTemporaryDefinitionsOf: temporaryVariableName in: class).
124-
(ReVariablesNotReadBeforeWrittenCondition new
125-
subtree: parseTree;
126-
variables: temporaryVariableName;
127-
checkForTemporaryVariables: true) }
117+
self preconditionNoSubclassDefinesVar.
118+
self preconditionNoMultipleTempOccurences.
119+
self preconditionNoReadBeforeWritten }
128120
]
129121

130122
{ #category : 'initialization' }
@@ -143,6 +135,31 @@ RBTemporaryToInstanceVariableRefactoring >> isTemporaryVariableNameValid [
143135
self refactoringError: temporaryVariableName , ' is a block parameter' ]
144136
]
145137

138+
{ #category : 'preconditions' }
139+
RBTemporaryToInstanceVariableRefactoring >> preconditionNoMultipleTempOccurences [
140+
141+
^ ReMultipleMethodsDontReferToTempVarCondition name: temporaryVariableName class: class selector: selector
142+
]
143+
144+
{ #category : 'preconditions' }
145+
RBTemporaryToInstanceVariableRefactoring >> preconditionNoReadBeforeWritten [
146+
147+
^ ReVariablesNotReadBeforeWrittenCondition new
148+
subtree: parseTree;
149+
variables: { temporaryVariableName };
150+
checkForTemporaryVariables: true
151+
]
152+
153+
{ #category : 'preconditions' }
154+
RBTemporaryToInstanceVariableRefactoring >> preconditionNoSubclassDefinesVar [
155+
156+
^ RBCondition
157+
withBlock: [ (class allSubclasses anySatisfy: [ :cls | cls definesInstanceVariable: temporaryVariableName asString ]) not ]
158+
errorString:
159+
('One or more subclasses of <1p> already defines an<n>instance variable with the same name.'
160+
expandMacrosWith: class name)
161+
]
162+
146163
{ #category : 'preconditions' }
147164
RBTemporaryToInstanceVariableRefactoring >> preconditions [
148165

@@ -159,10 +176,6 @@ RBTemporaryToInstanceVariableRefactoring >> prepareForExecution [
159176
RBTemporaryToInstanceVariableRefactoring >> privateTransform [
160177

161178
self removeTemporaryOfClass: class.
162-
class allSubclasses do: [ :cls |
163-
(cls definesInstanceVariable: temporaryVariableName)
164-
ifTrue: [ cls removeInstanceVariable: temporaryVariableName ]
165-
ifFalse: [ self removeTemporaryOfClass: cls ] ].
166179
class addInstanceVariable: temporaryVariableName
167180
]
168181

@@ -178,8 +191,8 @@ RBTemporaryToInstanceVariableRefactoring >> removeTemporaryOfMethod: aSelector i
178191
method := aClass methodFor: aSelector.
179192
methodParseTree := method parseTree.
180193
methodParseTree ifNil: [ self refactoringError: 'Could not parse method' ].
181-
( matcher := self parseTreeRewriterClass removeTemporaryNamed: temporaryVariableName )
182-
executeTree: methodParseTree.
194+
(methodParseTree temporaryNames includes: temporaryVariableName) ifFalse: [ ^ self ].
195+
(matcher := self parseTreeRewriterClass removeTemporaryNamed: temporaryVariableName) executeTree: methodParseTree.
183196
method compileTree: matcher tree
184197
]
185198

Lines changed: 79 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,79 @@
1+
"
2+
I check if temporary variable name is used in other methods of the class.
3+
"
4+
Class {
5+
#name : 'ReMultipleMethodsDontReferToTempVarCondition',
6+
#superclass : 'ReVariableNameCondition',
7+
#instVars : [
8+
'class',
9+
'selector'
10+
],
11+
#category : 'Refactoring-Core-Conditions',
12+
#package : 'Refactoring-Core',
13+
#tag : 'Conditions'
14+
}
15+
16+
{ #category : 'instance creation' }
17+
ReMultipleMethodsDontReferToTempVarCondition class >> name: aString class: aClass selector: aSelector [
18+
19+
^ (self name: aString)
20+
class: aClass;
21+
selector: aSelector yourself
22+
]
23+
24+
{ #category : 'checking' }
25+
ReMultipleMethodsDontReferToTempVarCondition >> check [
26+
27+
^ self violators isEmpty
28+
]
29+
30+
{ #category : 'setter' }
31+
ReMultipleMethodsDontReferToTempVarCondition >> class: aRBClass [
32+
33+
class := aRBClass.
34+
35+
]
36+
37+
{ #category : 'utilities' }
38+
ReMultipleMethodsDontReferToTempVarCondition >> multipleMethodsDefiningTemporary: aString in: aClass ignore: aBlock [
39+
40+
| searcher methods method |
41+
searcher := OCParseTreeSearcher new.
42+
methods := Set new.
43+
method := nil.
44+
45+
searcher matches: aString do: [ :aNode :answer | methods add: method ].
46+
aClass withAllSubclasses do: [ :cls |
47+
cls selectors do: [ :each |
48+
(aBlock value: cls value: each) ifFalse: [
49+
| parseTree |
50+
method := cls methodFor: each.
51+
parseTree := cls parseTreeForSelector: each.
52+
parseTree ifNotNil: [ searcher executeTree: parseTree ] ] ] ].
53+
^ methods
54+
]
55+
56+
{ #category : 'accessing' }
57+
ReMultipleMethodsDontReferToTempVarCondition >> selector: aSelector [
58+
59+
selector := aSelector
60+
]
61+
62+
{ #category : 'displaying' }
63+
ReMultipleMethodsDontReferToTempVarCondition >> violationMessageOn: aStream [
64+
65+
self violators ifEmpty: [ ^ self ].
66+
^ aStream
67+
nextPutAll: 'More than one method defines temporary variable ';
68+
nextPutAll: name;
69+
nextPutAll: ': ';
70+
nextPutAll: (self violators collect: [ :m | m selector ]) asArray asString
71+
]
72+
73+
{ #category : 'checking' }
74+
ReMultipleMethodsDontReferToTempVarCondition >> violators [
75+
76+
| methods |
77+
methods := self multipleMethodsDefiningTemporary: name in: class ignore: [ :cls :selectors | false ].
78+
^ methods reject: [ :m | m selector = selector ]
79+
]

src/Refactoring-Core/ReRefactoring.class.st

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,10 +59,11 @@ ReRefactoring >> canReferenceVariable: aString in: aClass [
5959
{ #category : 'scripting api - conditions' }
6060
ReRefactoring >> checkBreakingChangePreconditions [
6161
"Check a preconditions and raise an error on violations. This method is part of the scripting API since it raises an error."
62-
62+
6363
| failedPreconditions |
6464
failedPreconditions := self failedBreakingChangePreconditions.
6565
failedPreconditions ifEmpty: [ ^ self ].
66+
6667
RBRefactoringWarning signalFor: failedPreconditions
6768
]
6869

src/Refactoring-Core/ReVariablesNotReadBeforeWrittenCondition.class.st

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ ReVariablesNotReadBeforeWrittenCondition >> variables: aCollection [
4848
{ #category : 'displaying' }
4949
ReVariablesNotReadBeforeWrittenCondition >> violationMessageOn: aStream [
5050

51+
self check ifTrue: [ ^ self ].
5152
aStream
5253
nextPutAll: 'Cannot extract selected code because variables: ';
5354
nextPutAll: variables asString;
Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
Class {
2+
#name : 'ReClassToConvertTemporaryToInstanceVariable',
3+
#superclass : 'Object',
4+
#instVars : [
5+
'instVar'
6+
],
7+
#category : 'Refactoring-DataForTesting-ForConvertingVariables',
8+
#package : 'Refactoring-DataForTesting',
9+
#tag : 'ForConvertingVariables'
10+
}
11+
12+
{ #category : 'action' }
13+
ReClassToConvertTemporaryToInstanceVariable >> doAction1 [
14+
15+
| temp |
16+
temp := 35.
17+
18+
^ temp
19+
]
20+
21+
{ #category : 'action' }
22+
ReClassToConvertTemporaryToInstanceVariable >> doAction2 [
23+
24+
| instVar |
25+
instVar := 3.
26+
^ instVar
27+
]
28+
29+
{ #category : 'initialization' }
30+
ReClassToConvertTemporaryToInstanceVariable >> initialize [
31+
32+
<ignoreUnusedVariables: #( #instVar )>
33+
super initialize
34+
]
Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
Class {
2+
#name : 'ReConvertTemporaryToInstanceVariableDriverTest',
3+
#superclass : 'ReDriverTest',
4+
#instVars : [
5+
'testingEnvironment'
6+
],
7+
#category : 'Refactoring-UI-Tests-Driver',
8+
#package : 'Refactoring-UI-Tests',
9+
#tag : 'Driver'
10+
}
11+
12+
{ #category : 'getter' }
13+
ReConvertTemporaryToInstanceVariableDriverTest >> classToConvertTemporaryToInstanceVariable [
14+
15+
^ ReClassToConvertTemporaryToInstanceVariable
16+
]
17+
18+
{ #category : 'running' }
19+
ReConvertTemporaryToInstanceVariableDriverTest >> setUp [
20+
21+
super setUp.
22+
testingEnvironment := RBClassEnvironment classes: self classToConvertTemporaryToInstanceVariable withAllSubclasses
23+
]
24+
25+
{ #category : 'tests' }
26+
ReConvertTemporaryToInstanceVariableDriverTest >> testConvertTempFailure [
27+
28+
| driver |
29+
driver := ReConvertTemporaryToInstanceVariableDriver new.
30+
self setUpDriver: driver.
31+
driver class: self classToConvertTemporaryToInstanceVariable selector: #doAction2 variable: 'instVar'.
32+
33+
driver runRefactoring.
34+
35+
self assert: driver refactoring changes changes size equals: 0
36+
]
37+
38+
{ #category : 'tests' }
39+
ReConvertTemporaryToInstanceVariableDriverTest >> testConvertTempSuccessfully [
40+
41+
| driver |
42+
driver := ReConvertTemporaryToInstanceVariableDriver new.
43+
self setUpDriver: driver.
44+
driver class: self classToConvertTemporaryToInstanceVariable selector: #doAction1 variable: 'temp'.
45+
46+
driver runRefactoring.
47+
48+
self assert: driver refactoring changes changes size equals: 2.
49+
50+
]

src/Refactoring-UI/ReBrowseMethodChoice.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,5 +17,5 @@ ReBrowseMethodChoice >> action [
1717
{ #category : 'accessing' }
1818
ReBrowseMethodChoice >> description [
1919

20-
^ 'Browse the method(s)'
20+
^ 'Browse the method'
2121
]
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
Class {
2+
#name : 'ReBrowseMethodsChoice',
3+
#superclass : 'ReMethodChoice',
4+
#category : 'Refactoring-UI-Choices',
5+
#package : 'Refactoring-UI',
6+
#tag : 'Choices'
7+
}
8+
9+
{ #category : 'accessing' }
10+
ReBrowseMethodsChoice >> action [
11+
12+
driver browseMethods
13+
]
14+
15+
{ #category : 'accessing' }
16+
ReBrowseMethodsChoice >> description [
17+
18+
^ description ifNil: [ description := 'Browse the methods' ]
19+
]

0 commit comments

Comments
 (0)