Skip to content
Open
Show file tree
Hide file tree
Changes from 9 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
Extension { #name : 'SycPushDownVariableCommand2' }

{ #category : '*Calypso-SystemTools-FullBrowser' }
SycPushDownVariableCommand2 class >> fullBrowserMenuActivation [
<classAnnotation>

^CmdContextMenuActivation byRootGroupItemOrder: 2002 for: ClyFullBrowserVariableContext
]
29 changes: 29 additions & 0 deletions src/Refactoring-Core/ReClassesHaveAnySubclassCondition.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
Class {
#name : 'ReClassesHaveAnySubclassCondition',
#superclass : 'ReClassesCondition',
#category : 'Refactoring-Core-Conditions',
#package : 'Refactoring-Core',
#tag : 'Conditions'
}

{ #category : 'testing' }
ReClassesHaveAnySubclassCondition >> hasSubclasses: aClass [

^ aClass subclasses isNotEmpty
]

{ #category : 'displaying' }
ReClassesHaveAnySubclassCondition >> violationMessageOn: aStream [

self violators do: [ :violator |
aStream
nextPutAll: violator name;
nextPutAll: ' has no subclasses.';
space ]
]

{ #category : 'accessing' }
ReClassesHaveAnySubclassCondition >> violators [

^ violators ifNil: [ violators := classes reject: [ :aClass | self hasSubclasses: aClass ] ]
]
14 changes: 7 additions & 7 deletions src/Refactoring-Core/ReIsValidInstanceVariableName.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,21 +13,21 @@ Class {
ReIsValidInstanceVariableName >> check [

| string |
name isString ifFalse: [
violator := name.
variable isString ifFalse: [
violator := variable.
^ false ].
string := name asString.
string := variable asString.
string isEmpty ifTrue: [
violator := name.
violator := variable.
^ false ].
(Symbol reservedLiterals includes: string) ifTrue: [
violator := name.
violator := variable.
^ false ].
string first isUppercase ifTrue: [
violator := name.
violator := variable.
^ false ].
(OCScanner isVariable: string) ifFalse: [
violator := name.
violator := variable.
^ false ].
^ true
]
Expand Down
14 changes: 7 additions & 7 deletions src/Refactoring-Core/ReIsValidSharedVariableName.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,21 +13,21 @@ Class {
ReIsValidSharedVariableName >> check [

| string |
name isString ifFalse: [
violator := name.
variable isString ifFalse: [
violator := variable.
^ false ].
string := name asString.
string := variable asString.
(Symbol reservedLiterals includes: string) ifTrue: [
violator := name.
violator := variable.
^ false ].
string isEmpty ifTrue: [
violator := name.
violator := variable.
^ false ].
string first isUppercase ifFalse: [
violator := name.
violator := variable.
^ false ].
(OCScanner isVariable: string) ifFalse: [
violator := name.
violator := variable.
^ false ].
^ true
]
Expand Down
15 changes: 6 additions & 9 deletions src/Refactoring-Core/ReIsVariableNotDefinedInHierarchy.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,6 @@ I check if `name` is not already used by a variable in the `class` hierarchy
Class {
#name : 'ReIsVariableNotDefinedInHierarchy',
#superclass : 'ReVariableNameCondition',
#instVars : [
'class'
],
#category : 'Refactoring-Core-Conditions',
#package : 'Refactoring-Core',
#tag : 'Conditions'
Expand All @@ -22,21 +19,21 @@ ReIsVariableNotDefinedInHierarchy class >> name: aString class: aClass [
{ #category : 'checking' }
ReIsVariableNotDefinedInHierarchy >> check [

(class hierarchyDefinesVariable: name) ifTrue: [
violator := name.
(aClass hierarchyDefinesVariable: variable) ifTrue: [
violator := variable.
^ false ].
^ true
]

{ #category : 'accessing' }
ReIsVariableNotDefinedInHierarchy >> class: aClass [
class := aClass
ReIsVariableNotDefinedInHierarchy >> class: someClass [
aClass := someClass
]

{ #category : 'accessing' }
{ #category : 'displaying' }
ReIsVariableNotDefinedInHierarchy >> violationMessageOn: aStream [

^ aStream
nextPutAll: violator;
nextPutAll: (' is already defined in the class {1} or its hierarchy.' format: { class name })
nextPutAll: (' is already defined in the class {1} or its hierarchy.' format: { aClass name })
]
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ Class {
#superclass : 'ReMethodsCondition',
#instVars : [
'class',
'selectors'
'selectors',
'variables'
],
#category : 'Refactoring-Core-Conditions',
#package : 'Refactoring-Core',
Expand All @@ -18,7 +19,16 @@ Class {
ReMethodsDontReferToLocalSharedVarsCondition >> class: aRBClass selectors: aCollection [

class := aRBClass.
selectors := aCollection
selectors := aCollection.
variables := nil
]

{ #category : 'initialization' }
ReMethodsDontReferToLocalSharedVarsCondition >> class: aRBClass selectors: aCollection variables: aCollection2 [

class := aRBClass.
selectors := aCollection.
variables := aCollection2
]

{ #category : 'accessing' }
Expand All @@ -27,6 +37,11 @@ ReMethodsDontReferToLocalSharedVarsCondition >> referencedSharedVariables [
^ self violators collect: [ :violator | violator at: 2 ]
]

{ #category : 'accessing' }
ReMethodsDontReferToLocalSharedVarsCondition >> variables [
^ variables ifNil: [ variables := class classVariableNames ]
]

{ #category : 'displaying' }
ReMethodsDontReferToLocalSharedVarsCondition >> violationMessageOn: aStream [

Expand All @@ -48,7 +63,7 @@ ReMethodsDontReferToLocalSharedVarsCondition >> violators [

violators := Set new.
selectors do: [ :selector |
class classVariableNames do: [ :classVar |
self variables do: [ :classVar |
((class methodFor: selector) refersToVariable: classVar)
ifTrue: [ violators add: { selector . classVar } ] ] ].
^ violators asOrderedCollection
Expand Down
13 changes: 13 additions & 0 deletions src/Refactoring-Core/ReNewNegationCondition.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -24,12 +24,25 @@ ReNewNegationCondition >> condition: aCondition [
condition := aCondition.
]

{ #category : 'accessing' }
ReNewNegationCondition >> errorMacro [
"TODO: This was introduced for compatibility with RBAbstractCondition
and it should be removed"
^ self errorString
]

{ #category : 'accessing' }
ReNewNegationCondition >> errorString [

^ condition errorString
]

{ #category : 'logical operations' }
ReNewNegationCondition >> not [

^ condition
]

{ #category : 'displaying' }
ReNewNegationCondition >> violationMessageOn: aWriteStream [

Expand Down
59 changes: 59 additions & 0 deletions src/Refactoring-Core/RePushDownSharedVariableRefactoring.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
"
I am a refactoring for moving a class variable down to my subclasses.

My precondition verifies that the moved variable is not referenced in the methods of the original class.
"
Class {
#name : 'RePushDownSharedVariableRefactoring',
#superclass : 'RBVariableRefactoring',
#category : 'Refactoring-Core-Refactorings',
#package : 'Refactoring-Core',
#tag : 'Refactorings'
}

{ #category : 'preconditions' }
RePushDownSharedVariableRefactoring >> applicabilityPreconditions [

^ {
(RBCondition definesClassVariable: variableName in: class).
(ReClassesHaveAnySubclassCondition new classes: { class }) }
]

{ #category : 'preconditions' }
RePushDownSharedVariableRefactoring >> breakingChangePreconditions [

^ { self preconditionHasNoReferences }
]

{ #category : 'preconditions' }
RePushDownSharedVariableRefactoring >> findDestinationClasses [

| classes |
classes := class allSubclasses reject: [ :each |
(each whichSelectorsReferToClassVariable: variableName) isEmpty
and: [ (each classSide whichSelectorsReferToClassVariable: variableName) isEmpty ] ].
^ classes
]

{ #category : 'preconditions' }
RePushDownSharedVariableRefactoring >> preconditionHasNoReferences [

^ (ReSharedVariableHasReferencesInDefiningClass new class: class referencesToSharedVariable: variableName) not
]

{ #category : 'preconditions' }
RePushDownSharedVariableRefactoring >> preconditions [

^ self applicabilityPreconditions & self breakingChangePreconditions
]
Comment on lines +45 to +48
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This should not be needed anymore, and should not be used anywhere. I think this will also fail if it is called because both calls return lists and we try to & them. I should probably do a cleanup and remove preconditions soon

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I deleted it


{ #category : 'transforming' }
RePushDownSharedVariableRefactoring >> privateTransform [

| destinationClasses |

class removeClassVariable: variableName.
destinationClasses := self findDestinationClasses.
destinationClasses ifEmpty: [ ^ self ].
destinationClasses do: [ :aClass | aClass addClassVariable: variableName ]
]
26 changes: 15 additions & 11 deletions src/Refactoring-Core/ReSharedVariableHasReferences.class.st
Original file line number Diff line number Diff line change
@@ -1,28 +1,26 @@
"
I check if a Shared Variable is referenced from methods in aClass or any of its subclasses
"
Class {
#name : 'ReSharedVariableHasReferences',
#superclass : 'RBNewAbstractCondition',
#instVars : [
'aClass',
'violators',
'sharedVariable'
],
#superclass : 'ReVariableCondition',
#category : 'Refactoring-Core-Conditions',
#package : 'Refactoring-Core',
#tag : 'Conditions'
}

{ #category : 'accessing' }
{ #category : 'checking' }
ReSharedVariableHasReferences >> check [

aClass withAllSubclasses do: [ :each |
| res |
res := (each whichMethodsReferToSharedVariable: sharedVariable).
res := (each whichMethodsReferToSharedVariable: variable).
res isNotEmpty
ifTrue: [ violators addAll: res ].
].
aClass withAllSubclasses do: [ :each |
| res |
res := (each classSide whichMethodsReferToSharedVariable: sharedVariable).
res := (each classSide whichMethodsReferToSharedVariable: variable).
res isNotEmpty
ifTrue: [ violators addAll: res ].
].
Expand All @@ -32,14 +30,14 @@ ReSharedVariableHasReferences >> check [
{ #category : 'accessing' }
ReSharedVariableHasReferences >> errorString [

^ ' Variable ', sharedVariable , ' is still referenced'
^ ' Variable ', variable , ' is still referenced'
]

{ #category : 'instance creation' }
ReSharedVariableHasReferences >> hierarchyOf: aRBClass referencesSharedVariable: variableName [

aClass := aRBClass instanceSide.
sharedVariable := variableName
variable := variableName
]

{ #category : 'initialization' }
Expand All @@ -48,6 +46,12 @@ ReSharedVariableHasReferences >> initialize [
violators := OrderedCollection new
]

{ #category : 'accessing' }
ReSharedVariableHasReferences >> violatorCandidates [

^ aClass withAllSubclasses flatCollect: [ :cls | cls selectors , cls classSide selectors ]
]

{ #category : 'accessing' }
ReSharedVariableHasReferences >> violators [
^ violators
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
"
I check if a Shared Variable is referenced from methods in the class that defines it.
"
Class {
#name : 'ReSharedVariableHasReferencesInDefiningClass',
#superclass : 'ReVariableCondition',
#category : 'Refactoring-Core-Conditions',
#package : 'Refactoring-Core',
#tag : 'Conditions'
}

{ #category : 'checking' }
ReSharedVariableHasReferencesInDefiningClass >> check [

^ self violators isNotEmpty
]

{ #category : 'initialization' }
ReSharedVariableHasReferencesInDefiningClass >> class: definingClass referencesToSharedVariable: aSharedVarName [
aClass := definingClass.
variable := aSharedVarName
]

{ #category : 'accessing' }
ReSharedVariableHasReferencesInDefiningClass >> violatorCandidates [

^ aClass selectors, aClass classSide selectors
]

{ #category : 'accessing' }
ReSharedVariableHasReferencesInDefiningClass >> violators [
| res |
violators ifNotNil: [ ^ violators ].
violators := OrderedCollection new.
res := aClass whichMethodsReferToSharedVariable: variable.
res isNotEmpty
ifTrue: [ violators addAll: res ].
res := (aClass classSide whichMethodsReferToSharedVariable: variable).
res isNotEmpty
ifTrue: [ violators addAll: res ].
^ violators
]
Loading