diff --git a/src/Refactoring-Core/ManifestRefactoringCore.class.st b/src/Refactoring-Core/ManifestRefactoringCore.class.st index bf1f59395a2..124fb937fea 100644 --- a/src/Refactoring-Core/ManifestRefactoringCore.class.st +++ b/src/Refactoring-Core/ManifestRefactoringCore.class.st @@ -2,7 +2,9 @@ Please describe the package using the class comment of the included manifest class. The manifest class also includes other additional metadata for the package. These meta data are used by other tools such as the SmalllintManifestChecker and the critics Browser " Class { - #name : #ManifestRefactoringCore, - #superclass : #PackageManifest, - #category : #'Refactoring-Core-Manifest' + #name : 'ManifestRefactoringCore', + #superclass : 'PackageManifest', + #category : 'Refactoring-Core-Manifest', + #package : 'Refactoring-Core', + #tag : 'Manifest' } diff --git a/src/Refactoring-Core/RBAbstractClass.class.st b/src/Refactoring-Core/RBAbstractClass.class.st index 4e84f8a4a14..f139773b4f1 100644 --- a/src/Refactoring-Core/RBAbstractClass.class.st +++ b/src/Refactoring-Core/RBAbstractClass.class.st @@ -19,8 +19,8 @@ Like a real class I referre to my superclass and subclass, which again are actua " Class { - #name : #RBAbstractClass, - #superclass : #RBEntity, + #name : 'RBAbstractClass', + #superclass : 'RBEntity', #instVars : [ 'name', 'newMethods', @@ -34,37 +34,39 @@ Class { #classVars : [ 'LookupSuperclass' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass class >> existingNamed: aString [ ^ self subclassResponsibility ] -{ #category : #'class initialization' } +{ #category : 'class initialization' } RBAbstractClass class >> initialize [ LookupSuperclass := Object new ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass class >> named: aString [ ^ self subclassResponsibility ] -{ #category : #comparing } +{ #category : 'comparing' } RBAbstractClass >> = aRBClass [ ^self class = aRBClass class and: [self name = aRBClass name and: [self model = aRBClass model]] ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> addInstanceVariable: aString [ self privateInstanceVariableNames add: aString. model addInstanceVariable: aString to: self ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> addMethod: aRBMethod [ self newMethods at: aRBMethod selector put: aRBMethod. @@ -72,17 +74,17 @@ RBAbstractClass >> addMethod: aRBMethod [ removedMethods remove: aRBMethod selector ifAbsent: [ ] ] ] -{ #category : #private } +{ #category : 'private' } RBAbstractClass >> addSubclass: aRBClass [ self subclasses add: aRBClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allClassVariableNames [ ^self subclassResponsibility ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allInstanceVariableNames [ | sprClass | @@ -93,7 +95,7 @@ RBAbstractClass >> allInstanceVariableNames [ ifNotNil: [ sprClass allInstanceVariableNames , self instanceVariableNames ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allMethods [ ^ self allSelectors @@ -101,12 +103,12 @@ RBAbstractClass >> allMethods [ thenSelect: #isNotNil ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allPoolDictionaryNames [ ^self subclassResponsibility ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> allSelectors [ | class selectors | class := self. @@ -117,7 +119,7 @@ RBAbstractClass >> allSelectors [ ^selectors ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allSubclasses [ | allSubclasses index | index := 1. @@ -128,7 +130,7 @@ RBAbstractClass >> allSubclasses [ ^allSubclasses ] -{ #category : #enumerating } +{ #category : 'enumerating' } RBAbstractClass >> allSubclassesDo: aBlock [ "Evaluate the argument, aBlock, for each of the receiver's subclasses." @@ -138,7 +140,7 @@ RBAbstractClass >> allSubclassesDo: aBlock [ cl allSubclassesDo: aBlock] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allSuperclasses [ | supers sprClass | supers := OrderedCollection new. @@ -149,7 +151,7 @@ RBAbstractClass >> allSuperclasses [ ^supers ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> allSuperclassesUntil: aClass [ | supers sprClass | @@ -161,18 +163,23 @@ RBAbstractClass >> allSuperclassesUntil: aClass [ ^supers ] -{ #category : #'method accessing' } +{ #category : 'accessing' } +RBAbstractClass >> binding [ + ^ Smalltalk globals associationAt: self name +] + +{ #category : 'method accessing' } RBAbstractClass >> bindingOf: aString [ ^self realClass classPool associationAt: aString asSymbol ifAbsent: [self realClass classPool associationAt: aString asString ifAbsent: [nil]] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> canUnderstand: aSelector [ ^self definesMethod: aSelector ] -{ #category : #printing } +{ #category : 'printing' } RBAbstractClass >> canonicalArgumentName [ | prefix | prefix := self name first isVowel @@ -181,7 +188,7 @@ RBAbstractClass >> canonicalArgumentName [ ^ prefix, self name ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> checkSelector: aSelector using: aMatcher [ | parseTree | @@ -190,24 +197,25 @@ RBAbstractClass >> checkSelector: aSelector using: aMatcher [ ^ aMatcher answer ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> classBinding [ - ^ Smalltalk globals associationAt: self name + self deprecated: 'Use binding' transformWith: '`@receiver classBinding' -> '`@receiver binding'. + ^ self binding ] -{ #category : #'accessing - navigation' } +{ #category : 'accessing - navigation' } RBAbstractClass >> classSide [ "Return the metaclass of the couple class/metaclass. Useful to avoid explicit test." ^ model metaclassNamed: self name ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> compile: aString [ ^ self compile: aString withAttributesFrom: (self methodFor: (self parserClass parseMethodPattern: aString)) ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> compile: aString classified: aSymbolCollection [ | change method | change := model @@ -222,18 +230,18 @@ RBAbstractClass >> compile: aString classified: aSymbolCollection [ ^ change ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> compile: aString withAttributesFrom: aRBMethod [ self compile: aString classified: aRBMethod protocols ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> compileTree: aRBMethodNode [ ^ (self methodFor: aRBMethodNode selector) compileTree: aRBMethodNode ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractClass >> convertMethod: selector using: searchReplacer [ "Convert the parse tree for selector using the searchReplacer. If a @@ -247,7 +255,7 @@ RBAbstractClass >> convertMethod: selector using: searchReplacer [ ifTrue: [ self compileTree: searchReplacer tree ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> definesClassVariable: aSymbol [ self realClass isTrait ifTrue: [^false]. (self directlyDefinesClassVariable: aSymbol) ifTrue: [^true]. @@ -255,43 +263,43 @@ RBAbstractClass >> definesClassVariable: aSymbol [ and: [self superclass definesClassVariable: aSymbol] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> definesInstanceVariable: aString [ (self directlyDefinesInstanceVariable: aString) ifTrue: [^true]. ^self superclass notNil and: [self superclass definesInstanceVariable: aString] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> definesMethod: aSelector [ (self directlyDefinesMethod: aSelector) ifTrue: [^true]. ^self superclass notNil and: [self superclass definesMethod: aSelector] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> definesPoolDictionary: aSymbol [ (self directlyDefinesPoolDictionary: aSymbol) ifTrue: [^true]. ^ self superclass notNil and: [self superclass definesPoolDictionary: aSymbol] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> definesVariable: aVariableName [ ^(self definesClassVariable: aVariableName) or: [self definesInstanceVariable: aVariableName] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesClassVariable: aString [ self subclassResponsibility ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesInstanceVariable: aString [ ^self instanceVariableNames includes: aString ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesLocalMethod: aSelector [ self isDefined ifTrue: @@ -300,7 +308,7 @@ RBAbstractClass >> directlyDefinesLocalMethod: aSelector [ ^newMethods notNil and: [newMethods includesKey: aSelector] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesMethod: aSelector [ self isDefined ifTrue: @@ -309,18 +317,18 @@ RBAbstractClass >> directlyDefinesMethod: aSelector [ ^newMethods notNil and: [newMethods includesKey: aSelector] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesPoolDictionary: aString [ self subclassResponsibility ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> directlyDefinesVariable: aVariableName [ ^(self directlyDefinesClassVariable: aVariableName) or: [self directlyDefinesInstanceVariable: aVariableName] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> existingMethodsThatReferTo: aSymbol [ | existingMethods | existingMethods := self realClass thoroughWhichSelectorsReferTo: aSymbol. @@ -330,7 +338,7 @@ RBAbstractClass >> existingMethodsThatReferTo: aSymbol [ reject: [ :each | (self hasRemoved: each) or: [ self newMethods includesKey: each ] ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> existingMethodsThatReferToClassVariable: aString [ | binding existingMethods | binding := (self bindingOf: aString) @@ -343,7 +351,7 @@ RBAbstractClass >> existingMethodsThatReferToClassVariable: aString [ reject: [ :each | (self hasRemoved: each) or: [ self newMethods includesKey: each ] ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> existingMethodsThatReferToInstanceVariable: aString [ | existingMethods | existingMethods := self realClass @@ -354,14 +362,14 @@ RBAbstractClass >> existingMethodsThatReferToInstanceVariable: aString [ reject: [ :each | (self hasRemoved: each) or: [ self newMethods includesKey: each ] ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> firstSuperclassRedefines: aSelector [ "Return rbClass, if one of your superclasses redefines the method with name, aMethod" self allSuperclasses do: [:each | (each directlyDefinesMethod: aSelector) ifTrue: [^ each]] ] -{ #category : #querying } +{ #category : 'querying' } RBAbstractClass >> getterMethodFor: aVariableName [ | matcher candidateGetters | matcher := self parseTreeSearcherClass getterMethod: aVariableName. @@ -377,17 +385,17 @@ RBAbstractClass >> getterMethodFor: aVariableName [ ifNone: [ nil ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hasRemoved: aSelector [ ^removedMethods notNil and: [removedMethods includes: aSelector] ] -{ #category : #comparing } +{ #category : 'comparing' } RBAbstractClass >> hash [ ^self name hash bitXor: self class hash ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hierarchyDefinesClassVariable: aString [ (self definesClassVariable: aString) ifTrue: [ ^ true ]. @@ -395,7 +403,7 @@ RBAbstractClass >> hierarchyDefinesClassVariable: aString [ anySatisfy: [ :each | each directlyDefinesClassVariable: aString ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hierarchyDefinesInstanceVariable: aString [ (self definesInstanceVariable: aString) ifTrue: [ ^ true ]. @@ -403,13 +411,13 @@ RBAbstractClass >> hierarchyDefinesInstanceVariable: aString [ anySatisfy: [ :each | each directlyDefinesInstanceVariable: aString ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hierarchyDefinesMethod: aSelector [ (self definesMethod: aSelector) ifTrue: [^true]. ^self subclassRedefines: aSelector ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hierarchyDefinesPoolDictionary: aString [ (self definesPoolDictionary: aString) ifTrue: [ ^ true ]. @@ -417,7 +425,7 @@ RBAbstractClass >> hierarchyDefinesPoolDictionary: aString [ anySatisfy: [ :each | each directlyDefinesPoolDictionary: aString ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> hierarchyDefinesVariable: aString [ (self definesVariable: aString) ifTrue: [ ^ true ]. @@ -425,7 +433,7 @@ RBAbstractClass >> hierarchyDefinesVariable: aString [ anySatisfy: [ :each | each directlyDefinesVariable: aString ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> includesClass: aRBClass [ | currentClass | currentClass := self. @@ -434,47 +442,47 @@ RBAbstractClass >> includesClass: aRBClass [ ^currentClass = aRBClass ] -{ #category : #initialization } +{ #category : 'initialization' } RBAbstractClass >> initialize [ super initialize. name := #'Unknown Class' ] -{ #category : #'accessing - navigation' } +{ #category : 'accessing - navigation' } RBAbstractClass >> instanceSide [ "Return the class of the couple class/metaclass. Useful to avoid explicit test." ^ model classNamed: self name ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> instanceVariableNames [ ^self privateInstanceVariableNames copy ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> instanceVariableNames: aCollectionOfStrings [ instanceVariableNames := aCollectionOfStrings asOrderedCollection ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> isAbstract [ (self whichSelectorsReferToSymbol: #subclassResponsibility) ifNotEmpty: [^true]. model allReferencesToClass: self do: [:each | ^false]. ^true ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> isDefined [ ^self realClass notNil ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> isMeta [ self subclassResponsibility ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> localSelectors [ | selectors | selectors := Set new. @@ -486,7 +494,7 @@ RBAbstractClass >> localSelectors [ ^selectors ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> methodFor: aSelector [ ^ self newMethods at: aSelector ifAbsent: [ @@ -500,33 +508,33 @@ RBAbstractClass >> methodFor: aSelector [ ifFalse: [ modelFactory rbMethod for: self fromMethod: compiledMethod andSelector: aSelector ] ] ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> model [ ^model ] -{ #category : #initialization } +{ #category : 'initialization' } RBAbstractClass >> model: aRBSmalltalk [ model := aRBSmalltalk ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> name [ ^name ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> name: aSymbol [ name := aSymbol ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> newMethods [ ^ newMethods ifNil: [ newMethods := IdentityDictionary new ] ifNotNil: [ newMethods ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> parseTreeFor: aSymbol [ self @@ -536,7 +544,7 @@ RBAbstractClass >> parseTreeFor: aSymbol [ ^ self parseTreeForSelector: aSymbol ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> parseTreeForSelector: aSelector [ | class method | @@ -548,17 +556,17 @@ RBAbstractClass >> parseTreeForSelector: aSelector [ ^ method parseTree doSemanticAnalysis ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> parseTreeSearcherClass [ ^ RBParseTreeSearcher ] -{ #category : #printing } +{ #category : 'printing' } RBAbstractClass >> printOn: aStream [ aStream nextPutAll: self name ] -{ #category : #private } +{ #category : 'private' } RBAbstractClass >> privateInstanceVariableNames [ instanceVariableNames @@ -569,7 +577,7 @@ RBAbstractClass >> privateInstanceVariableNames [ ^ instanceVariableNames ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> protocols [ ^ (self allMethods @@ -577,7 +585,7 @@ RBAbstractClass >> protocols [ asOrderedCollection ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> protocolsFor: aSelector [ | change | @@ -593,54 +601,54 @@ RBAbstractClass >> protocolsFor: aSelector [ ifNotNil: [ change protocols ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> realClass [ ^realClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> realClass: aClass [ realClass := aClass. superclass ifNil: [ superclass := LookupSuperclass ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> realName: aSymbol [ ^ self subclassResponsibility ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> removeInstanceVariable: aString [ self privateInstanceVariableNames remove: aString. model removeInstanceVariable: aString from: self ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> removeInstanceVariable: aString ifAbsent: aBlock [ self privateInstanceVariableNames remove: aString ifAbsent: aBlock. model removeInstanceVariable: aString from: self ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> removeMethod: aSelector [ self newMethods removeKey: aSelector ifAbsent: []. model removeMethod: aSelector from: self. self removedMethods add: aSelector ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> removeSubclass: aRBClass [ self subclasses remove: aRBClass ifAbsent: [] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> removedMethods [ ^ removedMethods ifNil: [ removedMethods := Set new ] ifNotNil: [ removedMethods ] ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> renameInstanceVariable: oldName to: newName around: aBlock [ self privateInstanceVariableNames at: (self privateInstanceVariableNames indexOf: oldName asString) @@ -653,7 +661,7 @@ RBAbstractClass >> renameInstanceVariable: oldName to: newName around: aBlock [ around: aBlock ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> selectors [ | selectors | selectors := Set new. @@ -665,7 +673,7 @@ RBAbstractClass >> selectors [ ^selectors ] -{ #category : #querying } +{ #category : 'querying' } RBAbstractClass >> setterMethodFor: aVariableName [ | matcher candidateSetters | matcher := self parseTreeSearcherClass setterMethod: aVariableName. @@ -681,12 +689,12 @@ RBAbstractClass >> setterMethodFor: aVariableName [ ifNone: [ nil ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> soleInstance [ ^ self instanceSide ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> sourceCodeFor: aSelector [ | class | @@ -696,19 +704,19 @@ RBAbstractClass >> sourceCodeFor: aSelector [ ^ ( class methodFor: aSelector ) source ] -{ #category : #printing } +{ #category : 'printing' } RBAbstractClass >> storeOn: aStream [ aStream nextPutAll: self name ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> subclassRedefines: aSelector [ "Return true, if one of your subclasses redefines the method with name, aMethod" ^ self allSubclasses anySatisfy: [ :each | each directlyDefinesMethod: aSelector ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> subclasses [ ^ subclasses @@ -721,52 +729,52 @@ RBAbstractClass >> subclasses [ ifNotNil: [ subclasses ] ] -{ #category : #enumerating } +{ #category : 'enumerating' } RBAbstractClass >> subclassesDo: aBlock [ self subclasses do: aBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> superclass [ ^superclass == LookupSuperclass ifTrue: [model classFor: self realClass superclass] ifFalse: [superclass] ] -{ #category : #private } +{ #category : 'private' } RBAbstractClass >> superclass: aRBClass [ self superclass ifNotNil: [self superclass removeSubclass: self]. superclass := aRBClass. superclass ifNotNil: [superclass addSubclass: self] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> superclassRedefines: aSelector [ "Return true, if one of your superclasses redefines the method with name, aMethod" ^ self allSuperclasses anySatisfy: [ :each | each directlyDefinesMethod: aSelector ] ] -{ #category : #'accessing - deprecated' } +{ #category : 'accessing - deprecated' } RBAbstractClass >> theMetaClass [ self deprecated: 'Please use #classSide instead' transformWith: '`@receiver theMetaClass' -> '`@receiver classSide'. ^ self classSide ] -{ #category : #'accessing - deprecated' } +{ #category : 'accessing - deprecated' } RBAbstractClass >> theNonMetaClass [ self deprecated: 'Please use #instanceSide instead' transformWith: '`@receiver theNonMetaClass' -> '`@receiver instanceSide'. ^ self instanceSide ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> typeOfClassVariable: aSymbol [ ^model classNamed: #Object ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractClass >> whichClassIncludesSelector: aSelector [ (self directlyDefinesMethod: aSelector) ifTrue: [ ^ self ]. @@ -775,7 +783,7 @@ RBAbstractClass >> whichClassIncludesSelector: aSelector [ ifTrue: [ nil ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> whichSelectorsReferToClass: aRBClass [ | selectors | @@ -789,13 +797,13 @@ RBAbstractClass >> whichSelectorsReferToClass: aRBClass [ ] ]. ( self isDefined and: [ aRBClass isDefined ] ) - ifTrue: [ selectors addAll: ( self existingMethodsThatReferTo: aRBClass classBinding ). + ifTrue: [ selectors addAll: ( self existingMethodsThatReferTo: aRBClass binding ). selectors addAll: ( self existingMethodsThatReferTo: aRBClass name ) ]. ^ selectors ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> whichSelectorsReferToClassVariable: aString [ | selectors | @@ -810,7 +818,7 @@ RBAbstractClass >> whichSelectorsReferToClassVariable: aString [ ^ selectors ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> whichSelectorsReferToInstanceVariable: aString [ | selectors | @@ -827,7 +835,7 @@ RBAbstractClass >> whichSelectorsReferToInstanceVariable: aString [ ^ selectors ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> whichSelectorsReferToSymbol: aSymbol [ | selectors | @@ -845,7 +853,7 @@ RBAbstractClass >> whichSelectorsReferToSymbol: aSymbol [ ^ selectors ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> whoDefinesClassVariable: aString [ | sprClass | (self directlyDefinesClassVariable: aString) ifTrue: [ ^ self ]. @@ -853,7 +861,7 @@ RBAbstractClass >> whoDefinesClassVariable: aString [ ^ sprClass ifNotNil: [ sprClass whoDefinesClassVariable: aString ] ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBAbstractClass >> whoDefinesInstanceVariable: aString [ | sprClass | (self directlyDefinesInstanceVariable: aString) ifTrue: [ ^ self ]. @@ -861,7 +869,7 @@ RBAbstractClass >> whoDefinesInstanceVariable: aString [ ^ sprClass ifNotNil: [ sprClass whoDefinesInstanceVariable: aString ] ] -{ #category : #'method accessing' } +{ #category : 'method accessing' } RBAbstractClass >> whoDefinesMethod: aSelector [ | sprClass | (self directlyDefinesMethod: aSelector) ifTrue: [ ^ self ]. @@ -869,21 +877,21 @@ RBAbstractClass >> whoDefinesMethod: aSelector [ ^ sprClass ifNotNil: [ sprClass whoDefinesMethod: aSelector ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> withAllSubclasses [ ^ self allSubclasses add: self; yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> withAllSuperclasses [ ^ self allSuperclasses add: self; yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractClass >> withAllSuperclassesUntil: aClass [ ^ (self allSuperclassesUntil: aClass) diff --git a/src/Refactoring-Core/RBAbstractClassVariableReferencesRefactoring.class.st b/src/Refactoring-Core/RBAbstractClassVariableReferencesRefactoring.class.st index 899fb5483f4..d963456ca76 100644 --- a/src/Refactoring-Core/RBAbstractClassVariableReferencesRefactoring.class.st +++ b/src/Refactoring-Core/RBAbstractClassVariableReferencesRefactoring.class.st @@ -6,15 +6,17 @@ I create new accessor methods for the variables and replace every read and write " Class { - #name : #RBAbstractClassVariableReferencesRefactoring, - #superclass : #RBVariableRefactoring, + #name : 'RBAbstractClassVariableReferencesRefactoring', + #superclass : 'RBVariableRefactoring', #instVars : [ 'accessorsRefactoring' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractClassVariableReferencesRefactoring >> abstractClassSideReferences [ | replacer | replacer := self parseTreeRewriterClass @@ -32,7 +34,7 @@ RBAbstractClassVariableReferencesRefactoring >> abstractClassSideReferences [ using: replacer ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractClassVariableReferencesRefactoring >> abstractInstanceSideReferences [ | replacer | replacer := self parseTreeRewriterClass @@ -45,7 +47,7 @@ RBAbstractClassVariableReferencesRefactoring >> abstractInstanceSideReferences [ using: replacer ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBAbstractClassVariableReferencesRefactoring >> accessorsRefactoring [ ^ accessorsRefactoring @@ -58,12 +60,12 @@ RBAbstractClassVariableReferencesRefactoring >> accessorsRefactoring [ ifNotNil: [ accessorsRefactoring ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractClassVariableReferencesRefactoring >> createAccessors [ self generateChangesFor: self accessorsRefactoring ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractClassVariableReferencesRefactoring >> preconditions [ ^(RBCondition isMetaclass: class) not & (RBCondition directlyDefinesClassVariable: variableName asSymbol in: class) @@ -72,7 +74,7 @@ RBAbstractClassVariableReferencesRefactoring >> preconditions [ errorMacro: 'This refactoring does not work for Object, Behavior, ClassDescription, or Class') ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractClassVariableReferencesRefactoring >> privateTransform [ self createAccessors. self abstractInstanceSideReferences. diff --git a/src/Refactoring-Core/RBAbstractCondition.class.st b/src/Refactoring-Core/RBAbstractCondition.class.st index f86ace7ed21..0bdb24bb37a 100644 --- a/src/Refactoring-Core/RBAbstractCondition.class.st +++ b/src/Refactoring-Core/RBAbstractCondition.class.st @@ -12,61 +12,63 @@ RBCondition. Instances of RBConditions are created by factory methods on its class side. " Class { - #name : #RBAbstractCondition, - #superclass : #Object, + #name : 'RBAbstractCondition', + #superclass : 'Object', #instVars : [ 'errorMacro' ], - #category : #'Refactoring-Core-Conditions' + #category : 'Refactoring-Core-Conditions', + #package : 'Refactoring-Core', + #tag : 'Conditions' } -{ #category : #'logical operations' } +{ #category : 'logical operations' } RBAbstractCondition >> & aCondition [ ^RBConjunctiveCondition new left: self right: aCondition ] -{ #category : #checking } +{ #category : 'checking' } RBAbstractCondition >> check [ self subclassResponsibility ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractCondition >> errorBlock [ ^self errorBlockFor: false ] -{ #category : #private } +{ #category : 'private' } RBAbstractCondition >> errorBlockFor: aBoolean [ ^nil ] -{ #category : #private } +{ #category : 'private' } RBAbstractCondition >> errorMacro [ ^ errorMacro ifNil: [ 'unknown' ] ifNotNil: [ errorMacro ] ] -{ #category : #private } +{ #category : 'private' } RBAbstractCondition >> errorMacro: aString [ errorMacro := aString ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractCondition >> errorString [ ^self errorStringFor: false ] -{ #category : #private } +{ #category : 'private' } RBAbstractCondition >> errorStringFor: aBoolean [ ^self errorMacro expandMacrosWith: aBoolean ] -{ #category : #'logical operations' } +{ #category : 'logical operations' } RBAbstractCondition >> not [ ^RBNegationCondition on: self ] -{ #category : #'logical operations' } +{ #category : 'logical operations' } RBAbstractCondition >> | aCondition [ "(A | B) = (A not & B not) not" diff --git a/src/Refactoring-Core/RBAbstractInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBAbstractInstanceVariableRefactoring.class.st index b2ed9d61ab2..ebbecf79056 100644 --- a/src/Refactoring-Core/RBAbstractInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBAbstractInstanceVariableRefactoring.class.st @@ -6,15 +6,17 @@ I create new accessor methods for the variables and replace every read and write " Class { - #name : #RBAbstractInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, + #name : 'RBAbstractInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', #instVars : [ 'accessorsRefactoring' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractInstanceVariableRefactoring >> abstractReferences [ "Precondition: createAccessors has been executed. Else the setter and getter method are not initialized." @@ -36,7 +38,7 @@ RBAbstractInstanceVariableRefactoring >> abstractReferences [ using: replacer ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBAbstractInstanceVariableRefactoring >> accessorsRefactoring [ ^ accessorsRefactoring @@ -49,17 +51,17 @@ RBAbstractInstanceVariableRefactoring >> accessorsRefactoring [ ifNotNil: [ accessorsRefactoring ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractInstanceVariableRefactoring >> createAccessors [ self generateChangesFor: self accessorsRefactoring ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractInstanceVariableRefactoring >> preconditions [ ^ RBCondition directlyDefinesInstanceVariable: variableName in: class ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractInstanceVariableRefactoring >> privateTransform [ self createAccessors. self abstractReferences diff --git a/src/Refactoring-Core/RBAbstractTransformation.class.st b/src/Refactoring-Core/RBAbstractTransformation.class.st index ba1842011a5..f2ed117933d 100644 --- a/src/Refactoring-Core/RBAbstractTransformation.class.st +++ b/src/Refactoring-Core/RBAbstractTransformation.class.st @@ -1,6 +1,6 @@ Class { - #name : #RBAbstractTransformation, - #superclass : #Object, + #name : 'RBAbstractTransformation', + #superclass : 'Object', #instVars : [ 'model', 'options' @@ -8,28 +8,30 @@ Class { #classVars : [ 'RefactoringOptions' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #displaying } +{ #category : 'displaying' } RBAbstractTransformation class >> basicMenuItemString [ ^ self subclassResponsibility ] -{ #category : #cleanup } +{ #category : 'cleanup' } RBAbstractTransformation class >> cleanUp [ "RefactoringOptions holds on to blocks, we should make sure to recreate them so the block references the current method" self initializeRefactoringOptions ] -{ #category : #'class initialization' } +{ #category : 'class initialization' } RBAbstractTransformation class >> initialize [ self initializeRefactoringOptions ] -{ #category : #'private - initialization' } +{ #category : 'private - initialization' } RBAbstractTransformation class >> initializeRefactoringOptions [ RefactoringOptions := IdentityDictionary new. RefactoringOptions @@ -67,13 +69,13 @@ RBAbstractTransformation class >> initializeRefactoringOptions [ put: [ self error: #searchInWholeHierarchy ] ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractTransformation class >> isTransformation [ ^ false ] -{ #category : #displaying } +{ #category : 'displaying' } RBAbstractTransformation class >> menuItemString [ ^ (self isTransformation @@ -81,19 +83,19 @@ RBAbstractTransformation class >> menuItemString [ ifFalse: [ '' ]) , self basicMenuItemString ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation class >> refactoringOptions [ ^ RefactoringOptions ] -{ #category : #private } +{ #category : 'private' } RBAbstractTransformation >> buildSelectorString: aSelector [ aSelector numArgs = 0 ifTrue: [^aSelector]. ^self buildSelectorString: aSelector withPermuteMap: (1 to: aSelector numArgs) ] -{ #category : #private } +{ #category : 'private' } RBAbstractTransformation >> buildSelectorString: aSelector withPermuteMap: aPermutationCollection [ aSelector numArgs == 0 ifTrue: [^aSelector asString]. @@ -103,7 +105,7 @@ RBAbstractTransformation >> buildSelectorString: aSelector withPermuteMap: aPerm andNewArguments: #() ] -{ #category : #private } +{ #category : 'private' } RBAbstractTransformation >> buildSelectorString: aSelector withPermuteMap: aPermutationCollection andNewArguments: anArgumentsCollection [ | stream keywords | aSelector numArgs == 0 ifTrue: [^aSelector asString]. @@ -130,23 +132,23 @@ RBAbstractTransformation >> buildSelectorString: aSelector withPermuteMap: aPerm ^stream contents ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> changes [ ^ self model changes ] -{ #category : #'condition definitions' } +{ #category : 'condition definitions' } RBAbstractTransformation >> checkInstanceVariableName: aName in: aClass [ ^RBCondition checkInstanceVariableName: aName in: aClass ] -{ #category : #'condition definitions' } +{ #category : 'condition definitions' } RBAbstractTransformation >> checkMethodName: aName in: aClass [ ^RBCondition checkMethodName: aName in: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractTransformation >> checkPreconditions [ | conditions block | @@ -159,7 +161,7 @@ RBAbstractTransformation >> checkPreconditions [ ifNil: [ self refactoringError: conditions errorString ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractTransformation >> classExist [ | className | @@ -168,7 +170,7 @@ RBAbstractTransformation >> classExist [ errorString: 'Class named ' , className , ' does not exist' ] -{ #category : #private } +{ #category : 'private' } RBAbstractTransformation >> convertMethod: selector for: aClass using: searchReplacer [ "Convert the parse tree for selector using the searchReplacer. If a change is made then compile it into the changeBuilder." @@ -180,26 +182,26 @@ RBAbstractTransformation >> convertMethod: selector for: aClass using: searchRep ifTrue: [ aClass compileTree: searchReplacer tree ] ] -{ #category : #initialize } +{ #category : 'initialize' } RBAbstractTransformation >> defaultEnvironment [ ^ RBBrowserEnvironment new ] -{ #category : #'condition definitions' } +{ #category : 'condition definitions' } RBAbstractTransformation >> emptyCondition [ self deprecated: 'Use trueCondition' transformWith: '`@rec emptyCondition' -> '`@rec trueCondition'. ^ RBCondition true ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractTransformation >> execute [ "Check precondition, execute the transformation that produces changes and finally execute the changes" self generateChanges. self performChanges ] -{ #category : #executing } +{ #category : 'executing' } RBAbstractTransformation >> generateChanges [ "compatibility method RBRefactoring" @@ -210,7 +212,7 @@ RBAbstractTransformation >> generateChanges [ "RBRefactoringManager instance addRefactoring: self" ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> model [ ^ model @@ -221,63 +223,63 @@ RBAbstractTransformation >> model [ ifNotNil: [ model ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> model: aRBNamespace [ model := aRBNamespace ] -{ #category : #'To be removed' } +{ #category : 'To be removed' } RBAbstractTransformation >> openBrowserOn: anEnvironment [ ^ (self options at: #openBrowser) value: self value: anEnvironment ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> options [ ^ options ifNil: [ options := self class refactoringOptions copy ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> options: aDictionary [ options := aDictionary ] -{ #category : #parsing } +{ #category : 'parsing' } RBAbstractTransformation >> parseTreeRewriter [ ^ self parseTreeRewriterClass new ] -{ #category : #parsing } +{ #category : 'parsing' } RBAbstractTransformation >> parseTreeRewriterClass [ ^ RBParseTreeRewriter ] -{ #category : #parsing } +{ #category : 'parsing' } RBAbstractTransformation >> parseTreeSearcher [ ^ self parseTreeSearcherClass new ] -{ #category : #parsing } +{ #category : 'parsing' } RBAbstractTransformation >> parseTreeSearcherClass [ ^ RBParseTreeSearcher ] -{ #category : #parsing } +{ #category : 'parsing' } RBAbstractTransformation >> parserClass [ ^ RBParser ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractTransformation >> performChanges [ self performChanges: self changes ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractTransformation >> performChanges: aCompositeChange [ "Perform the changes contained in a composite change" @@ -286,7 +288,7 @@ RBAbstractTransformation >> performChanges: aCompositeChange [ addUndoPointer: RBRefactoryChangeManager nextCounter ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> poolVariableNamesFor: aClass [ | pools | pools := Set new. @@ -298,24 +300,24 @@ RBAbstractTransformation >> poolVariableNamesFor: aClass [ ^pools ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> poolVariableNamesIn: poolName [ ^(self model classNamed: poolName) classPool keys ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractTransformation >> preconditions [ self subclassResponsibility ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractTransformation >> privateTransform [ self subclassResponsibility ] -{ #category : #exceptions } +{ #category : 'exceptions' } RBAbstractTransformation >> refactoringConfirmWarning: aString [ | ret | ret := self uiManager @@ -324,44 +326,44 @@ RBAbstractTransformation >> refactoringConfirmWarning: aString [ ^ ret ] -{ #category : #exceptions } +{ #category : 'exceptions' } RBAbstractTransformation >> refactoringError: aString [ ^ RBRefactoringError signal: aString ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractTransformation >> refactoringErrorClass [ ^ RBRefactoringError ] -{ #category : #exceptions } +{ #category : 'exceptions' } RBAbstractTransformation >> refactoringWarning: aString [ ^ RBRefactoringWarning signal: aString ] -{ #category : #exceptions } +{ #category : 'exceptions' } RBAbstractTransformation >> refactoringWarning: aString with: aBlock [ ^ RBRefactoringWarning signal: aString with: aBlock ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> requestImplementorToInline: implementorsCollection [ ^(self options at: #implementorToInline) value: self value: implementorsCollection ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> requestMethodNameFor: aMethodName [ ^(self options at: #methodName) cull: aMethodName cull: self ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> requestSelfArgumentName [ ^(self options at: #selfArgumentName) value: self ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> selectVariableToMoveMethodTo: aSelector class: aClass [ ^(self options at: #selectVariableToMoveTo) value: self @@ -369,7 +371,7 @@ RBAbstractTransformation >> selectVariableToMoveMethodTo: aSelector class: aClas value: aSelector ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> selectVariableTypesFrom: initialTypeCollection selected: selectedTypeCollection [ ^ (self options at: #variableTypes) value: self @@ -377,17 +379,17 @@ RBAbstractTransformation >> selectVariableTypesFrom: initialTypeCollection selec value: selectedTypeCollection ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> shouldExtractAssignmentTo: aString [ ^(self options at: #extractAssignment) value: self value: aString ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> shouldInlineExpression: aString [ ^(self options at: #inlineExpression) value: self value: aString ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> shouldOverride: aSelector in: aClass [ ^(self options at: #alreadyDefined) value: self @@ -395,12 +397,12 @@ RBAbstractTransformation >> shouldOverride: aSelector in: aClass [ value: aSelector ] -{ #category : #requests } +{ #category : 'requests' } RBAbstractTransformation >> shouldUseExistingMethod: aSelector [ ^(self options at: #useExistingMethod) value: self value: aSelector ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractTransformation >> transform [ "Do the actual operations." self deprecated: 'Use generateChanges or privateTransform instead. Check subclasses for more details.'. @@ -408,7 +410,7 @@ RBAbstractTransformation >> transform [ self subclassResponsibility ] -{ #category : #'condition definitions' } +{ #category : 'condition definitions' } RBAbstractTransformation >> trueCondition [ ^ RBCondition true ] diff --git a/src/Refactoring-Core/RBAbstractVariablesRefactoring.class.st b/src/Refactoring-Core/RBAbstractVariablesRefactoring.class.st index 12c3912562a..8fc32089a99 100644 --- a/src/Refactoring-Core/RBAbstractVariablesRefactoring.class.st +++ b/src/Refactoring-Core/RBAbstractVariablesRefactoring.class.st @@ -5,8 +5,8 @@ access to accessor methods. For example RBMoveMethodRefactoring uses me. " Class { - #name : #RBAbstractVariablesRefactoring, - #superclass : #RBRefactoring, + #name : 'RBAbstractVariablesRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'tree', 'fromClass', @@ -17,10 +17,12 @@ Class { 'toClasses', 'ignore' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAbstractVariablesRefactoring class >> model: aRBModel abstractVariablesIn: aBRProgramNode from: fromBehavior toAll: behaviorCollection [ ^self model: aRBModel @@ -30,7 +32,7 @@ RBAbstractVariablesRefactoring class >> model: aRBModel abstractVariablesIn: aBR ignoring: nil ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAbstractVariablesRefactoring class >> model: aRBSmalltalk abstractVariablesIn: aBRProgramNode from: fromBehavior toAll: behaviorCollection ignoring: aVariableName [ ^ self new model: aRBSmalltalk; @@ -41,7 +43,7 @@ RBAbstractVariablesRefactoring class >> model: aRBSmalltalk abstractVariablesIn: yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> abstractClassVariable: aString [ | refactoring rewriter nonMetaClass | @@ -70,7 +72,7 @@ RBAbstractVariablesRefactoring >> abstractClassVariable: aString [ (rewriter executeTree: tree) ifTrue: [ tree := rewriter tree ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> abstractClassVariables [ | variables | (classVarReaders isEmpty and: [ classVarWriters isEmpty ]) @@ -82,7 +84,7 @@ RBAbstractVariablesRefactoring >> abstractClassVariables [ variables do: [ :each | self abstractClassVariable: each ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> abstractInstanceVariable: aString [ | refactoring rewriter | @@ -102,7 +104,7 @@ RBAbstractVariablesRefactoring >> abstractInstanceVariable: aString [ (rewriter executeTree: tree) ifTrue: [ tree := rewriter tree ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> abstractInstanceVariables [ | variables | (instVarReaders isEmpty and: [ instVarWriters isEmpty ]) @@ -114,7 +116,7 @@ RBAbstractVariablesRefactoring >> abstractInstanceVariables [ variables do: [ :each | self abstractInstanceVariable: each ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBAbstractVariablesRefactoring >> abstractVariablesIn: aBRProgramNode from: fromBehavior toAll: behaviorCollection ignoring: aVariableName [ | poolRefactoring | tree := aBRProgramNode. @@ -131,14 +133,14 @@ RBAbstractVariablesRefactoring >> abstractVariablesIn: aBRProgramNode from: from self computeVariablesToAbstract ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> classVariableNames [ | nonMetaClass | nonMetaClass := fromClass instanceSide. ^ (nonMetaClass allClassVariableNames collect: [ :each | each asString ]) asSet ] -{ #category : #'for driver' } +{ #category : 'for driver' } RBAbstractVariablesRefactoring >> computeVariablesToAbstract [ "should probably be moved to a driver" @@ -157,28 +159,28 @@ RBAbstractVariablesRefactoring >> computeVariablesToAbstract [ self removeDefinedClassVariables ] -{ #category : #testing } +{ #category : 'testing' } RBAbstractVariablesRefactoring >> hasVariablesToAbstract [ ^ instVarReaders notEmpty or: [ instVarWriters notEmpty or: [ classVarReaders notEmpty or: [ classVarWriters notEmpty ] ] ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> instanceVariableNames [ ^fromClass allInstanceVariableNames asSet ] -{ #category : #accessing } +{ #category : 'accessing' } RBAbstractVariablesRefactoring >> parseTree [ ^tree ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAbstractVariablesRefactoring >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBAbstractVariablesRefactoring >> privateTransform [ self hasVariablesToAbstract ifTrue: @@ -189,7 +191,7 @@ RBAbstractVariablesRefactoring >> privateTransform [ self abstractClassVariables ] -{ #category : #'for driver' } +{ #category : 'for driver' } RBAbstractVariablesRefactoring >> processAssignmentNode: aNode [ | varName | varName := aNode variable name. @@ -201,7 +203,7 @@ RBAbstractVariablesRefactoring >> processAssignmentNode: aNode [ ifTrue: [classVarWriters add: varName] ] -{ #category : #'for driver' } +{ #category : 'for driver' } RBAbstractVariablesRefactoring >> processReferenceNode: aNode [ | varName | varName := aNode name. @@ -213,7 +215,7 @@ RBAbstractVariablesRefactoring >> processReferenceNode: aNode [ ifTrue: [classVarReaders add: varName] ] -{ #category : #'for driver' } +{ #category : 'for driver' } RBAbstractVariablesRefactoring >> removeDefinedClassVariables [ | selectionBlock nonMetaClass | diff --git a/src/Refactoring-Core/RBAddClassVariableRefactoring.class.st b/src/Refactoring-Core/RBAddClassVariableRefactoring.class.st index 6deee9aed15..4fa0c0c6d76 100644 --- a/src/Refactoring-Core/RBAddClassVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBAddClassVariableRefactoring.class.st @@ -4,12 +4,14 @@ I am a refactoring for adding new class variables. My precondition verifies that the variable name is valid, not yet used in the whole hierarchy and not a global name. " Class { - #name : #RBAddClassVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBAddClassVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddClassVariableRefactoring >> applicabilityPreconditions [ ^ (RBCondition isMetaclass: class) not @@ -17,7 +19,7 @@ RBAddClassVariableRefactoring >> applicabilityPreconditions [ & (RBCondition isGlobal: variableName in: self model) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddClassVariableRefactoring >> breakingChangePreconditions [ ^ (RBCondition @@ -25,13 +27,13 @@ RBAddClassVariableRefactoring >> breakingChangePreconditions [ definesVariable: variableName asString) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddClassVariableRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBAddClassVariableRefactoring >> privateTransform [ class addClassVariable: variableName ] diff --git a/src/Refactoring-Core/RBAddInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBAddInstanceVariableRefactoring.class.st index 3f66ca20de5..ba1dbf5c4d1 100644 --- a/src/Refactoring-Core/RBAddInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBAddInstanceVariableRefactoring.class.st @@ -4,31 +4,33 @@ I am a refactoring for adding new instance variables. My precondition verifies that the variable name is valid, not yet used in the whole hierarchy and not a global name. " Class { - #name : #RBAddInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBAddInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddInstanceVariableRefactoring >> applicabilityPreconditions [ ^ (RBCondition isValidInstanceVariableName: variableName for: class) & (RBCondition isGlobal: variableName in: self model) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddInstanceVariableRefactoring >> breakingChangePreconditions [ ^ (RBCondition hierarchyOf: class definesVariable: variableName) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddInstanceVariableRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBAddInstanceVariableRefactoring >> privateTransform [ class addInstanceVariable: variableName ] diff --git a/src/Refactoring-Core/RBAddMethodRefactoring.class.st b/src/Refactoring-Core/RBAddMethodRefactoring.class.st index 5a1bd5eb940..2d3f5a25f13 100644 --- a/src/Refactoring-Core/RBAddMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBAddMethodRefactoring.class.st @@ -22,17 +22,19 @@ My preconditions also verify that `RBAddMethodTransformRefactoring` precondition " Class { - #name : #RBAddMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBAddMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'transformation', 'source', 'protocol' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAddMethodRefactoring class >> model: aRBSmalltalk sourceCode: aString in: aClass withProtocol: aProtocol [ ^ self new model: aRBSmalltalk; @@ -42,7 +44,7 @@ RBAddMethodRefactoring class >> model: aRBSmalltalk sourceCode: aString in: aCla yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAddMethodRefactoring class >> sourceCode: aString in: aClass withProtocol: aProtocol [ ^ self new sourceCode: aString @@ -50,7 +52,7 @@ RBAddMethodRefactoring class >> sourceCode: aString in: aClass withProtocol: aPr withProtocol: aProtocol ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddMethodRefactoring >> preconditions [ transformation checkPreconditions. @@ -58,13 +60,13 @@ RBAddMethodRefactoring >> preconditions [ ^ (RBCondition canUnderstand: transformation selector in: class) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBAddMethodRefactoring >> privateTransform [ transformation privateTransform ] -{ #category : #initialization } +{ #category : 'initialization' } RBAddMethodRefactoring >> sourceCode: aString in: aClass withProtocol: aProtocol [ class := self classObjectFor: aClass. source := aString. @@ -76,7 +78,7 @@ RBAddMethodRefactoring >> sourceCode: aString in: aClass withProtocol: aProtocol withProtocol: aProtocol ] -{ #category : #printing } +{ #category : 'printing' } RBAddMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBAddParameterRefactoring.class.st b/src/Refactoring-Core/RBAddParameterRefactoring.class.st index 798b3dda1e7..b83defab41e 100644 --- a/src/Refactoring-Core/RBAddParameterRefactoring.class.st +++ b/src/Refactoring-Core/RBAddParameterRefactoring.class.st @@ -12,16 +12,18 @@ This refactoring will - replace every sender of the prior method with the new one, using the specified default argument. " Class { - #name : #RBAddParameterRefactoring, - #superclass : #RBChangeMethodNameRefactoring, + #name : 'RBAddParameterRefactoring', + #superclass : 'RBChangeMethodNameRefactoring', #instVars : [ 'newArgs', 'senders' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAddParameterRefactoring class >> addParameterToMethod: aSelector in: aClass newSelector: newSelector permutation: aColl1 newArgs: aColl2 [ ^ self new addParameterToMethod: aSelector @@ -31,7 +33,7 @@ RBAddParameterRefactoring class >> addParameterToMethod: aSelector in: aClass ne newArgs: aColl2 ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBAddParameterRefactoring class >> model: aRBSmalltalk addParameterToMethod: aSelector in: aClass newSelector: newSelector permutation: aColl1 newArgs: aColl2 [ ^ self new model: aRBSmalltalk; @@ -43,7 +45,7 @@ RBAddParameterRefactoring class >> model: aRBSmalltalk addParameterToMethod: aSe yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBAddParameterRefactoring >> addParameterToMethod: aSelector in: aClass newSelector: newSel permutation: aColl1 newArgs: aColl2 [ self renameMethod: aSelector @@ -53,7 +55,7 @@ RBAddParameterRefactoring >> addParameterToMethod: aSelector in: aClass newSelec newArgs := aColl2 ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddParameterRefactoring >> checkSendersAccessTo: name [ (#('self' 'super') includes: name) ifTrue: [ ^ self ]. @@ -67,7 +69,7 @@ RBAddParameterRefactoring >> checkSendersAccessTo: name [ with: violatorClass) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddParameterRefactoring >> checkVariableReferencesIn: aParseTree [ | searcher | @@ -81,7 +83,7 @@ RBAddParameterRefactoring >> checkVariableReferencesIn: aParseTree [ searcher executeTree: aParseTree ] -{ #category : #private } +{ #category : 'private' } RBAddParameterRefactoring >> modifyImplementorParseTree: parseTree in: aClass [ | argNames index | argNames := newArgs collect: [ :arg | | newArg | @@ -97,7 +99,7 @@ RBAddParameterRefactoring >> modifyImplementorParseTree: parseTree in: aClass [ self renameArgumentsIn: parseTree ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddParameterRefactoring >> myConditions [ ^RBCondition withBlock: [oldSelector numArgs < newSelector numArgs @@ -108,12 +110,12 @@ RBAddParameterRefactoring >> myConditions [ true] ] -{ #category : #accessing } +{ #category : 'accessing' } RBAddParameterRefactoring >> newArgs [ ^ newArgs ifNil: [ newArgs := { } ] ] -{ #category : #action } +{ #category : 'action' } RBAddParameterRefactoring >> renameArgumentsIn: parseTree [ | newArgNames | newArgNames := newArgs collect: [ :arg | arg name ]. @@ -123,7 +125,7 @@ RBAddParameterRefactoring >> renameArgumentsIn: parseTree [ ] ] ] -{ #category : #private } +{ #category : 'private' } RBAddParameterRefactoring >> safeVariableNameFor: aClass temporaries: allTempVars [ | baseString index newString | newString := baseString := 'anObject'. @@ -137,7 +139,7 @@ RBAddParameterRefactoring >> safeVariableNameFor: aClass temporaries: allTempVar ^newString ] -{ #category : #private } +{ #category : 'private' } RBAddParameterRefactoring >> safeVariableNamed: argName for: aClass temporaries: allTempVars [ | baseString index newString | ((allTempVars includes: argName) @@ -153,7 +155,7 @@ RBAddParameterRefactoring >> safeVariableNamed: argName for: aClass temporaries: ^newString ] -{ #category : #private } +{ #category : 'private' } RBAddParameterRefactoring >> senders [ senders @@ -163,7 +165,7 @@ RBAddParameterRefactoring >> senders [ ^ senders ] -{ #category : #printing } +{ #category : 'printing' } RBAddParameterRefactoring >> storeOn: aStream [ aStream nextPut: $(. aStream nextPutAll: self class name. @@ -183,7 +185,7 @@ RBAddParameterRefactoring >> storeOn: aStream [ nextPutAll: ''')' ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBAddParameterRefactoring >> verifyInitializationExpressionOf: initializer [ | tree | tree := self parserClass diff --git a/src/Refactoring-Core/RBApplicabilityChecksFailedError.class.st b/src/Refactoring-Core/RBApplicabilityChecksFailedError.class.st index 7dec5846c76..40140707155 100644 --- a/src/Refactoring-Core/RBApplicabilityChecksFailedError.class.st +++ b/src/Refactoring-Core/RBApplicabilityChecksFailedError.class.st @@ -2,7 +2,9 @@ I represent an Error that is signaled when applicability checks are not met. " Class { - #name : #RBApplicabilityChecksFailedError, - #superclass : #RBRefactoringError, - #category : #'Refactoring-Core-Support' + #name : 'RBApplicabilityChecksFailedError', + #superclass : 'RBRefactoringError', + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } diff --git a/src/Refactoring-Core/RBArgumentName.class.st b/src/Refactoring-Core/RBArgumentName.class.st index cfaccf83bdb..21393f9e7ac 100644 --- a/src/Refactoring-Core/RBArgumentName.class.st +++ b/src/Refactoring-Core/RBArgumentName.class.st @@ -1,6 +1,6 @@ Class { - #name : #RBArgumentName, - #superclass : #Object, + #name : 'RBArgumentName', + #superclass : 'Object', #instVars : [ 'name', 'newName', @@ -8,93 +8,95 @@ Class { 'canBeRemoved', 'canBeRenamed' ], - #category : #'Refactoring-Core-Support' + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBArgumentName class >> name: aString [ ^ self new name: aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBArgumentName class >> name: aString value: anObject [ ^self new name: aString; value: anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> argValue [ ^ value ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> canBeRemoved [ ^ canBeRemoved ifNil: [ canBeRemoved := true ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> canBeRemoved: anObject [ canBeRemoved := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> canBeRenamed [ ^ canBeRenamed ifNil: [ canBeRenamed := true ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> canBeRenamed: anObject [ canBeRenamed := anObject ] -{ #category : #testing } +{ #category : 'testing' } RBArgumentName >> hasNewName [ ^ self name ~= self newName ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> name [ ^ name ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> name: anObject [ name := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> newName [ ^ newName ifNil: [ newName := name ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> newName: anObject [ newName := anObject ] -{ #category : #printing } +{ #category : 'printing' } RBArgumentName >> printOn: aStream [ aStream nextPutAll: self newName ] -{ #category : #printing } +{ #category : 'printing' } RBArgumentName >> storeOn: aStream [ aStream ] -{ #category : #accessing } +{ #category : 'accessing' } RBArgumentName >> value: anObject [ value := anObject diff --git a/src/Refactoring-Core/RBBreakingChangeChecksFailedWarning.class.st b/src/Refactoring-Core/RBBreakingChangeChecksFailedWarning.class.st index 31336c6f7e8..1ee763852ee 100644 --- a/src/Refactoring-Core/RBBreakingChangeChecksFailedWarning.class.st +++ b/src/Refactoring-Core/RBBreakingChangeChecksFailedWarning.class.st @@ -2,7 +2,9 @@ I represent a Warning that is signaled when breaking change checks are not met. " Class { - #name : #RBBreakingChangeChecksFailedWarning, - #superclass : #RBRefactoringWarning, - #category : #'Refactoring-Core-Support' + #name : 'RBBreakingChangeChecksFailedWarning', + #superclass : 'RBRefactoringWarning', + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } diff --git a/src/Refactoring-Core/RBBrowserEnvironment.extension.st b/src/Refactoring-Core/RBBrowserEnvironment.extension.st index 2d9e6b1037d..f0d317686ef 100644 --- a/src/Refactoring-Core/RBBrowserEnvironment.extension.st +++ b/src/Refactoring-Core/RBBrowserEnvironment.extension.st @@ -1,6 +1,6 @@ -Extension { #name : #RBBrowserEnvironment } +Extension { #name : 'RBBrowserEnvironment' } -{ #category : #'*Refactoring-Core' } +{ #category : '*Refactoring-Core' } RBBrowserEnvironment >> classesInPackages: aColl do: aBlock [ self systemDictionaryClassesDo: [ :aClass | diff --git a/src/Refactoring-Core/RBChangeMethodNameRefactoring.class.st b/src/Refactoring-Core/RBChangeMethodNameRefactoring.class.st index f1e126b55e9..a05dd75a8b7 100644 --- a/src/Refactoring-Core/RBChangeMethodNameRefactoring.class.st +++ b/src/Refactoring-Core/RBChangeMethodNameRefactoring.class.st @@ -11,8 +11,8 @@ Every concrete subclass has to add its own precondition (see `myPrecondition`). " Class { - #name : #RBChangeMethodNameRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBChangeMethodNameRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'newSelector', 'oldSelector', @@ -20,16 +20,18 @@ Class { 'implementors', 'renameMap' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBChangeMethodNameRefactoring class >> isAbstract [ ^ self == RBChangeMethodNameRefactoring ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBChangeMethodNameRefactoring >> doesNotOverrideExistingMethodPrecondition [ "Check that the new selector is not already defined in superclasses" @@ -39,7 +41,7 @@ RBChangeMethodNameRefactoring >> doesNotOverrideExistingMethodPrecondition [ condition & (RBCondition hierarchyOf: each canUnderstand: newSelector) not ] ] -{ #category : #testing } +{ #category : 'testing' } RBChangeMethodNameRefactoring >> hasPermutedArguments [ oldSelector numArgs = newSelector numArgs ifFalse: [^true]. 1 to: oldSelector numArgs @@ -47,60 +49,60 @@ RBChangeMethodNameRefactoring >> hasPermutedArguments [ ^false ] -{ #category : #private } +{ #category : 'private' } RBChangeMethodNameRefactoring >> implementors [ implementors ifNil: [ implementors := self model allImplementorsOf: oldSelector ]. ^ implementors ] -{ #category : #testing } +{ #category : 'testing' } RBChangeMethodNameRefactoring >> implementorsCanBePrimitives [ ^false ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBChangeMethodNameRefactoring >> isValidMethodNamePrecondition [ ^ (RBCondition isValidMethodName: newSelector for: class) ] -{ #category : #private } +{ #category : 'private' } RBChangeMethodNameRefactoring >> modifyImplementorParseTree: parseTree in: aClass [ | oldArgs | oldArgs := parseTree arguments. parseTree renameSelector: newSelector andArguments: (permutation collect: [:each | oldArgs at: each]) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBChangeMethodNameRefactoring >> myConditions [ "^self subclassResponsibility" ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBChangeMethodNameRefactoring >> newArgs [ ^ OrderedCollection new ] -{ #category : #accessing } +{ #category : 'accessing' } RBChangeMethodNameRefactoring >> newSelector [ ^ newSelector ] -{ #category : #accessing } +{ #category : 'accessing' } RBChangeMethodNameRefactoring >> newSelector: aSymbol [ newSelector := aSymbol ] -{ #category : #accessing } +{ #category : 'accessing' } RBChangeMethodNameRefactoring >> permutation: anObject [ permutation := anObject ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBChangeMethodNameRefactoring >> preconditions [ "This refactoring only preserves behavior if all implementors are renamed." @@ -112,14 +114,14 @@ RBChangeMethodNameRefactoring >> preconditions [ ^ conditions & self doesNotOverrideExistingMethodPrecondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBChangeMethodNameRefactoring >> privateTransform [ self renameImplementors. self replaceMessageSends. self removeRenamedImplementors ] -{ #category : #transforming } +{ #category : 'transforming' } RBChangeMethodNameRefactoring >> removeRenamedImplementors [ oldSelector = newSelector ifTrue: [ ^ self ]. @@ -127,14 +129,14 @@ RBChangeMethodNameRefactoring >> removeRenamedImplementors [ do: [ :each | each removeMethod: oldSelector ] ] -{ #category : #action } +{ #category : 'action' } RBChangeMethodNameRefactoring >> renameArgumentsIn: parseTree [ self renameMap do: [ :arg | (self parseTreeRewriterClass rename: arg name to: arg newName) executeTree: parseTree ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBChangeMethodNameRefactoring >> renameImplementors [ self implementors @@ -155,17 +157,17 @@ RBChangeMethodNameRefactoring >> renameImplementors [ ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBChangeMethodNameRefactoring >> renameMap [ ^renameMap ifNil: [ renameMap := { } ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBChangeMethodNameRefactoring >> renameMap: aColl [ renameMap := aColl ] -{ #category : #initialization } +{ #category : 'initialization' } RBChangeMethodNameRefactoring >> renameMethod: aSelector in: aClass [ "Watch out this is for partial configuration of the refactoring" @@ -174,7 +176,7 @@ RBChangeMethodNameRefactoring >> renameMethod: aSelector in: aClass [ ] -{ #category : #initialization } +{ #category : 'initialization' } RBChangeMethodNameRefactoring >> renameMethod: aSelector in: aClass to: newSel permutation: aMap [ self renameMethod: aSelector asSymbol in: aClass. @@ -182,7 +184,7 @@ RBChangeMethodNameRefactoring >> renameMethod: aSelector in: aClass to: newSel p permutation := aMap ] -{ #category : #transforming } +{ #category : 'transforming' } RBChangeMethodNameRefactoring >> replaceMessageSends [ self generateChangesFor: (RBReplaceMessageSendTransformation diff --git a/src/Refactoring-Core/RBChildrenToSiblingsRefactoring.class.st b/src/Refactoring-Core/RBChildrenToSiblingsRefactoring.class.st index 3c44807da77..749024082a3 100644 --- a/src/Refactoring-Core/RBChildrenToSiblingsRefactoring.class.st +++ b/src/Refactoring-Core/RBChildrenToSiblingsRefactoring.class.st @@ -21,16 +21,18 @@ Any method and instance variables, defined in ClassS and used by the new siblin " Class { - #name : #RBChildrenToSiblingsRefactoring, - #superclass : #RBClassRefactoring, + #name : 'RBChildrenToSiblingsRefactoring', + #superclass : 'RBClassRefactoring', #instVars : [ 'parent', 'subclasses' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBChildrenToSiblingsRefactoring class >> model: aRBSmalltalk name: aClassName class: aClass subclasses: subclassCollection [ ^ self new model: aRBSmalltalk; @@ -40,7 +42,7 @@ RBChildrenToSiblingsRefactoring class >> model: aRBSmalltalk name: aClassName cl yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBChildrenToSiblingsRefactoring class >> name: aClassName class: aClass subclasses: subclassCollection [ ^ self new name: aClassName @@ -49,12 +51,12 @@ RBChildrenToSiblingsRefactoring class >> name: aClassName class: aClass subclass yourself ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBChildrenToSiblingsRefactoring >> abstractSuperclass [ ^self model classNamed: className asSymbol ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> addSuperclass [ self generateChangesFor: (RBInsertNewClassRefactoring model: self model @@ -64,7 +66,7 @@ RBChildrenToSiblingsRefactoring >> addSuperclass [ category: parent category) ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> changeIsKindOfReferences [ | replacer | replacer := self parseTreeRewriter. @@ -73,7 +75,7 @@ RBChildrenToSiblingsRefactoring >> changeIsKindOfReferences [ self convertAllReferencesToClass: parent using: replacer ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> computeSubclassSupersOf: aClass [ | selectors | selectors := Set new. @@ -84,7 +86,7 @@ RBChildrenToSiblingsRefactoring >> computeSubclassSupersOf: aClass [ ^selectors ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> createSubclassResponsibilityFor: aSelector in: aClass [ | source | @@ -100,7 +102,7 @@ RBChildrenToSiblingsRefactoring >> createSubclassResponsibilityFor: aSelector in withProtocol: (aClass protocolsFor: aSelector)) ] -{ #category : #initialization } +{ #category : 'initialization' } RBChildrenToSiblingsRefactoring >> name: aClassName class: aClass subclasses: subclassCollection [ className := aClassName asSymbol. parent := self model classFor: aClass. @@ -108,7 +110,7 @@ RBChildrenToSiblingsRefactoring >> name: aClassName class: aClass subclasses: su collect: [:each | self model classFor: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBChildrenToSiblingsRefactoring >> preconditions [ ^subclasses inject: ((RBCondition isMetaclass: parent) @@ -123,7 +125,7 @@ RBChildrenToSiblingsRefactoring >> preconditions [ & (RBCondition isImmediateSubclass: each of: parent)] ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> privateTransform [ self addSuperclass; @@ -133,7 +135,7 @@ RBChildrenToSiblingsRefactoring >> privateTransform [ reparentSubclasses ] -{ #category : #'private - variables' } +{ #category : 'private - variables' } RBChildrenToSiblingsRefactoring >> pullUpClassInstanceVariables [ | newSuperclass | newSuperclass := self abstractSuperclass classSide. @@ -145,7 +147,7 @@ RBChildrenToSiblingsRefactoring >> pullUpClassInstanceVariables [ class: newSuperclass) ] ] -{ #category : #'private - variables' } +{ #category : 'private - variables' } RBChildrenToSiblingsRefactoring >> pullUpClassVariables [ | newSuperclass | newSuperclass := self abstractSuperclass. @@ -157,7 +159,7 @@ RBChildrenToSiblingsRefactoring >> pullUpClassVariables [ class: newSuperclass)] ] -{ #category : #'private - variables' } +{ #category : 'private - variables' } RBChildrenToSiblingsRefactoring >> pullUpInstanceVariables [ | newSuperclass | newSuperclass := self abstractSuperclass. @@ -169,13 +171,13 @@ RBChildrenToSiblingsRefactoring >> pullUpInstanceVariables [ class: newSuperclass)] ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> pullUpMethods [ self pushUpMethodsFrom: parent. self pushUpMethodsFrom: parent classSide ] -{ #category : #'private - variables' } +{ #category : 'private - variables' } RBChildrenToSiblingsRefactoring >> pullUpPoolVariables [ "Don't remove the pool variables from the subclass since they might be referenced there." @@ -185,7 +187,7 @@ RBChildrenToSiblingsRefactoring >> pullUpPoolVariables [ do: [:each | newSuperclass addPoolDictionary: each] ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> pushUp: aSelector in: aClass [ | source | @@ -199,7 +201,7 @@ RBChildrenToSiblingsRefactoring >> pushUp: aSelector in: aClass [ withProtocol: (aClass protocolsFor: aSelector)) ] ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> pushUpMethodsFrom: aClass [ | selectorsToPushUp | selectorsToPushUp := self selectorsToPushUpFrom: aClass. @@ -211,7 +213,7 @@ RBChildrenToSiblingsRefactoring >> pushUpMethodsFrom: aClass [ selectorsToPushUp do: [:each | aClass removeMethod: each] ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> pushUpVariables [ self pullUpInstanceVariables. self pullUpClassInstanceVariables. @@ -219,12 +221,12 @@ RBChildrenToSiblingsRefactoring >> pushUpVariables [ self pullUpPoolVariables ] -{ #category : #transforming } +{ #category : 'transforming' } RBChildrenToSiblingsRefactoring >> reparentSubclasses [ self model reparentClasses: subclasses to: self abstractSuperclass ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> selectorsToPushUpFrom: aClass [ | superSelectors | superSelectors := self computeSubclassSupersOf: aClass. @@ -233,7 +235,7 @@ RBChildrenToSiblingsRefactoring >> selectorsToPushUpFrom: aClass [ (superSelectors includes: each) or: [self shouldPushUp: each from: aClass]] ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> shouldPushUp: aSelector from: aClass [ ^ (aClass isMeta ifTrue: [ subclasses collect: [ :each | each classSide ] ] @@ -241,7 +243,7 @@ RBChildrenToSiblingsRefactoring >> shouldPushUp: aSelector from: aClass [ anySatisfy: [ :each | (each directlyDefinesMethod: aSelector) not ] ] -{ #category : #printing } +{ #category : 'printing' } RBChildrenToSiblingsRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -255,7 +257,7 @@ RBChildrenToSiblingsRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #'private - methods' } +{ #category : 'private - methods' } RBChildrenToSiblingsRefactoring >> subclassResponsibilityFor: aSelector in: aClass [ | methodNode position source | source := aClass sourceCodeFor: aSelector. diff --git a/src/Refactoring-Core/RBClass.class.st b/src/Refactoring-Core/RBClass.class.st index e0bd0330a23..19188be2551 100644 --- a/src/Refactoring-Core/RBClass.class.st +++ b/src/Refactoring-Core/RBClass.class.st @@ -7,8 +7,8 @@ I shouldn't be created directly, but always be part of a refactoring namespace. My namespace usally knows me and my meta class. " Class { - #name : #RBClass, - #superclass : #RBAbstractClass, + #name : 'RBClass', + #superclass : 'RBAbstractClass', #instVars : [ 'classVariableNames', 'poolDictionaryNames', @@ -19,17 +19,19 @@ Class { #classVars : [ 'LookupComment' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBClass class >> existingNamed: aSymbol [ ^(self named: aSymbol) realName: aSymbol; yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBClass class >> existingNamed: aSymbol model: aRBNamespace [ ^ (self named: aSymbol) model: aRBNamespace; @@ -37,38 +39,38 @@ RBClass class >> existingNamed: aSymbol model: aRBNamespace [ yourself ] -{ #category : #'class initialization' } +{ #category : 'class initialization' } RBClass class >> initialize [ LookupComment := Object new ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBClass class >> named: aSymbol [ ^(self new) name: aSymbol; yourself ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> addClassVariable: aString [ self privateClassVariableNames add: aString asSymbol. model addClassVariable: aString to: self. self classPool at: aString put: nil ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> addPoolDictionary: aString [ self privatePoolDictionaryNames add: aString asSymbol. model addPool: aString to: self ] -{ #category : #adding } +{ #category : 'adding' } RBClass >> addProtocolNamed: aString [ model addProtocolNamed: aString in: self ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> allClassVariableNames [ | sprClass | @@ -78,7 +80,7 @@ RBClass >> allClassVariableNames [ ifNotNil: [ sprClass allClassVariableNames , self classVariableNames ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> allPoolDictionaryNames [ | sprClass | @@ -88,7 +90,7 @@ RBClass >> allPoolDictionaryNames [ ifNotNil: [ sprClass allPoolDictionaryNames , self sharedPoolNames ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> category [ ^ category @@ -99,29 +101,29 @@ RBClass >> category [ ifNotNil: [ category ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> category: aSymbol [ category := aSymbol ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> classPool [ ^classPool ifNil: [ classPool := Dictionary new ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> classVariableNames [ ^self privateClassVariableNames copy ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> classVariableNames: aCollectionOfStrings [ classVariableNames := (aCollectionOfStrings collect: [:each | self classPool at: each asSymbol put: nil. each asSymbol]) asOrderedCollection ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> comment [ ^ comment = LookupComment ifTrue: [ @@ -131,12 +133,12 @@ RBClass >> comment [ ifFalse: [ comment ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> comment: aString [ self model changes comment: (comment := aString) in: self ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> definitionString [ ^ String streamContents: @@ -179,30 +181,30 @@ RBClass >> definitionString [ definitionStream nextPut: $' ] ] -{ #category : #testing } +{ #category : 'testing' } RBClass >> directlyDefinesClassVariable: aString [ ^self classVariableNames includes: aString asSymbol ] -{ #category : #testing } +{ #category : 'testing' } RBClass >> directlyDefinesPoolDictionary: aString [ ^self sharedPoolNames includes: aString asSymbol ] -{ #category : #initialization } +{ #category : 'initialization' } RBClass >> initialize [ super initialize. comment := LookupComment ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> instanceSide [ ^ self ] -{ #category : #testing } +{ #category : 'testing' } RBClass >> isEmptyClass [ ^ self classVariableNames isEmpty and: [ @@ -210,25 +212,25 @@ RBClass >> isEmptyClass [ self selectors isEmpty]] ] -{ #category : #testing } +{ #category : 'testing' } RBClass >> isMeta [ ^false ] -{ #category : #'self evaluating' } +{ #category : 'self evaluating' } RBClass >> isSelfEvaluating [ ^ true ] -{ #category : #testing } +{ #category : 'testing' } RBClass >> isSharedPool [ ^ (self allSuperclasses collect: [:each | each name]) includes: #SharedPool ] -{ #category : #querying } +{ #category : 'querying' } RBClass >> methodsUsingClassVariableNamed: aClassVariableName [ ^ (self realClass classVariableNamed: aClassVariableName) usingMethods collect: [ :aMethod | @@ -238,25 +240,25 @@ RBClass >> methodsUsingClassVariableNamed: aClassVariableName [ ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> poolDictionaryNames [ ^ self privatePoolDictionaryNames copy ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> poolDictionaryNames: aCollectionOfStrings [ poolDictionaryNames := (aCollectionOfStrings collect: [:each | each asSymbol]) asOrderedCollection ] -{ #category : #private } +{ #category : 'private' } RBClass >> privateClassVariableNames [ (self isDefined and: [classVariableNames isNil]) ifTrue: [self classVariableNames: self realClass classVarNames]. ^classVariableNames ] -{ #category : #private } +{ #category : 'private' } RBClass >> privatePoolDictionaryNames [ (self isDefined and: [poolDictionaryNames isNil]) ifTrue: @@ -265,35 +267,35 @@ RBClass >> privatePoolDictionaryNames [ ^poolDictionaryNames ] -{ #category : #initialization } +{ #category : 'initialization' } RBClass >> realName: aSymbol [ self realClass: (self model environment at: aSymbol) ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> removeClassVariable: aString [ self privateClassVariableNames remove: aString asSymbol. model removeClassVariable: aString from: self ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> removeClassVariable: aString ifAbsent: aBlock [ self privateClassVariableNames remove: aString asSymbol ifAbsent: aBlock. model removeClassVariable: aString from: self ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> removePoolDictionary: aString [ self privatePoolDictionaryNames remove: aString asSymbol ] -{ #category : #removing } +{ #category : 'removing' } RBClass >> removeProtocolNamed: aString [ model removeProtocolNamed: aString in: self ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBClass >> renameClassVariable: oldName to: newName around: aBlock [ self privateClassVariableNames at: (self privateClassVariableNames indexOf: oldName asSymbol) @@ -306,13 +308,13 @@ RBClass >> renameClassVariable: oldName to: newName around: aBlock [ around: aBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> sharedPoolNames [ ^self privatePoolDictionaryNames copy ] -{ #category : #accessing } +{ #category : 'accessing' } RBClass >> sharedPools [ ^ self allPoolDictionaryNames collect: [ :each | Smalltalk globals at: each asSymbol ifAbsent: [ Dictionary new ] ] ] diff --git a/src/Refactoring-Core/RBClassModelFactory.class.st b/src/Refactoring-Core/RBClassModelFactory.class.st index af2d07fe0b4..a37d2e8ee86 100644 --- a/src/Refactoring-Core/RBClassModelFactory.class.st +++ b/src/Refactoring-Core/RBClassModelFactory.class.st @@ -4,8 +4,8 @@ None of the classes inside this package should be directly accessed. They should I'm an important design point: I will let future evolution of the system to be experimented without the needs to change all the users. Then once the experiments and a good solution is found it may be the time to remove me and to think that I'm an overengineered solution. Right now I'm a change enabler. For example people can try to use Ring models to model RBmodel. " Class { - #name : #RBClassModelFactory, - #superclass : #Object, + #name : 'RBClassModelFactory', + #superclass : 'Object', #classVars : [ 'RBclass', 'RBmetaclass', @@ -15,130 +15,132 @@ Class { 'RBtrait', 'RBtraitMetaclass' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbClass [ ^ RBclass ifNil: [ RBclass := RBClass ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbMetaclass [ ^ RBmetaclass ifNil: [ RBmetaclass := RBMetaclass ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbMethod [ ^ RBmethod ifNil: [ RBmethod := RBMethod ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbNamespace [ ^ RBnamespace ifNil: [ RBnamespace := RBNamespace ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbPackage [ ^ RBpackage ifNil: [ RBpackage := RBPackage ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbTrait [ ^ RBtrait ifNil: [ RBtrait := RBTrait ] ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory class >> rbTraitMetaclass [ ^ RBtraitMetaclass ifNil: [ RBtraitMetaclass := RBTraitedMetaclass ] ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBClass: aClass [ RBclass := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBMetaclass: aClass [ RBmetaclass := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBMethod: aClass [ RBmethod := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBNamespace: aClass [ RBnamespace := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBPackage: aClass [ RBpackage := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBTrait: aClass [ RBtrait := aClass ] -{ #category : #'factory customisation' } +{ #category : 'factory customisation' } RBClassModelFactory class >> setRBTraitMetaclass: aClass [ RBtraitMetaclass := aClass ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbClass [ ^ self class rbClass ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbMetaclass [ ^ self class rbMetaclass ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbMethod [ ^ self class rbMethod ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbNamespace [ ^ self class rbNamespace ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbPackage [ ^ self class rbPackage ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbTrait [ ^ self class rbTrait ] -{ #category : #'factory access' } +{ #category : 'factory access' } RBClassModelFactory >> rbTraitMetaclass [ ^ self class rbTraitMetaclass diff --git a/src/Refactoring-Core/RBClassRefactoring.class.st b/src/Refactoring-Core/RBClassRefactoring.class.st index fc550377d0b..b6261c81c4c 100644 --- a/src/Refactoring-Core/RBClassRefactoring.class.st +++ b/src/Refactoring-Core/RBClassRefactoring.class.st @@ -9,26 +9,28 @@ Check method `RBClassRefactoring class>>#model:className:` " Class { - #name : #RBClassRefactoring, - #superclass : #RBRefactoring, + #name : 'RBClassRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'className' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBClassRefactoring class >> className: aName [ ^ self new className: aName ] -{ #category : #testing } +{ #category : 'testing' } RBClassRefactoring class >> isAbstract [ ^ self == RBClassRefactoring ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBClassRefactoring class >> model: aRBModel className: aName [ ^ self new model: aRBModel; @@ -36,7 +38,7 @@ RBClassRefactoring class >> model: aRBModel className: aName [ yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBClassRefactoring >> className: aName [ className := aName ] diff --git a/src/Refactoring-Core/RBClassRegexRefactoring.class.st b/src/Refactoring-Core/RBClassRegexRefactoring.class.st index d5e6cbb6beb..eb13e356b60 100644 --- a/src/Refactoring-Core/RBClassRegexRefactoring.class.st +++ b/src/Refactoring-Core/RBClassRegexRefactoring.class.st @@ -7,26 +7,28 @@ Refactored classes can be renamed, copied and kept aside old ones: try renameCla See also the comment of superclass for a nice script. " Class { - #name : #RBClassRegexRefactoring, - #superclass : #RBRegexRefactoring, + #name : 'RBClassRegexRefactoring', + #superclass : 'RBRegexRefactoring', #instVars : [ 'rootClass', 'mode' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #transforming } +{ #category : 'transforming' } RBClassRegexRefactoring >> copy: aClass name: aSymbol [ ^ self duplicate: aClass name: aSymbol deep: true ] -{ #category : #actions } +{ #category : 'actions' } RBClassRegexRefactoring >> copyClasses [ mode := #copy:name: ] -{ #category : #private } +{ #category : 'private' } RBClassRegexRefactoring >> copyFrom: aSourceClass to: aTargetClass [ aSourceClass instanceVariableNames do: [ :each | aTargetClass addInstanceVariable: each ]. @@ -43,17 +45,17 @@ RBClassRegexRefactoring >> copyFrom: aSourceClass to: aTargetClass [ withProtocol: (aSourceClass protocolsFor: each))] ] -{ #category : #transforming } +{ #category : 'transforming' } RBClassRegexRefactoring >> create: aClass name: aSymbol [ ^ self duplicate: aClass name: aSymbol deep: false ] -{ #category : #actions } +{ #category : 'actions' } RBClassRegexRefactoring >> createClasses [ mode := #create:name: ] -{ #category : #private } +{ #category : 'private' } RBClassRegexRefactoring >> duplicate: aClass name: aSymbol deep: aBoolean [ | superclass superclassName name class | (self model includesClassNamed: aSymbol) @@ -77,13 +79,13 @@ RBClassRegexRefactoring >> duplicate: aClass name: aSymbol deep: aBoolean [ ^ nil ] -{ #category : #initialization } +{ #category : 'initialization' } RBClassRegexRefactoring >> initialize [ super initialize. self createClasses ] -{ #category : #transforming } +{ #category : 'transforming' } RBClassRegexRefactoring >> privateTransform [ | replacement refactoring | self model allClassesDo: [ :class | @@ -96,7 +98,7 @@ RBClassRegexRefactoring >> privateTransform [ ifTrue: [ refactoring privateTransform ] ] ] ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBClassRegexRefactoring >> rename: aClass name: aSymbol [ ^ RBRenameClassRefactoring model: self model @@ -104,17 +106,17 @@ RBClassRegexRefactoring >> rename: aClass name: aSymbol [ to: aSymbol ] -{ #category : #actions } +{ #category : 'actions' } RBClassRegexRefactoring >> renameClasses [ mode := #rename:name: ] -{ #category : #accessing } +{ #category : 'accessing' } RBClassRegexRefactoring >> rootClass [ ^ rootClass ifNil: [ Object ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBClassRegexRefactoring >> rootClass: aClass [ rootClass := aClass instanceSide ] diff --git a/src/Refactoring-Core/RBCombinatorVisitor.class.st b/src/Refactoring-Core/RBCombinatorVisitor.class.st index ed95271166b..0db5eec84cd 100644 --- a/src/Refactoring-Core/RBCombinatorVisitor.class.st +++ b/src/Refactoring-Core/RBCombinatorVisitor.class.st @@ -2,25 +2,27 @@ I am a visitor to find differents combinations of sequences nodes " Class { - #name : #RBCombinatorVisitor, - #superclass : #RBProgramNodeVisitor, + #name : 'RBCombinatorVisitor', + #superclass : 'RBProgramNodeVisitor', #instVars : [ 'combinations' ], - #category : #'Refactoring-Core-Base' + #category : 'Refactoring-Core-Base', + #package : 'Refactoring-Core', + #tag : 'Base' } -{ #category : #accessing } +{ #category : 'accessing' } RBCombinatorVisitor >> combinations [ ^ combinations ] -{ #category : #initialization } +{ #category : 'initialization' } RBCombinatorVisitor >> initialize [ combinations := OrderedCollection new ] -{ #category : #visiting } +{ #category : 'visiting' } RBCombinatorVisitor >> visitSequenceNode: aSequenceNode [ | starts ends | starts := aSequenceNode statements collect: [ :node | node start ]. diff --git a/src/Refactoring-Core/RBCompositeContinuingRefactoring.class.st b/src/Refactoring-Core/RBCompositeContinuingRefactoring.class.st index 25b26823f97..9c3a4d002ab 100644 --- a/src/Refactoring-Core/RBCompositeContinuingRefactoring.class.st +++ b/src/Refactoring-Core/RBCompositeContinuingRefactoring.class.st @@ -2,12 +2,14 @@ I represent a sequence of refactorings but I will skip refactorings failing and execute as much as possible. " Class { - #name : #RBCompositeContinuingRefactoring, - #superclass : #RBCompositeRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBCompositeContinuingRefactoring', + #superclass : 'RBCompositeRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBCompositeContinuingRefactoring >> privateTransform [ refactorings do: [ :each | [ each generateChanges] on: RBRefactoringError do: [ :ex | ] ] diff --git a/src/Refactoring-Core/RBCompositeRefactoring.class.st b/src/Refactoring-Core/RBCompositeRefactoring.class.st index 26ff820e1a8..1de38ef55bd 100644 --- a/src/Refactoring-Core/RBCompositeRefactoring.class.st +++ b/src/Refactoring-Core/RBCompositeRefactoring.class.st @@ -3,27 +3,29 @@ I represent a sequence of refactorings that are executed one after the others. I will fail on the first one that fails. " Class { - #name : #RBCompositeRefactoring, - #superclass : #RBRefactoring, + #name : 'RBCompositeRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'refactorings' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBCompositeRefactoring >> applicabilityPreconditions [ ^ RBCondition true ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCompositeRefactoring >> breakingChangePreconditions [ ^ RBCondition true ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCompositeRefactoring >> generateChanges [ self applicabilityPreconditions check ifFalse: [ @@ -37,25 +39,25 @@ RBCompositeRefactoring >> generateChanges [ ^ self changes ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCompositeRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBCompositeRefactoring >> privateTransform [ refactorings do: [ :each | each generateChanges ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBCompositeRefactoring >> refactorings [ ^ refactorings ] -{ #category : #accessing } +{ #category : 'accessing' } RBCompositeRefactoring >> refactorings: aCollection [ refactorings := aCollection diff --git a/src/Refactoring-Core/RBCondition.class.st b/src/Refactoring-Core/RBCondition.class.st index 49c6930b4eb..049b711372d 100644 --- a/src/Refactoring-Core/RBCondition.class.st +++ b/src/Refactoring-Core/RBCondition.class.st @@ -14,16 +14,18 @@ Most users of me are refactoring operations and use my methods on the class side " Class { - #name : #RBCondition, - #superclass : #RBAbstractCondition, + #name : 'RBCondition', + #superclass : 'RBAbstractCondition', #instVars : [ 'block', 'errorBlock' ], - #category : #'Refactoring-Core-Conditions' + #category : 'Refactoring-Core-Conditions', + #package : 'Refactoring-Core', + #tag : 'Conditions' } -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBCondition class >> accessesClassVariable: variableName in: aClass showIn: aTransformation [ self flag: #popUp. @@ -43,7 +45,7 @@ RBCondition class >> accessesClassVariable: variableName in: aClass showIn: aTra true ] ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBCondition class >> accessesInstanceVariable: variableName in: aClass showIn: aTransformation [ | references | @@ -58,7 +60,7 @@ RBCondition class >> accessesInstanceVariable: variableName in: aClass showIn: a ^ references not ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> canUnderstand: aSelector in: aClass [ ^self new @@ -66,7 +68,7 @@ RBCondition class >> canUnderstand: aSelector in: aClass [ errorString: aClass printString , ' <1?:does not >understand<1?s:> ' , aSelector printString ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> checkClassVarName: aName in: aClass [ | string | aName isString ifFalse: [^false]. @@ -77,7 +79,7 @@ RBCondition class >> checkClassVarName: aName in: aClass [ ^RBScanner isVariable: string ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> checkInstanceVariableName: aName in: aClass [ | string | aName isString ifFalse: [^false]. @@ -88,14 +90,14 @@ RBCondition class >> checkInstanceVariableName: aName in: aClass [ ^RBScanner isVariable: string ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> checkMethodName: aString [ "Return whether the argument aName is can represent a selector" ^ aString isString and: [ aString isValidSelector ] ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> checkMethodName: aString in: aClass [ "Return whether the argument aName is can represent a selector" "You probably look for checkMethodName: since the second argument is ignored" @@ -103,7 +105,7 @@ RBCondition class >> checkMethodName: aString in: aClass [ ^aString isString and: [ aString isValidSelector ] ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesClassVariable: aString in: aClass [ ^self new block: [aClass definesClassVariable: aString] @@ -111,7 +113,7 @@ RBCondition class >> definesClassVariable: aString in: aClass [ , ' <1?:does not >define<1?s:> class variable ' , aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesInstanceVariable: aString in: aClass [ ^self new block: [aClass definesInstanceVariable: aString] @@ -119,14 +121,14 @@ RBCondition class >> definesInstanceVariable: aString in: aClass [ , ' <1?:does not >define<1?s:> instance variable ' , aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesSelector: aSelector in: aClass [ ^self new block: [aClass directlyDefinesMethod: aSelector] errorString: aClass printString , ' <1?:does not >define<1?s:> ' , aSelector printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesSelector: aSelector in: aClass orIsSimilarTo: rbMethod [ ^self new block: [(aClass directlyDefinesMethod: aSelector) @@ -136,7 +138,7 @@ RBCondition class >> definesSelector: aSelector in: aClass orIsSimilarTo: rbMeth errorString: aClass printString , ' <1?:does not >define<1?s:> ' , aSelector printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesTempVar: aString in: aClass ignoreClass: subclass [ | condition | @@ -159,7 +161,7 @@ RBCondition class >> definesTempVar: aString in: aClass ignoreClass: subclass [ ^ condition ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> definesTemporaryVariable: aString in: aClass [ | condition | @@ -181,7 +183,7 @@ RBCondition class >> definesTemporaryVariable: aString in: aClass [ ^ condition ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> directlyDefinesClassVariable: aString in: aClass [ ^self new block: [aClass directlyDefinesClassVariable: aString] @@ -189,7 +191,7 @@ RBCondition class >> directlyDefinesClassVariable: aString in: aClass [ , ' <1?:does not >directly define<1?s:> class variable ' , aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> directlyDefinesInstanceVariable: aString in: aClass [ ^self new block: [aClass directlyDefinesInstanceVariable: aString] @@ -197,7 +199,7 @@ RBCondition class >> directlyDefinesInstanceVariable: aString in: aClass [ , ' <1?:does not >directly define<1?s:> instance variable ' , aString ] -{ #category : #'variable accessing' } +{ #category : 'variable accessing' } RBCondition class >> doesNotAccessInstanceVariable: variableName inHierarchyOf: aClass showIn: aTransformation [ | references | @@ -212,42 +214,42 @@ RBCondition class >> doesNotAccessInstanceVariable: variableName inHierarchyOf: ^ references not ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> empty [ "Returns an empty condition" self deprecated: 'Use RBCondition true instead' transformWith: '`@rec empty' -> '`@ true'. ^ self true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hasSubclasses: aClass [ ^self new block: [aClass subclasses isNotEmpty ] errorString: aClass printString , ' has <1?:no >subclasses' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hasSubclasses: aClass excluding: classList [ ^self new block: [ ((aClass subclasses collect: [:each | each name]) copyWithoutAll: classList) isNotEmpty ] errorString: aClass printString , ' has <1?:no >subclasses' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hasSuperclass: aClass [ ^self new block: [aClass superclass isNil not] errorString: aClass printString , ' has <1?a:no> superclass' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hierarchyOf: aClass canUnderstand: aSelector [ ^self new block: [aClass hierarchyDefinesMethod: aSelector] errorString: aClass printString , ' <1? and/or part of it''s Hierarchy already: and/or part of it''s Hierarchy do not> understand<1?s:> ' , aSelector printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hierarchyOf: aClass definesVariable: aString [ ^self new block: [aClass hierarchyDefinesVariable: aString] @@ -256,7 +258,7 @@ RBCondition class >> hierarchyOf: aClass definesVariable: aString [ , aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hierarchyOf: aClass referencesInstanceVariable: aString [ ^ self new @@ -268,7 +270,7 @@ RBCondition class >> hierarchyOf: aClass referencesInstanceVariable: aString [ , '#' , aString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> hierarchyOf: aClass referencesSharedVariable: aString [ "Returns whether a shared variable is accessed anywhere in a class hierarchy, being it class or instance side." @@ -284,7 +286,7 @@ RBCondition class >> hierarchyOf: aClass referencesSharedVariable: aString [ , '#' , aString ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> invalidArgumentNamesForSelector: aSymbol in: aModel [ "Return the list of elements that when added as argument to a selector would break it e.g., an argument cannot have the same name as a instance variables or the same name as an already existing argument." @@ -298,7 +300,7 @@ RBCondition class >> invalidArgumentNamesForSelector: aSymbol in: aModel [ ^ invalidArgNames ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isAbstractClass: aClass [ ^ self new @@ -306,19 +308,19 @@ RBCondition class >> isAbstractClass: aClass [ errorString: aClass printString , ' is <1?:not >an abstract class' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isClass: anObject [ ^self new block: [anObject isBehavior] errorString: anObject printString , ' is <1?:not >a behavior' ] -{ #category : #testing } +{ #category : 'testing' } RBCondition class >> isClass: aRBClass definedIn: aRBNamespace [ ^ self isClassNamed: aRBClass name definedIn: aRBNamespace ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isClassNamed: className definedIn: aModel [ ^ self new @@ -328,7 +330,7 @@ RBCondition class >> isClassNamed: className definedIn: aModel [ errorString: [ className , ' is <1?:not > defined' ] ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isEmptyClass: anObject [ ^ self new @@ -339,7 +341,7 @@ RBCondition class >> isEmptyClass: anObject [ errorString: anObject printString , ' is <1?:not > empty' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isGlobal: aString in: aRBSmalltalk [ ^ self new @@ -347,7 +349,7 @@ RBCondition class >> isGlobal: aString in: aRBSmalltalk [ errorString: aString , ' is <1?:not >a class or global variable' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isImmediateSubclass: subclass of: superClass [ ^ self new @@ -357,7 +359,7 @@ RBCondition class >> isImmediateSubclass: subclass of: superClass [ , superClass printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isMetaclass: anObject [ ^ self new @@ -365,7 +367,7 @@ RBCondition class >> isMetaclass: anObject [ errorString: anObject printString , ' is <1?:not >a metaclass' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isSubclass: subclass of: superClass [ ^ self new @@ -374,7 +376,7 @@ RBCondition class >> isSubclass: subclass of: superClass [ , superClass printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isSymbol: aString [ ^ self new @@ -382,7 +384,7 @@ RBCondition class >> isSymbol: aString [ errorString: aString , ' is <1?:not >a symbol' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isValidClassName: aString [ ^ self new @@ -390,7 +392,7 @@ RBCondition class >> isValidClassName: aString [ errorString: aString , ' is <1?:not >a valid class name' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isValidClassVarName: aString for: aClass [ ^ self new @@ -398,7 +400,7 @@ RBCondition class >> isValidClassVarName: aString for: aClass [ errorString: aString , ' is <1?:not >a valid class variable name' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isValidInstanceVariableName: aString for: aClass [ ^ self new @@ -407,7 +409,7 @@ RBCondition class >> isValidInstanceVariableName: aString for: aClass [ aString , ' is <1?:not >a valid instance variable name' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> isValidMethodName: aString for: aClass [ ^ self new @@ -416,7 +418,7 @@ RBCondition class >> isValidMethodName: aString for: aClass [ aString printString , ' is <1?:not >a valid method name' ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> methodDefiningTemporary: aString in: aClass ignore: aBlock [ | searcher method | @@ -433,7 +435,7 @@ RBCondition class >> methodDefiningTemporary: aString in: aClass ignore: aBlock ^ nil ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> referencesInstanceVariable: aString in: aClass [ ^ self new @@ -443,12 +445,12 @@ RBCondition class >> referencesInstanceVariable: aString in: aClass [ , ' <1?:does not >reference<1?s:> instance variable ' , aString ] -{ #category : #utilities } +{ #category : 'utilities' } RBCondition class >> reservedNames [ ^#('self' 'true' 'false' 'nil' 'thisContext' 'super') ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> subclassesOf: aClass isDoingASuperSendFor: aSelector [ ^ self new @@ -463,7 +465,7 @@ RBCondition class >> subclassesOf: aClass isDoingASuperSendFor: aSelector [ , aSelector printString ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> true [ "Returns a true condition. It is useful when chaining condition. It acts as neutral element of the operation such AND." @@ -472,40 +474,40 @@ RBCondition class >> true [ errorString: 'true' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> withBlock: aBlock [ ^self new withBlock: aBlock ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCondition class >> withBlock: aBlock errorString: aString [ ^ self new block: aBlock errorString: aString ] -{ #category : #initialization } +{ #category : 'initialization' } RBCondition >> block: aBlock errorString: aString [ block := aBlock. self errorMacro: aString ] -{ #category : #checking } +{ #category : 'checking' } RBCondition >> check [ ^block value ] -{ #category : #initialization } +{ #category : 'initialization' } RBCondition >> errorBlock: anObject [ errorBlock := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBCondition >> errorBlockFor: aBoolean [ ^errorBlock ] -{ #category : #initialization } +{ #category : 'initialization' } RBCondition >> withBlock: aBlock [ block := aBlock ] diff --git a/src/Refactoring-Core/RBConjunctiveCondition.class.st b/src/Refactoring-Core/RBConjunctiveCondition.class.st index d6b4b301870..939e6d6435d 100644 --- a/src/Refactoring-Core/RBConjunctiveCondition.class.st +++ b/src/Refactoring-Core/RBConjunctiveCondition.class.st @@ -22,17 +22,19 @@ check ``` " Class { - #name : #RBConjunctiveCondition, - #superclass : #RBAbstractCondition, + #name : 'RBConjunctiveCondition', + #superclass : 'RBAbstractCondition', #instVars : [ 'left', 'right', 'failed' ], - #category : #'Refactoring-Core-Conditions' + #category : 'Refactoring-Core-Conditions', + #package : 'Refactoring-Core', + #tag : 'Conditions' } -{ #category : #checking } +{ #category : 'checking' } RBConjunctiveCondition >> check [ left check ifFalse: @@ -45,7 +47,7 @@ RBConjunctiveCondition >> check [ ^true ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> errorBlockFor: aBoolean [ ^aBoolean ifTrue: [nil] @@ -53,42 +55,42 @@ RBConjunctiveCondition >> errorBlockFor: aBoolean [ [failed = #leftFailed ifTrue: [left errorBlock] ifFalse: [right errorBlock]] ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> errorMacro [ ^ errorMacro ifNil: [ self longMacro ] ifNotNil: [ super errorMacro ] ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> errorStringFor: aBoolean [ ^ aBoolean ifTrue: [ self neitherFailed ] ifFalse: [ self perform: failed ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBConjunctiveCondition >> left: aCondition right: aCondition2 [ left := aCondition. right := aCondition2. failed := #unknownFailed ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> leftFailed [ ^left errorStringFor: false ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> longMacro [ ^'(' , left errorMacro , ') <1?AND:OR> (' , right errorMacro , ')' ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> neitherFailed [ ^(left errorStringFor: true) , ' AND ' , (right errorStringFor: true) ] -{ #category : #printing } +{ #category : 'printing' } RBConjunctiveCondition >> printOn: aStream [ aStream print: left; @@ -96,12 +98,12 @@ RBConjunctiveCondition >> printOn: aStream [ print: right ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> rightFailed [ ^right errorStringFor: false ] -{ #category : #private } +{ #category : 'private' } RBConjunctiveCondition >> unknownFailed [ ^(left errorStringFor: false) , ' OR ' , (right errorStringFor: false) ] diff --git a/src/Refactoring-Core/RBCopyClassRefactoring.class.st b/src/Refactoring-Core/RBCopyClassRefactoring.class.st index f56ec498f32..06461dc93a6 100644 --- a/src/Refactoring-Core/RBCopyClassRefactoring.class.st +++ b/src/Refactoring-Core/RBCopyClassRefactoring.class.st @@ -14,35 +14,37 @@ Example ``` " Class { - #name : #RBCopyClassRefactoring, - #superclass : #RBClassRefactoring, + #name : 'RBCopyClassRefactoring', + #superclass : 'RBClassRefactoring', #instVars : [ 'aClass', 'category' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring class >> copyClass: cls withName: aSymbol [ ^ self new copyClass: cls withName: aSymbol ] -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring class >> copyClass: cls withName: copyName in: aSymbol [ ^ self new category: aSymbol; copyClass: cls withName: copyName ] -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring class >> model: aRBSmalltalk copyClass: cls withName: aSymbol [ ^ self new model: aRBSmalltalk; copyClass: cls withName: aSymbol ] -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring class >> model: aRBSmalltalk copyClass: cls withName: copyName in: aSymbol [ ^ self new model: aRBSmalltalk; @@ -50,18 +52,18 @@ RBCopyClassRefactoring class >> model: aRBSmalltalk copyClass: cls withName: cop copyClass: cls withName: copyName ] -{ #category : #accessing } +{ #category : 'accessing' } RBCopyClassRefactoring >> category [ ^ category ifNil: [ category := aClass category ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBCopyClassRefactoring >> category: aSymbol [ category := aSymbol ] -{ #category : #transforming } +{ #category : 'transforming' } RBCopyClassRefactoring >> copyClass [ self generateChangesFor: (RBInsertNewClassRefactoring model: self model @@ -72,13 +74,13 @@ RBCopyClassRefactoring >> copyClass [ comment: aClass comment) ] -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring >> copyClass: cls withName: aName [ self className: aName. aClass := self classObjectFor: cls ] -{ #category : #transforming } +{ #category : 'transforming' } RBCopyClassRefactoring >> copyMethods [ | newClass | newClass := (self model classNamed: className). @@ -86,7 +88,7 @@ RBCopyClassRefactoring >> copyMethods [ self copyMethodsOf: aClass classSide in: newClass classSide ] -{ #category : #copying } +{ #category : 'copying' } RBCopyClassRefactoring >> copyMethodsOf: rbClass1 in: rbClass2 [ rbClass1 selectors do: [ :symbol | | rbMethod | rbMethod := rbClass1 methodFor: symbol. @@ -99,7 +101,7 @@ RBCopyClassRefactoring >> copyMethodsOf: rbClass1 in: rbClass2 [ ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBCopyClassRefactoring >> copyVariables [ aClass instanceVariableNames do: [ :varName | self generateChangesFor: (RBAddInstanceVariableRefactoring @@ -114,13 +116,13 @@ RBCopyClassRefactoring >> copyVariables [ class: className) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyClassRefactoring >> preconditions [ ^ (RBCondition isValidClassName: className) & (RBCondition isGlobal: className in: self model) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBCopyClassRefactoring >> privateTransform [ self copyClass. self copyVariables. diff --git a/src/Refactoring-Core/RBCopyPackageRefactoring.class.st b/src/Refactoring-Core/RBCopyPackageRefactoring.class.st index 6e9f94d4d9c..4ab43b3318e 100644 --- a/src/Refactoring-Core/RBCopyPackageRefactoring.class.st +++ b/src/Refactoring-Core/RBCopyPackageRefactoring.class.st @@ -17,23 +17,25 @@ a new name prefixed with Copy. Pay attention the class extensions are not copied ``` " Class { - #name : #RBCopyPackageRefactoring, - #superclass : #RBPackageRefactoring, + #name : 'RBCopyPackageRefactoring', + #superclass : 'RBPackageRefactoring', #instVars : [ 'package', 'classMappings' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #copying } +{ #category : 'copying' } RBCopyPackageRefactoring class >> copyPackage: aString1 in: aString2 [ ^ self new copyPackage: aString1 in: aString2; yourself ] -{ #category : #copying } +{ #category : 'copying' } RBCopyPackageRefactoring class >> model: aRBSmalltalk copyPackage: aString1 in: aString2 [ ^ self new model: aRBSmalltalk; @@ -41,7 +43,7 @@ RBCopyPackageRefactoring class >> model: aRBSmalltalk copyPackage: aString1 in: yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyPackageRefactoring >> changeReferencesOf: classes with: copyClasses [ [ : job | @@ -59,27 +61,27 @@ RBCopyPackageRefactoring >> changeReferencesOf: classes with: copyClasses [ ] asJob run ] -{ #category : #accessing } +{ #category : 'accessing' } RBCopyPackageRefactoring >> classMappings [ ^ classMappings ] -{ #category : #accessing } +{ #category : 'accessing' } RBCopyPackageRefactoring >> classMappings: aDictionary [ "Set the receiver's dictionary containing mappings between the source class name to be copied and the target new namename" classMappings := aDictionary ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyPackageRefactoring >> classes [ "Answer a of the receiver's class names to be copied" ^ self classMappings keys ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyPackageRefactoring >> copyAllClasses [ "Perform a copy class refactoring on each new class to be copied and answer a with the names of the new" @@ -95,14 +97,14 @@ RBCopyPackageRefactoring >> copyAllClasses [ copyClassName ] ] -{ #category : #copying } +{ #category : 'copying' } RBCopyPackageRefactoring >> copyPackage: aString1 in: aString2 [ packageName := aString1 asSymbol. package := self model packageNamed: packageName. newName := aString2 asSymbol ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyPackageRefactoring >> preconditions [ ^ super preconditions @@ -113,7 +115,7 @@ RBCopyPackageRefactoring >> preconditions [ errorString: 'The system already includes a package named ' , newName) ] -{ #category : #transforming } +{ #category : 'transforming' } RBCopyPackageRefactoring >> privateTransform [ | copyClasses | @@ -123,7 +125,7 @@ RBCopyPackageRefactoring >> privateTransform [ self reparent: self classes with: copyClasses ] -{ #category : #renaming } +{ #category : 'renaming' } RBCopyPackageRefactoring >> renameReferencesOf: aClass1 with: aClass2 [ | replacer | replacer := (self parseTreeRewriterClass replaceLiteral: aClass1 name with: aClass2) @@ -147,7 +149,7 @@ RBCopyPackageRefactoring >> renameReferencesOf: aClass1 with: aClass2 [ using: replacer] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCopyPackageRefactoring >> reparent: classes with: copyClasses [ [ : job | | jobIndex subclasses dict | @@ -165,7 +167,7 @@ RBCopyPackageRefactoring >> reparent: classes with: copyClasses [ ] asJob run ] -{ #category : #printing } +{ #category : 'printing' } RBCopyPackageRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBCreateAccessorsForVariableTransformation.class.st b/src/Refactoring-Core/RBCreateAccessorsForVariableTransformation.class.st index d9a1091633c..4c7ed005fd2 100644 --- a/src/Refactoring-Core/RBCreateAccessorsForVariableTransformation.class.st +++ b/src/Refactoring-Core/RBCreateAccessorsForVariableTransformation.class.st @@ -29,8 +29,8 @@ x: anObject " Class { - #name : #RBCreateAccessorsForVariableTransformation, - #superclass : #RBVariableRefactoring, + #name : 'RBCreateAccessorsForVariableTransformation', + #superclass : 'RBVariableRefactoring', #instVars : [ 'classVariable', 'needsReturn', @@ -38,44 +38,46 @@ Class { 'getterMethodName', 'setterMethodName' ], - #category : #'Refactoring-Core-Transformation' + #category : 'Refactoring-Core-Transformation', + #package : 'Refactoring-Core', + #tag : 'Transformation' } -{ #category : #displaying } +{ #category : 'displaying' } RBCreateAccessorsForVariableTransformation class >> basicMenuItemString [ ^ 'Generate accessors' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> classVariable: aVarName class: aClass [ ^ self variable: aVarName class: aClass classVariable: true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> instanceVariable: aVarName class: aClass [ ^ self variable: aVarName class: aClass classVariable: false ] -{ #category : #accessing } +{ #category : 'accessing' } RBCreateAccessorsForVariableTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> model: aRBSmalltalk classVariable: aVarName class: aClass [ ^ self model: aRBSmalltalk variable: aVarName class: aClass classVariable: true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> model: aRBSmalltalk instanceVariable: aVarName class: aClass [ ^ self model: aRBSmalltalk variable: aVarName class: aClass classVariable: false ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> model: aRBSmalltalk variable: aVarName class: aClass classVariable: aBoolean [ ^(self model: aRBSmalltalk @@ -85,18 +87,18 @@ RBCreateAccessorsForVariableTransformation class >> model: aRBSmalltalk variable yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateAccessorsForVariableTransformation class >> variable: aVarName class: aClass classVariable: aBoolean [ ^(self variable: aVarName class: aClass) classVariable: aBoolean; yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBCreateAccessorsForVariableTransformation >> classVariable: aBoolean [ classVariable := aBoolean ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> createGetterAccessor [ "Only define a getter if it is not already defined in the class or its subclasses." @@ -104,19 +106,19 @@ RBCreateAccessorsForVariableTransformation >> createGetterAccessor [ getterMethodName ifNil: [ getterMethodName := self defineGetterMethod ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> createMatcher [ ^ self parseTreeSearcherClass getterMethod: variableName ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> createSetterAccessor [ setterMethodName := self findSetterMethod. setterMethodName ifNil: [ setterMethodName := self defineSetterMethod ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> defineGetterMethod [ self generateChangesFor: @@ -130,7 +132,7 @@ RBCreateAccessorsForVariableTransformation >> defineGetterMethod [ ^ selector ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> defineSetterMethod [ | definingClass string | definingClass := self definingClass. @@ -150,14 +152,14 @@ RBCreateAccessorsForVariableTransformation >> defineSetterMethod [ ^selector ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> definingClass [ ^ classVariable ifTrue: [ class classSide ] ifFalse: [ class ] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> findGetterMethod [ "Look for possible already existing getter method (a method accessing the instance variable in a class or its subclasses). This information will be used to avoid creating a new getter." @@ -172,7 +174,7 @@ RBCreateAccessorsForVariableTransformation >> findGetterMethod [ ifNone: [ nil ] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> findSetterMethod [ "Look for possible already existing setter method (a method accessing the instance variable in a class or its subclasses). This information will be used to avoid creating a new setter." @@ -189,20 +191,20 @@ RBCreateAccessorsForVariableTransformation >> findSetterMethod [ ifNone: [ nil ] ] -{ #category : #'client refactoring API' } +{ #category : 'client refactoring API' } RBCreateAccessorsForVariableTransformation >> getterMethod [ self deprecated: 'Use getterMethodName' transformWith: '`@arg getterMethod' -> '`@arg getterMethodName'. ^ self getterMethodName ] -{ #category : #'client refactoring API' } +{ #category : 'client refactoring API' } RBCreateAccessorsForVariableTransformation >> getterMethodName [ ^getterMethodName ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> methodsReferencingVariable [ ^ classVariable @@ -210,7 +212,7 @@ RBCreateAccessorsForVariableTransformation >> methodsReferencingVariable [ ifFalse: [ self definingClass whichSelectorsReferToInstanceVariable: variableName ] ] -{ #category : #testing } +{ #category : 'testing' } RBCreateAccessorsForVariableTransformation >> needsReturnForSetter [ "In case the variable is used in a sequence of assignments y := x := 2, the generated code for the setter will generate @@ -233,17 +235,17 @@ RBCreateAccessorsForVariableTransformation >> needsReturnForSetter [ ^ needsReturn ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> possibleGetterSelectors [ ^self methodsReferencingVariable select: [:each | each numArgs == 0] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBCreateAccessorsForVariableTransformation >> possibleSetterSelectors [ ^self methodsReferencingVariable select: [:each | each numArgs == 1] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateAccessorsForVariableTransformation >> preconditions [ "Checks that the class actually defines the variable from which we will build setter and getter." @@ -252,34 +254,34 @@ RBCreateAccessorsForVariableTransformation >> preconditions [ ifFalse: [RBCondition definesInstanceVariable: variableName in: class] ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> privateTransform [ self createGetterAccessor; createSetterAccessor ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateAccessorsForVariableTransformation >> selector [ ^ selector ifNil: [ selector := self safeMethodNameFor: self definingClass basedOn: variableName asString. ] ] -{ #category : #'client refactoring API' } +{ #category : 'client refactoring API' } RBCreateAccessorsForVariableTransformation >> setterMethod [ self deprecated: 'Use getterMethodName' transformWith: '`@arg setterMethod' -> '`@arg setterMethodName'. ^ self setterMethodName ] -{ #category : #'client refactoring API' } +{ #category : 'client refactoring API' } RBCreateAccessorsForVariableTransformation >> setterMethodName [ ^ setterMethodName ] -{ #category : #printing } +{ #category : 'printing' } RBCreateAccessorsForVariableTransformation >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -292,7 +294,7 @@ RBCreateAccessorsForVariableTransformation >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #testing } +{ #category : 'testing' } RBCreateAccessorsForVariableTransformation >> usesAssignmentOf: aString in: aClass classVariable: isClassVar [ "Returns whether the variable aString is used in a assignement sequence e.g., x := y := 2 in the class and its subclasses." diff --git a/src/Refactoring-Core/RBCreateCascadeRefactoring.class.st b/src/Refactoring-Core/RBCreateCascadeRefactoring.class.st index f136351b742..82160de8a8e 100644 --- a/src/Refactoring-Core/RBCreateCascadeRefactoring.class.st +++ b/src/Refactoring-Core/RBCreateCascadeRefactoring.class.st @@ -5,8 +5,8 @@ Two or more message sends to the same object are replaced by a cascaded message " Class { - #name : #RBCreateCascadeRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBCreateCascadeRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'selectedInterval', @@ -15,17 +15,19 @@ Class { 'statementNodes', 'transformedNode' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateCascadeRefactoring class >> combine: anInterval from: aSelector in: aClass [ ^ self new combine: anInterval from: aSelector in: aClass; yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateCascadeRefactoring class >> model: aNamespace combine: anInterval from: aSelector in: aClass [ ^ self new model: aNamespace; @@ -33,7 +35,7 @@ RBCreateCascadeRefactoring class >> model: aNamespace combine: anInterval from: yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateCascadeRefactoring >> addStatementNode: aNode [ aNode isMessage ifTrue: [ ^ statementNodes add: aNode ]. @@ -42,14 +44,14 @@ RBCreateCascadeRefactoring >> addStatementNode: aNode [ self refactoringError: aNode formattedCode , ' is not a valid message' ] -{ #category : #initialization } +{ #category : 'initialization' } RBCreateCascadeRefactoring >> combine: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. selectedInterval := anInterval ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateCascadeRefactoring >> combineMessages [ "This combines the messages and adds the assignements of the last statement to the cascade. This is not necessary if there is a return, because the refactoring engine automatically compensates for that." @@ -64,7 +66,7 @@ RBCreateCascadeRefactoring >> combineMessages [ expression := expression parent ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateCascadeRefactoring >> compileCode [ class compileTree: (self parseTreeRewriterClass replaceStatements: sequenceNode formattedCode @@ -73,7 +75,7 @@ RBCreateCascadeRefactoring >> compileCode [ onInterval: selectedInterval) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateCascadeRefactoring >> findReceiverNode [ "Find the sequence to be combined." @@ -86,7 +88,7 @@ RBCreateCascadeRefactoring >> findReceiverNode [ ifFalse: [ self refactoringWarning: 'The receiver is an expression. Proceed with caution' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateCascadeRefactoring >> findSequenceNode [ "Find the sequence to be combined." @@ -97,7 +99,7 @@ RBCreateCascadeRefactoring >> findSequenceNode [ ifFalse: [ self refactoringError: 'You must select two or more statements' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateCascadeRefactoring >> findStatementNodes [ "Find the sequence to be combined." @@ -113,7 +115,7 @@ RBCreateCascadeRefactoring >> findStatementNodes [ self addStatementNode: current ] ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBCreateCascadeRefactoring >> parseTree [ parseTree @@ -123,20 +125,20 @@ RBCreateCascadeRefactoring >> parseTree [ ^ parseTree doSemanticAnalysis ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateCascadeRefactoring >> preconditions [ ^ (RBCondition definesSelector: selector in: class) & (RBCondition withBlock: [ self findSequenceNode; findStatementNodes; findReceiverNode. true ]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateCascadeRefactoring >> privateTransform [ self combineMessages. self compileCode ] -{ #category : #accessing } +{ #category : 'accessing' } RBCreateCascadeRefactoring >> selectedSource [ ^ self parseTree source copyFrom: selectedInterval first to: selectedInterval last ] diff --git a/src/Refactoring-Core/RBCreateLazyAccessorsForVariableTransformation.class.st b/src/Refactoring-Core/RBCreateLazyAccessorsForVariableTransformation.class.st index 78e9dade694..c0e9a1a6400 100644 --- a/src/Refactoring-Core/RBCreateLazyAccessorsForVariableTransformation.class.st +++ b/src/Refactoring-Core/RBCreateLazyAccessorsForVariableTransformation.class.st @@ -25,21 +25,23 @@ RBLintRuleTestData >> foo1: anObject ``` " Class { - #name : #RBCreateLazyAccessorsForVariableTransformation, - #superclass : #RBCreateAccessorsForVariableTransformation, + #name : 'RBCreateLazyAccessorsForVariableTransformation', + #superclass : 'RBCreateAccessorsForVariableTransformation', #instVars : [ 'defaultValue' ], - #category : #'Refactoring-Core-Transformation' + #category : 'Refactoring-Core-Transformation', + #package : 'Refactoring-Core', + #tag : 'Transformation' } -{ #category : #displaying } +{ #category : 'displaying' } RBCreateLazyAccessorsForVariableTransformation class >> basicMenuItemString [ ^ 'Generate lazy accessors' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateLazyAccessorsForVariableTransformation class >> model: aRBSmalltalk variable: aVarName class: aClass classVariable: aBoolean defaultValue: aString [ ^(self model: aRBSmalltalk @@ -50,7 +52,7 @@ RBCreateLazyAccessorsForVariableTransformation class >> model: aRBSmalltalk vari yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBCreateLazyAccessorsForVariableTransformation class >> variable: aVarName class: aClass classVariable: aBoolean defaultValue: aString [ ^(self variable: aVarName class: aClass) @@ -59,7 +61,7 @@ RBCreateLazyAccessorsForVariableTransformation class >> variable: aVarName class yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateLazyAccessorsForVariableTransformation >> checkVariableReferencesIn: aParseTree [ | searcher | @@ -76,7 +78,7 @@ RBCreateLazyAccessorsForVariableTransformation >> checkVariableReferencesIn: aPa searcher executeTree: aParseTree ] -{ #category : #private } +{ #category : 'private' } RBCreateLazyAccessorsForVariableTransformation >> createGetterAccessor [ getterMethodName := self findGetterMethod. @@ -90,17 +92,17 @@ RBCreateLazyAccessorsForVariableTransformation >> createGetterAccessor [ getterMethodName := self defineGetterMethod ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBCreateLazyAccessorsForVariableTransformation >> defaultValue [ ^ defaultValue ifNil: [ defaultValue := 'nil' ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBCreateLazyAccessorsForVariableTransformation >> defaultValue: aString [ defaultValue := aString ] -{ #category : #transforming } +{ #category : 'transforming' } RBCreateLazyAccessorsForVariableTransformation >> defineGetterMethod [ self generateChangesFor: @@ -115,7 +117,7 @@ RBCreateLazyAccessorsForVariableTransformation >> defineGetterMethod [ ^ selector ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateLazyAccessorsForVariableTransformation >> preconditions [ "In addition check that the initialization is valid" @@ -123,7 +125,7 @@ RBCreateLazyAccessorsForVariableTransformation >> preconditions [ & (RBCondition withBlock: [ self verifyInitializationExpressionOf: self defaultValue. true ]) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBCreateLazyAccessorsForVariableTransformation >> verifyInitializationExpressionOf: initializer [ | tree | tree := self parserClass diff --git a/src/Refactoring-Core/RBDeprecateClassRefactoring.class.st b/src/Refactoring-Core/RBDeprecateClassRefactoring.class.st index 4d4e8a01b4b..de8d678169b 100644 --- a/src/Refactoring-Core/RBDeprecateClassRefactoring.class.st +++ b/src/Refactoring-Core/RBDeprecateClassRefactoring.class.st @@ -10,8 +10,8 @@ I am a refactoring operation for removing of usages of a deprecated class, that " Class { - #name : #RBDeprecateClassRefactoring, - #superclass : #RBClassRefactoring, + #name : 'RBDeprecateClassRefactoring', + #superclass : 'RBClassRefactoring', #instVars : [ 'newName', 'deprecatedClass', @@ -19,15 +19,17 @@ Class { 'shouldRemoveExtensions', 'shouldFixSubclasses' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBDeprecateClassRefactoring class >> deprecate: aDeprecatedClass in: aNewName [ ^ self new className: aDeprecatedClass name newName: aNewName ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBDeprecateClassRefactoring class >> model: aRBSmalltalk deprecate: aClass in: aNewName [ ^ self new model: aRBSmalltalk; @@ -35,7 +37,7 @@ RBDeprecateClassRefactoring class >> model: aRBSmalltalk deprecate: aClass in: a yourself ] -{ #category : #adding } +{ #category : 'adding' } RBDeprecateClassRefactoring >> addMethod: source to: aClass in: aProtocol [ self generateChangesFor: @@ -45,14 +47,14 @@ RBDeprecateClassRefactoring >> addMethod: source to: aClass in: aProtocol [ withProtocol: aProtocol) ] -{ #category : #initialization } +{ #category : 'initialization' } RBDeprecateClassRefactoring >> className: aName newName: aNewName [ className := aName asSymbol. deprecatedClass := self model classNamed: className. newName := aNewName asSymbol ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> classSideExtensionMethodsOf: anRBClass [ ^ anRBClass realClass classSide localMethods @@ -60,7 +62,7 @@ RBDeprecateClassRefactoring >> classSideExtensionMethodsOf: anRBClass [ thenCollect: [ :each | anRBClass classSide methodFor: each selector ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> convertDeprecatedToSubclass [ | replacement | replacement := self model classNamed: newName. @@ -78,7 +80,7 @@ RBDeprecateClassRefactoring >> convertDeprecatedToSubclass [ in: 'testing' ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> copyExtensionMethods [ (self instanceSideExtensionMethodsOf: deprecatedClass) @@ -88,17 +90,17 @@ RBDeprecateClassRefactoring >> copyExtensionMethods [ do: [ :each | self addMethod: each source to: self newClass classSide in: each protocols ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> deprecatedClass [ ^ deprecatedClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> deprecatedClass: anObject [ deprecatedClass := anObject ] -{ #category : #initialization } +{ #category : 'initialization' } RBDeprecateClassRefactoring >> initialize [ super initialize. @@ -108,7 +110,7 @@ RBDeprecateClassRefactoring >> initialize [ shouldRemoveExtensions := true ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> instanceSideExtensionMethodsOf: anRBClass [ ^ anRBClass realClass instanceSide localMethods @@ -116,13 +118,13 @@ RBDeprecateClassRefactoring >> instanceSideExtensionMethodsOf: anRBClass [ thenCollect: [ :each | anRBClass instanceSide methodFor: each selector ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> newClass [ ^ self model classNamed: newName ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBDeprecateClassRefactoring >> preconditions [ ^((RBCondition withBlock: [deprecatedClass notNil and: [deprecatedClass isMeta not]]) & (RBCondition isValidClassName: newName) @@ -130,7 +132,7 @@ RBDeprecateClassRefactoring >> preconditions [ (RBCondition withBlock: [ self refactoringError: newName , ' is not a valid class name']) ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> privateTransform [ self shouldFixSubclasses @@ -146,7 +148,7 @@ RBDeprecateClassRefactoring >> privateTransform [ ifTrue: [ self removeExtensionMethods ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> removeExtensionMethods [ (self instanceSideExtensionMethodsOf: deprecatedClass) @@ -156,7 +158,7 @@ RBDeprecateClassRefactoring >> removeExtensionMethods [ do: [ :each | deprecatedClass classSide removeMethod: each selector ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> renameReferences [ | replacer | replacer := (self parseTreeRewriterClass replaceLiteral: className with: newName) @@ -175,7 +177,7 @@ RBDeprecateClassRefactoring >> renameReferences [ using: replacer ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBDeprecateClassRefactoring >> renameSuperclassOfSubclasses [ | replacement | @@ -183,37 +185,37 @@ RBDeprecateClassRefactoring >> renameSuperclassOfSubclasses [ self model reparentClasses: deprecatedClass subclasses to: replacement ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldCopyExtensions [ ^ shouldCopyExtensions ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldCopyExtensions: anObject [ shouldCopyExtensions := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldFixSubclasses [ ^ shouldFixSubclasses ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldFixSubclasses: anObject [ shouldFixSubclasses := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldRemoveExtensions [ ^ shouldRemoveExtensions ] -{ #category : #accessing } +{ #category : 'accessing' } RBDeprecateClassRefactoring >> shouldRemoveExtensions: anObject [ shouldRemoveExtensions := anObject ] -{ #category : #printing } +{ #category : 'printing' } RBDeprecateClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBEntity.class.st b/src/Refactoring-Core/RBEntity.class.st index 211139a42d1..276f71059d3 100644 --- a/src/Refactoring-Core/RBEntity.class.st +++ b/src/Refactoring-Core/RBEntity.class.st @@ -2,23 +2,25 @@ I'm the root of the model classes. " Class { - #name : #RBEntity, - #superclass : #Object, + #name : 'RBEntity', + #superclass : 'Object', #instVars : [ 'modelFactory', 'changeFactory' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #initialization } +{ #category : 'initialization' } RBEntity >> initialize [ super initialize. modelFactory := RBClassModelFactory new. changeFactory := RBRefactoryChangeManager changeFactory ] -{ #category : #initialization } +{ #category : 'initialization' } RBEntity >> parserClass [ ^ RBParser diff --git a/src/Refactoring-Core/RBExpandReferencedPoolsRefactoring.class.st b/src/Refactoring-Core/RBExpandReferencedPoolsRefactoring.class.st index 4a999bb9ec5..7853b80eedf 100644 --- a/src/Refactoring-Core/RBExpandReferencedPoolsRefactoring.class.st +++ b/src/Refactoring-Core/RBExpandReferencedPoolsRefactoring.class.st @@ -8,18 +8,20 @@ this refactoring will add the pool definition to class B. " Class { - #name : #RBExpandReferencedPoolsRefactoring, - #superclass : #RBRefactoring, + #name : 'RBExpandReferencedPoolsRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'pools', 'fromClass', 'parseTree', 'toClasses' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExpandReferencedPoolsRefactoring class >> forMethod: aParseTree fromClass: aClass toClasses: classCollection [ ^ self new forMethod: aParseTree @@ -28,7 +30,7 @@ RBExpandReferencedPoolsRefactoring class >> forMethod: aParseTree fromClass: aCl yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExpandReferencedPoolsRefactoring class >> model: aRBNamespace forMethod: aParseTree fromClass: aClass toClasses: classCollection [ ^ self new model: aRBNamespace; @@ -38,7 +40,7 @@ RBExpandReferencedPoolsRefactoring class >> model: aRBNamespace forMethod: aPars yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBExpandReferencedPoolsRefactoring >> computePoolsToMove [ | poolVariables searcher | @@ -61,38 +63,38 @@ RBExpandReferencedPoolsRefactoring >> computePoolsToMove [ searcher executeTree: parseTree ] -{ #category : #initialization } +{ #category : 'initialization' } RBExpandReferencedPoolsRefactoring >> forMethod: aParseTree fromClass: aClass toClasses: classCollection [ fromClass := self model classFor: aClass. parseTree := aParseTree. toClasses := classCollection collect: [:each | self model classFor: each] ] -{ #category : #testing } +{ #category : 'testing' } RBExpandReferencedPoolsRefactoring >> hasPoolsToMove [ ^pools isNotEmpty ] -{ #category : #transforming } +{ #category : 'transforming' } RBExpandReferencedPoolsRefactoring >> movePool: aSymbol toClass: aClass [ | nonMetaClass | nonMetaClass := aClass instanceSide. (nonMetaClass definesPoolDictionary: aSymbol) ifFalse: [ nonMetaClass addPoolDictionary: aSymbol ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExpandReferencedPoolsRefactoring >> movePoolVariables [ pools do: [:poolDict | toClasses do: [:each | self movePool: poolDict toClass: each]] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExpandReferencedPoolsRefactoring >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBExpandReferencedPoolsRefactoring >> privateTransform [ self computePoolsToMove. self hasPoolsToMove @@ -103,7 +105,7 @@ RBExpandReferencedPoolsRefactoring >> privateTransform [ self movePoolVariables ] -{ #category : #transforming } +{ #category : 'transforming' } RBExpandReferencedPoolsRefactoring >> whichPoolDefines: varName [ | currentClass | currentClass := fromClass. diff --git a/src/Refactoring-Core/RBExtractMethodAndOccurrences.class.st b/src/Refactoring-Core/RBExtractMethodAndOccurrences.class.st index 9ee4d1bfea1..f4845828956 100644 --- a/src/Refactoring-Core/RBExtractMethodAndOccurrences.class.st +++ b/src/Refactoring-Core/RBExtractMethodAndOccurrences.class.st @@ -4,16 +4,18 @@ I am a refactoring for creating a method from a code fragment and then find all You can select an interval of some code in a method and call this refactoring to create a new method implementing that code and replace the code by calling this method instead. Then find occurrences of extracted method in all class methods and replace the duplicated code by calling extracted method istead. " Class { - #name : #RBExtractMethodAndOccurrences, - #superclass : #RBMethodRefactoring, + #name : 'RBExtractMethodAndOccurrences', + #superclass : 'RBMethodRefactoring', #instVars : [ 'extractionInterval', 'selector' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodAndOccurrences class >> extract: anInterval from: aSelector in: aClass [ ^self new extract: anInterval @@ -21,7 +23,7 @@ RBExtractMethodAndOccurrences class >> extract: anInterval from: aSelector in: a in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodAndOccurrences class >> model: aRBSmalltalk extract: anInterval from: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -31,14 +33,14 @@ RBExtractMethodAndOccurrences class >> model: aRBSmalltalk extract: anInterval f yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodAndOccurrences >> extract: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. extractionInterval := anInterval ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> extractMethod [ | refactoring | @@ -51,13 +53,13 @@ RBExtractMethodAndOccurrences >> extractMethod [ ^ refactoring newExtractedSelector ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> extractMethodClass [ ^ RBExtractMethodRefactoring ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> findImplementorOf: aSelector [ (class directlyDefinesMethod: aSelector) ifTrue: [ ^ true ]. class superclass ifNotNil: [ @@ -67,13 +69,13 @@ RBExtractMethodAndOccurrences >> findImplementorOf: aSelector [ ^ false ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> findOccurrencesClass [ ^ RBFindAndReplaceTransformation ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> findOccurrencesOf: aSelector [ | refactoring | @@ -90,25 +92,25 @@ RBExtractMethodAndOccurrences >> findOccurrencesOf: aSelector [ aSelector , ' is not a valid selector name.' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractMethodAndOccurrences >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodAndOccurrences >> privateTransform [ | newExtractedSelector | newExtractedSelector := self extractMethod. self findOccurrencesOf: newExtractedSelector ] -{ #category : #asserting } +{ #category : 'asserting' } RBExtractMethodAndOccurrences >> shouldSearchInHierarchy [ ^(self options at: #searchInWholeHierarchy) value: self value: class ] -{ #category : #printing } +{ #category : 'printing' } RBExtractMethodAndOccurrences >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBExtractMethodRefactoring.class.st b/src/Refactoring-Core/RBExtractMethodRefactoring.class.st index a098d2b1fca..dee3b3bdc03 100644 --- a/src/Refactoring-Core/RBExtractMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBExtractMethodRefactoring.class.st @@ -7,8 +7,8 @@ The new method needs to have as many arguments as the number of (temp)variables, The preconditions are quite complex. The code needs to be parseable valid code. " Class { - #name : #RBExtractMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBExtractMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'extractionInterval', @@ -19,10 +19,12 @@ Class { 'parameterMap', 'newExtractedSelector' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodRefactoring class >> extract: anInterval from: aSelector in: aClass [ ^ self new extract: anInterval @@ -30,7 +32,7 @@ RBExtractMethodRefactoring class >> extract: anInterval from: aSelector in: aCla in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodRefactoring class >> model: aRBSmalltalk extract: anInterval from: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -40,7 +42,7 @@ RBExtractMethodRefactoring class >> model: aRBSmalltalk extract: anInterval from yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkAssignments: variableNames [ | node outsideVars removeAssigned | removeAssigned := variableNames copy. @@ -60,7 +62,7 @@ RBExtractMethodRefactoring >> checkAssignments: variableNames [ self updateTemporariesInExtractedMethodFor: variableNames ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkReturn [ needsReturn := self placeholderNode isUsed. extractedParseTree containsReturn ifFalse: [^self]. @@ -71,7 +73,7 @@ RBExtractMethodRefactoring >> checkReturn [ self checkSelfReturns ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkSelfReturns [ | searcher | searcher := self parseTreeSearcher. @@ -82,7 +84,7 @@ RBExtractMethodRefactoring >> checkSelfReturns [ ifTrue: [ self placeholderNode asReturn ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkSingleAssignment: varName [ ((RBReadBeforeWrittenTester isVariable: varName readBeforeWrittenIn: extractedParseTree) @@ -98,7 +100,7 @@ RBExtractMethodRefactoring >> checkSingleAssignment: varName [ in: modifiedParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkSpecialExtractions [ | node | node := self placeholderNode parent. @@ -109,7 +111,7 @@ RBExtractMethodRefactoring >> checkSpecialExtractions [ [self refactoringError: 'Cannot extract first message of a cascaded message'] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> checkTemporaries [ | temps accesses assigned | temps := self remainingTemporaries. @@ -121,7 +123,7 @@ RBExtractMethodRefactoring >> checkTemporaries [ yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> compileExtractedMethod [ | cls | @@ -132,7 +134,7 @@ RBExtractMethodRefactoring >> compileExtractedMethod [ withAttributesFrom: (class methodFor: selector) ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> existingSelector [ "Try to find an existing method instead of creating a new one" @@ -142,14 +144,14 @@ RBExtractMethodRefactoring >> existingSelector [ ifNone: [ nil ] ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBExtractMethodRefactoring >> extract: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. extractionInterval := anInterval ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> extractMethod [ | parseTree isSequence extractCode subtree newCode | extractCode := self getExtractedSource. @@ -213,12 +215,12 @@ RBExtractMethodRefactoring >> extractMethod [ onInterval: extractionInterval ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBExtractMethodRefactoring >> extractedParseTree [ ^ extractedParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> getExtractedSource [ | source | source := class sourceCodeFor: selector. @@ -228,7 +230,7 @@ RBExtractMethodRefactoring >> getExtractedSource [ ^source copyFrom: extractionInterval first to: extractionInterval last ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> getNewMethodName [ | newSelector methodName newMethodName | methodName := RBMethodName new. @@ -251,7 +253,7 @@ RBExtractMethodRefactoring >> getNewMethodName [ ^newSelector asSymbol ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> isMethodEquivalentTo: aSelector [ selector == aSelector ifTrue: [^false]. @@ -263,7 +265,7 @@ RBExtractMethodRefactoring >> isMethodEquivalentTo: aSelector [ ^true ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> isParseTreeEquivalentTo: aSelector [ | tree definingClass | definingClass := class whoDefinesMethod: aSelector. @@ -283,17 +285,17 @@ RBExtractMethodRefactoring >> isParseTreeEquivalentTo: aSelector [ ^self shouldUseExistingMethod: aSelector ] -{ #category : #accessing } +{ #category : 'accessing' } RBExtractMethodRefactoring >> method [ ^ class realClass >> selector ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> methodDelimiter [ ^'#''place.holder.for.method''' ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> nameNewMethod: aSymbol [ | args newSend | newExtractedSelector := aSymbol . @@ -318,27 +320,27 @@ RBExtractMethodRefactoring >> nameNewMethod: aSymbol [ (self parseTreeRewriterClass rename: e newName to: e name) executeTree: modifiedParseTree ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> newExtractedSelector [ ^ newExtractedSelector ] -{ #category : #accessing } +{ #category : 'accessing' } RBExtractMethodRefactoring >> parameterMap [ ^ parameterMap ifNil: [ parameterMap := { } ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBExtractMethodRefactoring >> parameterMap: aDictionary [ parameterMap := aDictionary ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> parameters: anOrderedCollection [ parameters := anOrderedCollection ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> placeholderNode [ | node | node := self parseTreeSearcherClass @@ -348,7 +350,7 @@ RBExtractMethodRefactoring >> placeholderNode [ ^ node ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractMethodRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition withBlock: @@ -360,7 +362,7 @@ RBExtractMethodRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> privateTransform [ | existingSelector | @@ -372,7 +374,7 @@ RBExtractMethodRefactoring >> privateTransform [ class compileTree: modifiedParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> remainingTemporaries [ | temps | temps := modifiedParseTree allDefinedVariables asSet. @@ -381,23 +383,23 @@ RBExtractMethodRefactoring >> remainingTemporaries [ ^temps ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> renameAllParameters [ self parameterMap do: [ :each | self renameParameterWith: each name to: each newName ] ] -{ #category : #renaming } +{ #category : 'renaming' } RBExtractMethodRefactoring >> renameNode: aParseTree withOldName: oldName toWithName: newName [ (self parseTreeRewriterClass rename: oldName to: newName) executeTree: aParseTree ] -{ #category : #renaming } +{ #category : 'renaming' } RBExtractMethodRefactoring >> renameParameterWith: oldName to: newName [ self renameNode: extractedParseTree withOldName: oldName toWithName: newName ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> reorderParametersToMatch: aSelector [ | tree dictionary | tree := class parseTreeForSelector: aSelector. @@ -412,29 +414,29 @@ RBExtractMethodRefactoring >> reorderParametersToMatch: aSelector [ refactoringError: 'An internal error occured, please report this error.']] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> requestExistingSelector [ ^ [(self options at: #existingSelector) value: self] on: Exception do: [ :e | nil ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> requestExtractionClass [ ^ (self options at: #extractionClass ifAbsent: [ [:ref | class ]]) value: self ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> selectorsToSearch [ ^ class allSelectors ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> startLimit: aNumber [ ^ aNumber ] -{ #category : #printing } +{ #category : 'printing' } RBExtractMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -448,18 +450,18 @@ RBExtractMethodRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #accessing } +{ #category : 'accessing' } RBExtractMethodRefactoring >> targetClass [ ^ class ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodRefactoring >> updateTemporariesInExtractedMethodFor: assigned [ "Add temporaries in extract method" assigned do: [:each | extractedParseTree body addTemporaryNamed: each] ] -{ #category : #renaming } +{ #category : 'renaming' } RBExtractMethodRefactoring >> validateRenameNode: aParseTree withOldName: oldName toWithName: newName [ |conditions block| conditions := ((RBCondition isValidInstanceVariableName: newName for: class) @@ -479,7 +481,7 @@ RBExtractMethodRefactoring >> validateRenameNode: aParseTree withOldName: oldNam ifTrue: [ self refactoringError: newName asString , ' is already defined' ] ] -{ #category : #renaming } +{ #category : 'renaming' } RBExtractMethodRefactoring >> validateRenameOf: oldName to: newName [ self validateRenameNode: extractedParseTree withOldName: oldName toWithName: newName ] diff --git a/src/Refactoring-Core/RBExtractMethodToComponentRefactoring.class.st b/src/Refactoring-Core/RBExtractMethodToComponentRefactoring.class.st index 7b1dffee458..68b5b517be5 100644 --- a/src/Refactoring-Core/RBExtractMethodToComponentRefactoring.class.st +++ b/src/Refactoring-Core/RBExtractMethodToComponentRefactoring.class.st @@ -7,17 +7,19 @@ Based on the instance variable you chosed for this method I will guess the class " Class { - #name : #RBExtractMethodToComponentRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBExtractMethodToComponentRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'extractionInterval', 'extractedMethodSelector' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodToComponentRefactoring class >> extract: anInterval from: aSelector in: aClass [ ^ self new extract: anInterval @@ -25,7 +27,7 @@ RBExtractMethodToComponentRefactoring class >> extract: anInterval from: aSelect in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractMethodToComponentRefactoring class >> model: aRBSmalltalk extract: anInterval from: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -35,14 +37,14 @@ RBExtractMethodToComponentRefactoring class >> model: aRBSmalltalk extract: anIn yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBExtractMethodToComponentRefactoring >> extract: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. extractionInterval := anInterval ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodToComponentRefactoring >> extractMethod [ | refactoring | refactoring := RBExtractMethodRefactoring @@ -61,7 +63,7 @@ RBExtractMethodToComponentRefactoring >> extractMethod [ self generateChangesFor: refactoring ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodToComponentRefactoring >> inlineForwarder [ | refactoring | refactoring := RBInlineAllSendersRefactoring @@ -72,7 +74,7 @@ RBExtractMethodToComponentRefactoring >> inlineForwarder [ self generateChangesFor: refactoring ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodToComponentRefactoring >> moveMethod [ | variable refactoring | @@ -87,13 +89,13 @@ RBExtractMethodToComponentRefactoring >> moveMethod [ self generateChangesFor: refactoring ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractMethodToComponentRefactoring >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractMethodToComponentRefactoring >> privateTransform [ self extractMethod; @@ -101,7 +103,7 @@ RBExtractMethodToComponentRefactoring >> privateTransform [ inlineForwarder ] -{ #category : #printing } +{ #category : 'printing' } RBExtractMethodToComponentRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBExtractSetUpMethodAndOccurrences.class.st b/src/Refactoring-Core/RBExtractSetUpMethodAndOccurrences.class.st index 6d1a5e6671d..22214139185 100644 --- a/src/Refactoring-Core/RBExtractSetUpMethodAndOccurrences.class.st +++ b/src/Refactoring-Core/RBExtractSetUpMethodAndOccurrences.class.st @@ -54,22 +54,24 @@ RBDataTest >> testExample4 ""this method did not change"" ``` " Class { - #name : #RBExtractSetUpMethodAndOccurrences, - #superclass : #RBExtractMethodAndOccurrences, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBExtractSetUpMethodAndOccurrences', + #superclass : 'RBExtractMethodAndOccurrences', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodAndOccurrences >> extractMethodClass [ ^ RBExtractSetUpMethodRefactoring ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodAndOccurrences >> findOccurrencesClass [ ^ RBFindAndReplaceSetUpTransformation ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodAndOccurrences >> privateTransform [ self extractMethod. self findOccurrencesOf: #setUp diff --git a/src/Refactoring-Core/RBExtractSetUpMethodRefactoring.class.st b/src/Refactoring-Core/RBExtractSetUpMethodRefactoring.class.st index 6e3522bb510..1774edbc7aa 100644 --- a/src/Refactoring-Core/RBExtractSetUpMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBExtractSetUpMethodRefactoring.class.st @@ -47,12 +47,14 @@ RBDataTest >> testExample " Class { - #name : #RBExtractSetUpMethodRefactoring, - #superclass : #RBExtractMethodRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBExtractSetUpMethodRefactoring', + #superclass : 'RBExtractMethodRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> checkAssignments: variableNames [ | node outsideVars removeAssigned | removeAssigned := variableNames copy. @@ -68,7 +70,7 @@ RBExtractSetUpMethodRefactoring >> checkAssignments: variableNames [ self updateTemporariesInExtractedMethodFor: variableNames ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> checkSingleAssignment: varName [ ((RBReadBeforeWrittenTester isVariable: varName @@ -85,7 +87,7 @@ RBExtractSetUpMethodRefactoring >> checkSingleAssignment: varName [ variable: varName) ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> nameNewMethod: aSymbol [ | args | args := parameters collect: [ :parm | RBVariableNode named: parm ]. @@ -93,7 +95,7 @@ RBExtractSetUpMethodRefactoring >> nameNewMethod: aSymbol [ modifiedParseTree := RBParseTreeRewriter replace: self methodDelimiter with: '#callToSetUp' in: modifiedParseTree ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractSetUpMethodRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (self requestExistingSelector ifNil: [ (RBCondition definesSelector: #setUp in: class) not ] @@ -108,7 +110,7 @@ RBExtractSetUpMethodRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> privateTransform [ | existingSelector | @@ -126,12 +128,12 @@ RBExtractSetUpMethodRefactoring >> privateTransform [ class compileTree: modifiedParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> shouldExtractAssignmentTo: name [ ^ true ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> startLimit: aNumber [ | node | node := class parseTreeForSelector: selector. @@ -139,6 +141,6 @@ RBExtractSetUpMethodRefactoring >> startLimit: aNumber [ ifNotEmpty: [ node statements first start ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractSetUpMethodRefactoring >> updateTemporariesInExtractedMethodFor: variableNames [ ] diff --git a/src/Refactoring-Core/RBExtractToTemporaryRefactoring.class.st b/src/Refactoring-Core/RBExtractToTemporaryRefactoring.class.st index 95fde084a29..818e4566b96 100644 --- a/src/Refactoring-Core/RBExtractToTemporaryRefactoring.class.st +++ b/src/Refactoring-Core/RBExtractToTemporaryRefactoring.class.st @@ -5,18 +5,20 @@ As the code is now only evaluated once for initializing the variable value, this My preconditions verify that the new temporary name is a valid name and isn't already used (neither a temporary, an instance variable or a class variable). " Class { - #name : #RBExtractToTemporaryRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBExtractToTemporaryRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'sourceInterval', 'selector', 'newVariableName', 'parseTree' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractToTemporaryRefactoring class >> extract: anInterval to: aString from: aSelector in: aClass [ ^ self new extract: anInterval @@ -25,7 +27,7 @@ RBExtractToTemporaryRefactoring class >> extract: anInterval to: aString from: a in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBExtractToTemporaryRefactoring class >> model: aRBSmalltalk extract: anInterval to: aString from: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -36,7 +38,7 @@ RBExtractToTemporaryRefactoring class >> model: aRBSmalltalk extract: anInterval yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractToTemporaryRefactoring >> checkVariableName [ (class whoDefinesInstanceVariable: newVariableName) ifNotNil: [self refactoringError: ('<1p> defines an instance variable named <2s>' @@ -52,19 +54,19 @@ RBExtractToTemporaryRefactoring >> checkVariableName [ expandMacrosWith: newVariableName)] ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractToTemporaryRefactoring >> compileNewMethod [ class compileTree: self parseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractToTemporaryRefactoring >> constructAssignmentFrom: aNode [ | valueNode | valueNode := RBVariableNode named: newVariableName. ^RBAssignmentNode variable: valueNode value: aNode ] -{ #category : #initialization } +{ #category : 'initialization' } RBExtractToTemporaryRefactoring >> extract: anInterval to: aString from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. @@ -72,7 +74,7 @@ RBExtractToTemporaryRefactoring >> extract: anInterval to: aString from: aSelect newVariableName := aString ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractToTemporaryRefactoring >> insertTemporary [ | node statementNode nodeReferences children | node := self parseTree whichNodeIsContainedBy: sourceInterval. @@ -91,7 +93,7 @@ RBExtractToTemporaryRefactoring >> insertTemporary [ addTemporaryNamed: newVariableName ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBExtractToTemporaryRefactoring >> parseTree [ parseTree @@ -101,7 +103,7 @@ RBExtractToTemporaryRefactoring >> parseTree [ ^ parseTree doSemanticAnalysis ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractToTemporaryRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition isValidInstanceVariableName: newVariableName for: class) @@ -111,14 +113,14 @@ RBExtractToTemporaryRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBExtractToTemporaryRefactoring >> privateTransform [ self insertTemporary; compileNewMethod ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBExtractToTemporaryRefactoring >> selectedSource [ | source | @@ -131,7 +133,7 @@ RBExtractToTemporaryRefactoring >> selectedSource [ ^ source copyFrom: sourceInterval first to: sourceInterval last ] -{ #category : #printing } +{ #category : 'printing' } RBExtractToTemporaryRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -147,7 +149,7 @@ RBExtractToTemporaryRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBExtractToTemporaryRefactoring >> verifySelectedInterval [ | selectedParseTree selectedSources | selectedSources := self selectedSource. diff --git a/src/Refactoring-Core/RBFindAndReplaceSetUpTransformation.class.st b/src/Refactoring-Core/RBFindAndReplaceSetUpTransformation.class.st index c115263f609..ba688046098 100644 --- a/src/Refactoring-Core/RBFindAndReplaceSetUpTransformation.class.st +++ b/src/Refactoring-Core/RBFindAndReplaceSetUpTransformation.class.st @@ -54,12 +54,14 @@ RBTest >> testExample4 ``` " Class { - #name : #RBFindAndReplaceSetUpTransformation, - #superclass : #RBFindAndReplaceTransformation, - #category : #'Refactoring-Core-Transformation-Simple' + #name : 'RBFindAndReplaceSetUpTransformation', + #superclass : 'RBFindAndReplaceTransformation', + #category : 'Refactoring-Core-Transformation-Simple', + #package : 'Refactoring-Core', + #tag : 'Transformation-Simple' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceSetUpTransformation class >> model: aModel of: aClass inWholeHierarchy: aBoolean [ ^ self new model: aModel; @@ -68,7 +70,7 @@ RBFindAndReplaceSetUpTransformation class >> model: aModel of: aClass inWholeHie yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceSetUpTransformation class >> of: aClass inWholeHierarchy: aBoolean [ ^ self new of: aClass @@ -76,7 +78,7 @@ RBFindAndReplaceSetUpTransformation class >> of: aClass inWholeHierarchy: aBoole yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceSetUpTransformation >> extractMethodRefactoring [ ^ RBExtractSetUpMethodRefactoring new setOption: #useExistingMethod @@ -88,7 +90,7 @@ RBFindAndReplaceSetUpTransformation >> extractMethodRefactoring [ yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceSetUpTransformation >> methodNode [ | node | node := super methodNode. @@ -96,7 +98,7 @@ RBFindAndReplaceSetUpTransformation >> methodNode [ ^ node ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceSetUpTransformation >> nodesOf: methodNode [ | combinations limit | @@ -106,19 +108,19 @@ RBFindAndReplaceSetUpTransformation >> nodesOf: methodNode [ combinations select: [ :e | e first <= limit ] ] ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceSetUpTransformation >> of: aClass inWholeHierarchy: aBoolean [ class := self classObjectFor: aClass. selector := #setUp. replacesAllHierarchy := aBoolean ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBFindAndReplaceSetUpTransformation >> selectorsFor: cls [ ^ (cls selectors select: [:e | e isTestSelector]) copyWithout: selector ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceSetUpTransformation >> startLimitOf: sourceCode [ ^ ((self parserClass parseMethod: sourceCode) body statements first start) ] diff --git a/src/Refactoring-Core/RBFindAndReplaceTransformation.class.st b/src/Refactoring-Core/RBFindAndReplaceTransformation.class.st index a634c9e1f00..a2807130640 100644 --- a/src/Refactoring-Core/RBFindAndReplaceTransformation.class.st +++ b/src/Refactoring-Core/RBFindAndReplaceTransformation.class.st @@ -40,8 +40,8 @@ MyClassB >> dummyMethod ``` " Class { - #name : #RBFindAndReplaceTransformation, - #superclass : #RBMethodRefactoring, + #name : 'RBFindAndReplaceTransformation', + #superclass : 'RBMethodRefactoring', #instVars : [ 'method', 'selector', @@ -49,16 +49,18 @@ Class { 'matchNodes', 'occurrences' ], - #category : #'Refactoring-Core-Transformation-Simple' + #category : 'Refactoring-Core-Transformation-Simple', + #package : 'Refactoring-Core', + #tag : 'Transformation-Simple' } -{ #category : #displaying } +{ #category : 'displaying' } RBFindAndReplaceTransformation class >> basicMenuItemString [ ^ 'Find and Replace' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceTransformation class >> find: aMethod of: aClass inWholeHierarchy: aBoolean [ ^ self new @@ -68,12 +70,12 @@ RBFindAndReplaceTransformation class >> find: aMethod of: aClass inWholeHierarch yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBFindAndReplaceTransformation class >> model: aModel find: aMethod of: aClass inWholeHierarchy: aBoolean [ ^ self new model: aModel; @@ -83,7 +85,7 @@ RBFindAndReplaceTransformation class >> model: aModel find: aMethod of: aClass i yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> argumentsOf: aDictionary [ "Return the arguments values of a method ocurrence" @@ -98,7 +100,7 @@ RBFindAndReplaceTransformation >> argumentsOf: aDictionary [ ^ args ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> extract: occurrence of: rbMethod [ [|refactoring | refactoring := self extractMethodRefactoring. @@ -110,7 +112,7 @@ RBFindAndReplaceTransformation >> extract: occurrence of: rbMethod [ self generateChangesFor: refactoring ] on: Exception do: [ :e | e ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> extractMethodRefactoring [ ^ RBExtractMethodRefactoring new setOption: #useExistingMethod @@ -119,7 +121,7 @@ RBFindAndReplaceTransformation >> extractMethodRefactoring [ yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBFindAndReplaceTransformation >> find: aSelector of: aClass inWholeHierarchy: aBoolean [ class := self classObjectFor: aClass. @@ -127,7 +129,7 @@ RBFindAndReplaceTransformation >> find: aSelector of: aClass inWholeHierarchy: a replacesAllHierarchy := aBoolean ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> findOccurrencesIn: rbMethod [ |methodNode sourceCode flag | flag := false. @@ -159,13 +161,13 @@ RBFindAndReplaceTransformation >> findOccurrencesIn: rbMethod [ ^ self]]] ] -{ #category : #initialization } +{ #category : 'initialization' } RBFindAndReplaceTransformation >> initialize [ super initialize. occurrences := 0 ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> matchNodes [ ^ matchNodes ifNil: [ @@ -188,18 +190,18 @@ RBFindAndReplaceTransformation >> matchNodes [ matchNodes ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> method [ ^ method ifNil: [ method := class methodFor: selector ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> methodNode [ ^ self method ast copy ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> nodesOf: methodNode [ |visitor node| visitor := RBCombinatorVisitor new. @@ -208,12 +210,12 @@ RBFindAndReplaceTransformation >> nodesOf: methodNode [ ^ visitor combinations ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> patternParserClass [ ^ RBPatternParser ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBFindAndReplaceTransformation >> preconditions [ | condition rbMethod | @@ -233,7 +235,7 @@ RBFindAndReplaceTransformation >> preconditions [ ^ condition ] -{ #category : #transforming } +{ #category : 'transforming' } RBFindAndReplaceTransformation >> privateTransform [ |classes| classes :=replacesAllHierarchy ifFalse: [ { class } ] ifTrue: [ class withAllSubclasses ]. @@ -243,7 +245,7 @@ RBFindAndReplaceTransformation >> privateTransform [ self inform: occurrences asString, ' occurrences were found and changed.' ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> replaceArgumentsByPattern: sourceCode [ |newSource| newSource := sourceCode copyWithRegex: 'tempMatch*' matchesReplacedWith: '`@tempMatch' . @@ -251,17 +253,17 @@ RBFindAndReplaceTransformation >> replaceArgumentsByPattern: sourceCode [ ^ newSource ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBFindAndReplaceTransformation >> selectorsFor: cls [ ^ cls selectors copyWithout: selector ] -{ #category : #accessing } +{ #category : 'accessing' } RBFindAndReplaceTransformation >> startLimitOf: sourceCode [ ^ self method ast body statements first start ] -{ #category : #printing } +{ #category : 'printing' } RBFindAndReplaceTransformation >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBGenerateEqualHashTransformation.class.st b/src/Refactoring-Core/RBGenerateEqualHashTransformation.class.st index b8ea18374d9..d15227bb2e1 100644 --- a/src/Refactoring-Core/RBGenerateEqualHashTransformation.class.st +++ b/src/Refactoring-Core/RBGenerateEqualHashTransformation.class.st @@ -39,37 +39,39 @@ and any instvar accessor for the instance variables used by method `#=`. " Class { - #name : #RBGenerateEqualHashTransformation, - #superclass : #RBClassRefactoring, + #name : 'RBGenerateEqualHashTransformation', + #superclass : 'RBClassRefactoring', #instVars : [ 'variables' ], - #category : #'Refactoring-Core-Transformation' + #category : 'Refactoring-Core-Transformation', + #package : 'Refactoring-Core', + #tag : 'Transformation' } -{ #category : #displaying } +{ #category : 'displaying' } RBGenerateEqualHashTransformation class >> basicMenuItemString [ ^ 'Generate equal and hash' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBGenerateEqualHashTransformation class >> className: aClass variables: anArray [ ^ (self className: aClass) variables: anArray ] -{ #category : #testing } +{ #category : 'testing' } RBGenerateEqualHashTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBGenerateEqualHashTransformation class >> model: aNamespace className: aClass variables: anArray [ ^ (self model: aNamespace className: aClass) variables: anArray ] -{ #category : #transforming } +{ #category : 'transforming' } RBGenerateEqualHashTransformation >> accessorForVariable: aString [ | refactoring | @@ -82,7 +84,7 @@ RBGenerateEqualHashTransformation >> accessorForVariable: aString [ ^ refactoring getterMethodName ] -{ #category : #transforming } +{ #category : 'transforming' } RBGenerateEqualHashTransformation >> compileEqual [ | method statement comparison | method := self parserClass @@ -126,7 +128,7 @@ RBGenerateEqualHashTransformation >> compileEqual [ withProtocol: #comparing) ] -{ #category : #transforming } +{ #category : 'transforming' } RBGenerateEqualHashTransformation >> compileHash [ | method statement hash | method := self parserClass @@ -155,7 +157,7 @@ RBGenerateEqualHashTransformation >> compileHash [ withProtocol: #comparing) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBGenerateEqualHashTransformation >> preconditions [ "Checks that the class actually defines all the variables that will be part of the hash." @@ -167,18 +169,18 @@ RBGenerateEqualHashTransformation >> preconditions [ (RBCondition definesInstanceVariable: variable in: self theClass) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBGenerateEqualHashTransformation >> privateTransform [ self compileHash. self compileEqual ] -{ #category : #accessing } +{ #category : 'accessing' } RBGenerateEqualHashTransformation >> theClass [ ^ (self classObjectFor: className) instanceSide ] -{ #category : #accessing } +{ #category : 'accessing' } RBGenerateEqualHashTransformation >> variables: anArray [ variables := anArray ] diff --git a/src/Refactoring-Core/RBGeneratePrintOnTransformation.class.st b/src/Refactoring-Core/RBGeneratePrintOnTransformation.class.st index 96b7c070d99..c8a40ddb191 100644 --- a/src/Refactoring-Core/RBGeneratePrintOnTransformation.class.st +++ b/src/Refactoring-Core/RBGeneratePrintOnTransformation.class.st @@ -27,37 +27,39 @@ printOn: aStream ``` " Class { - #name : #RBGeneratePrintOnTransformation, - #superclass : #RBClassRefactoring, + #name : 'RBGeneratePrintOnTransformation', + #superclass : 'RBClassRefactoring', #instVars : [ 'variables' ], - #category : #'Refactoring-Core-Transformation' + #category : 'Refactoring-Core-Transformation', + #package : 'Refactoring-Core', + #tag : 'Transformation' } -{ #category : #displaying } +{ #category : 'displaying' } RBGeneratePrintOnTransformation class >> basicMenuItemString [ ^ 'Generate printOn:' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBGeneratePrintOnTransformation class >> className: aClass variables: anArray [ ^ (self className: aClass) variables: anArray ] -{ #category : #testing } +{ #category : 'testing' } RBGeneratePrintOnTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBGeneratePrintOnTransformation class >> model: aNamespace className: aClass variables: anArray [ ^ (self model: aNamespace className: aClass) variables: anArray ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBGeneratePrintOnTransformation >> preconditions [ "Checks that the class actually defines all the variables that will be part of the printOn:." @@ -69,7 +71,7 @@ RBGeneratePrintOnTransformation >> preconditions [ (RBCondition definesInstanceVariable: variable in: self theClass) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBGeneratePrintOnTransformation >> privateTransform [ | method | method := self parserClass @@ -92,12 +94,12 @@ RBGeneratePrintOnTransformation >> privateTransform [ withProtocol: #printing) ] -{ #category : #accessing } +{ #category : 'accessing' } RBGeneratePrintOnTransformation >> theClass [ ^ (self classObjectFor: className) instanceSide ] -{ #category : #accessing } +{ #category : 'accessing' } RBGeneratePrintOnTransformation >> variables: anArray [ variables := anArray ] diff --git a/src/Refactoring-Core/RBInlineAllSendersRefactoring.class.st b/src/Refactoring-Core/RBInlineAllSendersRefactoring.class.st index 58b3cb356e1..0a7b1493c49 100644 --- a/src/Refactoring-Core/RBInlineAllSendersRefactoring.class.st +++ b/src/Refactoring-Core/RBInlineAllSendersRefactoring.class.st @@ -28,8 +28,8 @@ baz " Class { - #name : #RBInlineAllSendersRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBInlineAllSendersRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'numberReplaced', @@ -37,10 +37,12 @@ Class { 'pattern', 'selectorString' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineAllSendersRefactoring class >> model: aRBSmalltalk sendersOf: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -48,20 +50,20 @@ RBInlineAllSendersRefactoring class >> model: aRBSmalltalk sendersOf: aSelector yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineAllSendersRefactoring class >> sendersOf: aSelector in: aClass [ ^ self new sendersOf: aSelector in: aClass ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> checkInlinedMethods [ numberReplaced = 0 ifTrue: [self inform: 'Could not find any senders to inline into'] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> initializePatternFor: aClass [ pattern := nil. (aClass = class or: [(aClass directlyDefinesMethod: selector) not]) ifTrue: [ @@ -72,7 +74,7 @@ RBInlineAllSendersRefactoring >> initializePatternFor: aClass [ pattern := 'super ' , self selectorString ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> inlineMessagesInClass: aClass andSelector: aSelector [ | messagesToInline previousCountOfMessages rbMethod | previousCountOfMessages := 4294967295. "Some really large number > # of initial self sends." @@ -95,7 +97,7 @@ RBInlineAllSendersRefactoring >> inlineMessagesInClass: aClass andSelector: aSel numberNotReplaced := numberNotReplaced + messagesToInline ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> inlineSelfSends [ class withAllSubclasses do: [:each | @@ -107,12 +109,12 @@ RBInlineAllSendersRefactoring >> inlineSelfSends [ selectors do: [:sel | self inlineMessagesInClass: each andSelector: sel]]] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> messagePattern [ ^'self ' , (self buildSelectorString: selector) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> numberOfSelfSendsIn: aParseTree [ | search | search := self parseTreeSearcher. @@ -122,12 +124,12 @@ RBInlineAllSendersRefactoring >> numberOfSelfSendsIn: aParseTree [ ^ search executeTree: aParseTree initialAnswer: 0 ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInlineAllSendersRefactoring >> preconditions [ ^RBCondition canUnderstand: selector in: class ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> privateTransform [ self inlineSelfSends; @@ -135,7 +137,7 @@ RBInlineAllSendersRefactoring >> privateTransform [ checkInlinedMethods ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> removeMethod [ self onError: [self generateChangesFor: (RBRemoveMethodRefactoring @@ -145,12 +147,12 @@ RBInlineAllSendersRefactoring >> removeMethod [ do: [] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> selectorString [ ^selectorString ifNil: [ selectorString := self buildSelectorString: selector ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineAllSendersRefactoring >> selfSendIn: aTree [ | searcher | searcher := self parseTreeSearcher. @@ -160,14 +162,14 @@ RBInlineAllSendersRefactoring >> selfSendIn: aTree [ ^ searcher executeTree: aTree initialAnswer: nil ] -{ #category : #initialization } +{ #category : 'initialization' } RBInlineAllSendersRefactoring >> sendersOf: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. numberReplaced := numberNotReplaced := 0 ] -{ #category : #printing } +{ #category : 'printing' } RBInlineAllSendersRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBInlineMethodFromComponentRefactoring.class.st b/src/Refactoring-Core/RBInlineMethodFromComponentRefactoring.class.st index 0661727a461..e95c31414e3 100644 --- a/src/Refactoring-Core/RBInlineMethodFromComponentRefactoring.class.st +++ b/src/Refactoring-Core/RBInlineMethodFromComponentRefactoring.class.st @@ -6,12 +6,14 @@ where this implementation is taken from or choose one if there are move than one If the method implementation has some direct variable references, accessor for this variable are created (just as by the generate accessor refactoring). " Class { - #name : #RBInlineMethodFromComponentRefactoring, - #superclass : #RBInlineMethodRefactoring, - #category : #'Refactoring-Core-Refactorings-Unused' + #name : 'RBInlineMethodFromComponentRefactoring', + #superclass : 'RBInlineMethodRefactoring', + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> abstractVariableReferences [ | refactoring | refactoring := RBAbstractVariablesRefactoring @@ -23,14 +25,14 @@ RBInlineMethodFromComponentRefactoring >> abstractVariableReferences [ inlineParseTree := refactoring parseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> addArgumentToSelector: aSymbol [ ^aSymbol isInfix ifTrue: [#value:value:] ifFalse: [(aSymbol , 'value:') asSymbol] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> addSelfReferenceToInlineParseTree [ | variableName rewriter newArguments | @@ -46,7 +48,7 @@ RBInlineMethodFromComponentRefactoring >> addSelfReferenceToInlineParseTree [ sourceMessage receiver replaceWith: (RBVariableNode named: variableName) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> addSelfReferenceToSourceMessage [ | newArguments | @@ -55,7 +57,7 @@ RBInlineMethodFromComponentRefactoring >> addSelfReferenceToSourceMessage [ sourceMessage renameSelector: (self addArgumentToSelector: sourceMessage selector) andArguments: newArguments ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> checkSuperMessages [ inlineParseTree superMessages isEmpty ifFalse: @@ -63,7 +65,7 @@ RBInlineMethodFromComponentRefactoring >> checkSuperMessages [ refactoringError: 'Cannot inline method since it sends a super message'] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> classOfTheMethodToInline [ | imps | @@ -78,7 +80,7 @@ RBInlineMethodFromComponentRefactoring >> classOfTheMethodToInline [ ^ classOfTheMethodToInline ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> findSelectedMessage [ sourceParseTree := class parseTreeForSelector: sourceSelector. @@ -92,7 +94,7 @@ RBInlineMethodFromComponentRefactoring >> findSelectedMessage [ ifFalse: [ self refactoringError: 'The selection doesn''t appear to be a message send' ] ] -{ #category : #testing } +{ #category : 'testing' } RBInlineMethodFromComponentRefactoring >> isOverridden [ | selector| selector := self inlineSelector. @@ -102,13 +104,13 @@ RBInlineMethodFromComponentRefactoring >> isOverridden [ ^ false ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> nameOfTheClassOfTheMethodToInline [ ^ self classOfTheMethodToInline instanceSide name ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> newNameForSelf [ | variableName index originalName nonMetaClass | @@ -128,20 +130,20 @@ RBInlineMethodFromComponentRefactoring >> newNameForSelf [ ^ variableName ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> privateTransform [ self abstractVariableReferences. self renameSelfReferences. super privateTransform ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> renameSelfReferences [ self addSelfReferenceToSourceMessage. self addSelfReferenceToInlineParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodFromComponentRefactoring >> safeVariableNameBasedOn: aString [ "Creates an unused variable name containing aString" diff --git a/src/Refactoring-Core/RBInlineMethodRefactoring.class.st b/src/Refactoring-Core/RBInlineMethodRefactoring.class.st index 18690a55a44..7531dcec8b9 100644 --- a/src/Refactoring-Core/RBInlineMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBInlineMethodRefactoring.class.st @@ -9,8 +9,8 @@ My preconditions verify that the inlined method is not a primitive call, the met " Class { - #name : #RBInlineMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBInlineMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'sourceInterval', 'inlineParseTree', @@ -20,10 +20,12 @@ Class { 'checkOverridden', 'classOfTheMethodToInline' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineMethodRefactoring class >> inline: anInterval inMethod: aSelector forClass: aClass [ ^ self new inline: anInterval @@ -31,7 +33,7 @@ RBInlineMethodRefactoring class >> inline: anInterval inMethod: aSelector forCla forClass: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineMethodRefactoring class >> model: aRBSmalltalk inline: anInterval inMethod: aSelector forClass: aClass [ ^ self new model: aRBSmalltalk; @@ -41,12 +43,12 @@ RBInlineMethodRefactoring class >> model: aRBSmalltalk inline: anInterval inMeth yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> addSelfReturn [ inlineParseTree addSelfReturn ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> addTemporary: sourceNode assignedTo: replacementNode [ | newName | newName := self renameConflictingTemporary: sourceNode name. @@ -56,17 +58,17 @@ RBInlineMethodRefactoring >> addTemporary: sourceNode assignedTo: replacementNod value: replacementNode) ] -{ #category : #accessing } +{ #category : 'accessing' } RBInlineMethodRefactoring >> checkOverridden [ ^ checkOverridden ifNil: [ checkOverridden := true ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBInlineMethodRefactoring >> checkOverridden: aBoolean [ checkOverridden := aBoolean ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> checkSuperMessages [ self classOfTheMethodToInline = class @@ -83,7 +85,7 @@ RBInlineMethodRefactoring >> checkSuperMessages [ ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> classOfTheMethodToInline [ ^ classOfTheMethodToInline @@ -94,13 +96,13 @@ RBInlineMethodRefactoring >> classOfTheMethodToInline [ ifNotNil: [ classOfTheMethodToInline ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> compileMethod [ class compileTree: sourceParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> findSelectedMessage [ sourceParseTree := class parseTreeForSelector: sourceSelector. @@ -116,7 +118,7 @@ RBInlineMethodRefactoring >> findSelectedMessage [ ifFalse: [ self refactoringError: 'Cannot inline non-self messages' ] ] -{ #category : #testing } +{ #category : 'testing' } RBInlineMethodRefactoring >> hasMultipleReturns [ "Do we have multiple returns? If the last statement isn't a return, then we have an implicit return of self." @@ -134,26 +136,26 @@ RBInlineMethodRefactoring >> hasMultipleReturns [ ^ false ] -{ #category : #initialization } +{ #category : 'initialization' } RBInlineMethodRefactoring >> inline: anInterval inMethod: aSelector forClass: aClass [ sourceSelector := aSelector. class := self classObjectFor: aClass. sourceInterval := anInterval ] -{ #category : #accessing } +{ #category : 'accessing' } RBInlineMethodRefactoring >> inlineParseTree [ ^ inlineParseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> inlineSelector [ sourceMessage ifNil: [ self findSelectedMessage ]. ^ sourceMessage selector ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> inlineSourceReplacing: aParseTree [ | statements nodeUnderSequence | statements := inlineParseTree body statements. @@ -171,7 +173,7 @@ RBInlineMethodRefactoring >> inlineSourceReplacing: aParseTree [ ifFalse: [ statements last ]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> insertInlinedMethod [ | node | @@ -191,19 +193,19 @@ RBInlineMethodRefactoring >> insertInlinedMethod [ self removeImmediateBlocks ] -{ #category : #testing } +{ #category : 'testing' } RBInlineMethodRefactoring >> isOverridden [ | selector| selector := self inlineSelector. ^ class subclassRedefines: selector ] -{ #category : #testing } +{ #category : 'testing' } RBInlineMethodRefactoring >> isPrimitive [ ^inlineParseTree isPrimitive ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> moveComments [ inlineParseTree nodesDo: [:each | @@ -219,7 +221,7 @@ RBInlineMethodRefactoring >> moveComments [ RBComment with: aComment contents at: start])] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> normalizeIfTrues [ | rewriter | rewriter := self parseTreeRewriter. @@ -232,7 +234,7 @@ RBInlineMethodRefactoring >> normalizeIfTrues [ whileTrue: [inlineParseTree := rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> normalizeReturns [ | rewriter | rewriter := self parseTreeRewriter. @@ -257,7 +259,7 @@ RBInlineMethodRefactoring >> normalizeReturns [ whileTrue: [inlineParseTree := rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> parseInlineMethod [ self classOfTheMethodToInline @@ -273,7 +275,7 @@ RBInlineMethodRefactoring >> parseInlineMethod [ ifFalse: [ inlineParseTree addSelfReturn ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInlineMethodRefactoring >> preconditions [ "Even though it looks complex it only does preconditions and set up. `transform` does actual refactoring" ^ (RBCondition definesSelector: sourceSelector in: class) @@ -298,7 +300,7 @@ RBInlineMethodRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> privateTransform [ self renameConflictingTemporaries; @@ -306,7 +308,7 @@ RBInlineMethodRefactoring >> privateTransform [ compileMethod ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> removeEmptyIfTrues [ | rewriter | rewriter := self parseTreeRewriter. @@ -323,7 +325,7 @@ RBInlineMethodRefactoring >> removeEmptyIfTrues [ ifTrue: [sourceParseTree := rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> removeImmediateBlocks [ | rewriter | rewriter := self parseTreeRewriter. @@ -338,13 +340,13 @@ RBInlineMethodRefactoring >> removeImmediateBlocks [ ifTrue: [sourceParseTree := rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> renameConflictingTemporaries [ inlineParseTree allDefinedVariables do: [:each | self renameConflictingTemporary: each] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> renameConflictingTemporary: aName [ | allNames newName index seqNode | allNames := (Set new) @@ -367,7 +369,7 @@ RBInlineMethodRefactoring >> renameConflictingTemporary: aName [ ^newName ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> renameTemporary: oldName to: newName [ | rewriter | rewriter := self parseTreeRewriter. @@ -378,7 +380,7 @@ RBInlineMethodRefactoring >> renameTemporary: oldName to: newName [ ifTrue: [inlineParseTree := rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> replaceArgument: sourceNode with: replacementNode [ | rewriter | rewriter := self parseTreeRewriter. @@ -387,7 +389,7 @@ RBInlineMethodRefactoring >> replaceArgument: sourceNode with: replacementNode [ ifTrue: [inlineParseTree body: rewriter tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> replaceArguments [ sourceMessage arguments reversed with: inlineParseTree arguments reversed @@ -397,7 +399,7 @@ RBInlineMethodRefactoring >> replaceArguments [ ifFalse: [ self addTemporary: source assignedTo: replacement ] ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> rewriteCascadedMessage [ | index messages | @@ -412,7 +414,7 @@ RBInlineMethodRefactoring >> rewriteCascadedMessage [ inlineParseTree addReturn ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> rewriteInlinedTree [ sourceMessage parent isReturn ifTrue: @@ -426,12 +428,12 @@ RBInlineMethodRefactoring >> rewriteInlinedTree [ addSelfReturn] ] -{ #category : #accessing } +{ #category : 'accessing' } RBInlineMethodRefactoring >> sourceSelector [ ^ sourceSelector ] -{ #category : #printing } +{ #category : 'printing' } RBInlineMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -445,7 +447,7 @@ RBInlineMethodRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineMethodRefactoring >> writeGuardClauses [ | rewriter | rewriter := self parseTreeRewriter. diff --git a/src/Refactoring-Core/RBInlineParameterRefactoring.class.st b/src/Refactoring-Core/RBInlineParameterRefactoring.class.st index 74a179b0218..68e53cff3f5 100644 --- a/src/Refactoring-Core/RBInlineParameterRefactoring.class.st +++ b/src/Refactoring-Core/RBInlineParameterRefactoring.class.st @@ -38,15 +38,17 @@ method1 ``` " Class { - #name : #RBInlineParameterRefactoring, - #superclass : #RBRemoveParameterRefactoring, + #name : 'RBInlineParameterRefactoring', + #superclass : 'RBRemoveParameterRefactoring', #instVars : [ 'expressions' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineParameterRefactoring class >> inlineParameter: aString in: aClass selector: aSelector [ ^ self new inlineParameter: aString @@ -54,7 +56,7 @@ RBInlineParameterRefactoring class >> inlineParameter: aString in: aClass select selector: aSelector ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineParameterRefactoring class >> model: aRBSmalltalk inlineParameter: aString in: aClass selector: aSelector [ ^ self new model: aRBSmalltalk; @@ -64,7 +66,7 @@ RBInlineParameterRefactoring class >> model: aRBSmalltalk inlineParameter: aStri yourself ] -{ #category : #private } +{ #category : 'private' } RBInlineParameterRefactoring >> allExpressionsToInline [ | coll | coll := Set new. @@ -77,7 +79,7 @@ RBInlineParameterRefactoring >> allExpressionsToInline [ ^coll asOrderedCollection ] -{ #category : #private } +{ #category : 'private' } RBInlineParameterRefactoring >> expressionsToInlineFrom: aTree [ | searcher | searcher := self parseTreeSearcher. @@ -90,14 +92,14 @@ RBInlineParameterRefactoring >> expressionsToInlineFrom: aTree [ ^ searcher executeTree: aTree initialAnswer: OrderedCollection new ] -{ #category : #initialization } +{ #category : 'initialization' } RBInlineParameterRefactoring >> inlineParameter: aString in: aClass selector: aSelector [ oldSelector := aSelector. class := self classObjectFor: aClass. argument := aString ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineParameterRefactoring >> modifyImplementorParseTree: parseTree in: aClass [ | node assignment | node := (parseTree arguments at: parameterIndex) copy. @@ -107,7 +109,7 @@ RBInlineParameterRefactoring >> modifyImplementorParseTree: parseTree in: aClass super modifyImplementorParseTree: parseTree in: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInlineParameterRefactoring >> myConditions [ self getNewSelector. expressions := self allExpressionsToInline. @@ -120,7 +122,7 @@ RBInlineParameterRefactoring >> myConditions [ errorMacro: 'All values passed must be literal.') ] -{ #category : #printing } +{ #category : 'printing' } RBInlineParameterRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBInlineTemporaryRefactoring.class.st b/src/Refactoring-Core/RBInlineTemporaryRefactoring.class.st index 52dc0908155..d45197ec3a6 100644 --- a/src/Refactoring-Core/RBInlineTemporaryRefactoring.class.st +++ b/src/Refactoring-Core/RBInlineTemporaryRefactoring.class.st @@ -5,8 +5,8 @@ All references to the temporary variable in this method are replaced by the valu The initialization and declaration of this variable will be removed. You need to select the variable and its initial assignment code to apply this refactoring. " Class { - #name : #RBInlineTemporaryRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBInlineTemporaryRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'sourceInterval', 'selector', @@ -14,10 +14,12 @@ Class { 'assignmentNode', 'definingNode' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineTemporaryRefactoring class >> inline: anInterval from: aSelector in: aClass [ ^ self new inline: anInterval @@ -25,7 +27,7 @@ RBInlineTemporaryRefactoring class >> inline: anInterval from: aSelector in: aCl in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInlineTemporaryRefactoring class >> model: aRBSmalltalk inline: anInterval from: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -35,12 +37,12 @@ RBInlineTemporaryRefactoring class >> model: aRBSmalltalk inline: anInterval fro yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineTemporaryRefactoring >> compileMethod [ class compileTree: sourceTree ] -{ #category : #testing } +{ #category : 'testing' } RBInlineTemporaryRefactoring >> hasOnlyOneAssignment [ | searcher | searcher := self parseTreeSearcher. @@ -50,14 +52,14 @@ RBInlineTemporaryRefactoring >> hasOnlyOneAssignment [ ^ (searcher executeTree: definingNode initialAnswer: 0) == 1 ] -{ #category : #initialization } +{ #category : 'initialization' } RBInlineTemporaryRefactoring >> inline: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. sourceInterval := anInterval ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInlineTemporaryRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition withBlock: @@ -65,7 +67,7 @@ RBInlineTemporaryRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineTemporaryRefactoring >> privateTransform [ self replaceAssignment; @@ -73,14 +75,14 @@ RBInlineTemporaryRefactoring >> privateTransform [ compileMethod ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineTemporaryRefactoring >> replaceAssignment [ assignmentNode parent isSequence ifTrue: [assignmentNode parent removeNode: assignmentNode] ifFalse: [assignmentNode replaceWith: assignmentNode value] ] -{ #category : #transforming } +{ #category : 'transforming' } RBInlineTemporaryRefactoring >> replaceReferences [ | rewriter | rewriter := self parseTreeRewriter. @@ -90,7 +92,7 @@ RBInlineTemporaryRefactoring >> replaceReferences [ rewriter executeTree: definingNode ] -{ #category : #printing } +{ #category : 'printing' } RBInlineTemporaryRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -104,7 +106,7 @@ RBInlineTemporaryRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInlineTemporaryRefactoring >> verifySelectedInterval [ sourceTree := class parseTreeForSelector: selector. diff --git a/src/Refactoring-Core/RBInsertNewClassRefactoring.class.st b/src/Refactoring-Core/RBInsertNewClassRefactoring.class.st index 27ee3b987e5..0deb6c3327c 100644 --- a/src/Refactoring-Core/RBInsertNewClassRefactoring.class.st +++ b/src/Refactoring-Core/RBInsertNewClassRefactoring.class.st @@ -9,18 +9,20 @@ My preconditions verify that I use a valid class name, that does not yet exists and the subclasses (if any) were direct subclasses of the superclass. " Class { - #name : #RBInsertNewClassRefactoring, - #superclass : #RBClassRefactoring, + #name : 'RBInsertNewClassRefactoring', + #superclass : 'RBClassRefactoring', #instVars : [ 'category', 'superclass', 'subclasses', 'comment' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInsertNewClassRefactoring class >> addClass: aName superclass: aClass subclasses: aCollection category: aSymbol [ ^ self new addClass: aName @@ -29,7 +31,7 @@ RBInsertNewClassRefactoring class >> addClass: aName superclass: aClass subclass category: aSymbol ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInsertNewClassRefactoring class >> model: aRBSmalltalk addClass: aName superclass: aClass subclasses: aCollection category: aSymbol [ ^ self new model: aRBSmalltalk; @@ -40,7 +42,7 @@ RBInsertNewClassRefactoring class >> model: aRBSmalltalk addClass: aName supercl yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBInsertNewClassRefactoring class >> model: aRBSmalltalk addClass: aName superclass: aClass subclasses: aCollection category: aSymbol comment: aCommentString [ ^ self new model: aRBSmalltalk; @@ -52,13 +54,13 @@ RBInsertNewClassRefactoring class >> model: aRBSmalltalk addClass: aName supercl yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBInsertNewClassRefactoring >> addClass: aName superclass: aClass subclasses: aCollection category: aSymbol [ self addClass: aName superclass: aClass subclasses: aCollection category: aSymbol comment: '' ] -{ #category : #initialization } +{ #category : 'initialization' } RBInsertNewClassRefactoring >> addClass: aName superclass: aClass subclasses: aCollection category: aSymbol comment: aCommentString [ self className: aName. superclass := self classObjectFor: aClass. @@ -67,7 +69,7 @@ RBInsertNewClassRefactoring >> addClass: aName superclass: aClass subclasses: aC comment := aCommentString ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBInsertNewClassRefactoring >> preconditions [ | cond | cond := ((RBCondition isMetaclass: superclass) @@ -86,7 +88,7 @@ RBInsertNewClassRefactoring >> preconditions [ errorMacro: 'Invalid category name') ] -{ #category : #transforming } +{ #category : 'transforming' } RBInsertNewClassRefactoring >> privateTransform [ | classDefinitionString | @@ -99,7 +101,7 @@ RBInsertNewClassRefactoring >> privateTransform [ reparentClasses: subclasses to: (self model classNamed: className asSymbol) ] -{ #category : #printing } +{ #category : 'printing' } RBInsertNewClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBMakeClassAbstractTransformation.class.st b/src/Refactoring-Core/RBMakeClassAbstractTransformation.class.st index b3f7c2e6733..f3a70823d29 100644 --- a/src/Refactoring-Core/RBMakeClassAbstractTransformation.class.st +++ b/src/Refactoring-Core/RBMakeClassAbstractTransformation.class.st @@ -4,46 +4,48 @@ It just adds class side method `isAbstract` to the selected class, and as such c So it is behavior preserving but we prefer to stress the fact that we have no warranty that the class is really abstract. " Class { - #name : #RBMakeClassAbstractTransformation, - #superclass : #RBClassRefactoring, + #name : 'RBMakeClassAbstractTransformation', + #superclass : 'RBClassRefactoring', #instVars : [ 'targetClass' ], - #category : #'Refactoring-Core-Transformation' + #category : 'Refactoring-Core-Transformation', + #package : 'Refactoring-Core', + #tag : 'Transformation' } -{ #category : #displaying } +{ #category : 'displaying' } RBMakeClassAbstractTransformation class >> basicMenuItemString [ ^ 'Make abstract' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMakeClassAbstractTransformation class >> class: targetClass [ ^ self new class: targetClass ] -{ #category : #testing } +{ #category : 'testing' } RBMakeClassAbstractTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMakeClassAbstractTransformation >> class: class [ targetClass := class ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMakeClassAbstractTransformation >> preconditions [ "We cannot validate that the class is actually not used and not receiving a message new." ^ self skippingPreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBMakeClassAbstractTransformation >> privateTransform [ (RBAddMethodTransformation @@ -54,7 +56,7 @@ RBMakeClassAbstractTransformation >> privateTransform [ withProtocol: #testing) execute ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMakeClassAbstractTransformation >> skippingPreconditions [ "We cannot validate that the class is actually not used and not receiving a message new." diff --git a/src/Refactoring-Core/RBMatchVisitor.class.st b/src/Refactoring-Core/RBMatchVisitor.class.st index 415e17b4ab0..6008072a66f 100644 --- a/src/Refactoring-Core/RBMatchVisitor.class.st +++ b/src/Refactoring-Core/RBMatchVisitor.class.st @@ -2,22 +2,24 @@ I am a visitor to change temporaries and arguments to generic names (`tempMatch , `argMatch) " Class { - #name : #RBMatchVisitor, - #superclass : #RBProgramNodeVisitor, + #name : 'RBMatchVisitor', + #superclass : 'RBProgramNodeVisitor', #instVars : [ 'arguments', 'temporaries', 'difference' ], - #category : #'Refactoring-Core-Base' + #category : 'Refactoring-Core-Base', + #package : 'Refactoring-Core', + #tag : 'Base' } -{ #category : #accessing } +{ #category : 'accessing' } RBMatchVisitor >> difference [ ^ difference ] -{ #category : #initialization } +{ #category : 'initialization' } RBMatchVisitor >> initialize [ super initialize . arguments := 0 . @@ -25,14 +27,14 @@ RBMatchVisitor >> initialize [ difference := 0 ] -{ #category : #accessing } +{ #category : 'accessing' } RBMatchVisitor >> replace: temp with: aString [ |definingNode| definingNode := temp whoDefines: temp name. (RBParseTreeRewriter rename: temp name to: aString) executeTree: definingNode ] -{ #category : #visiting } +{ #category : 'visiting' } RBMatchVisitor >> visitBlockNode: aBlockNode [ aBlockNode arguments do: [ :arg | self replace: arg with: ('tempMatch', temporaries asString). @@ -40,7 +42,7 @@ RBMatchVisitor >> visitBlockNode: aBlockNode [ super visitBlockNode: aBlockNode ] -{ #category : #visiting } +{ #category : 'visiting' } RBMatchVisitor >> visitMethodNode: aMethodNode [ aMethodNode arguments do: [ :arg | difference := difference + (('argMatch', arguments asString )size- (arg name asString )size + 2 ). @@ -49,7 +51,7 @@ RBMatchVisitor >> visitMethodNode: aMethodNode [ super visitMethodNode: aMethodNode ] -{ #category : #visiting } +{ #category : 'visiting' } RBMatchVisitor >> visitSequenceNode: aSequenceNode [ |isMethod| isMethod := aSequenceNode parent isMethod. diff --git a/src/Refactoring-Core/RBMergeInstanceVariableIntoAnother.class.st b/src/Refactoring-Core/RBMergeInstanceVariableIntoAnother.class.st index 7058ba48ebb..211bcb62bb8 100644 --- a/src/Refactoring-Core/RBMergeInstanceVariableIntoAnother.class.st +++ b/src/Refactoring-Core/RBMergeInstanceVariableIntoAnother.class.st @@ -34,12 +34,14 @@ Foo >> foo ``` " Class { - #name : #RBMergeInstanceVariableIntoAnother, - #superclass : #RBRenameInstanceVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBMergeInstanceVariableIntoAnother', + #superclass : 'RBRenameInstanceVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBMergeInstanceVariableIntoAnother >> preconditions [ ^ (RBCondition withBlock: [ (variableName = newName) @@ -49,7 +51,7 @@ RBMergeInstanceVariableIntoAnother >> preconditions [ & (RBCondition definesInstanceVariable: newName in: class) ] -{ #category : #transforming } +{ #category : 'transforming' } RBMergeInstanceVariableIntoAnother >> privateTransform [ renameAccessors ifTrue: [ self removeOldAccessors @@ -62,7 +64,7 @@ RBMergeInstanceVariableIntoAnother >> privateTransform [ self renameAccessorsReferences ] -{ #category : #transforming } +{ #category : 'transforming' } RBMergeInstanceVariableIntoAnother >> renameVariable [ model renameInstanceVariable: variableName diff --git a/src/Refactoring-Core/RBMetaclass.class.st b/src/Refactoring-Core/RBMetaclass.class.st index 655adbf9e44..46a6a060161 100644 --- a/src/Refactoring-Core/RBMetaclass.class.st +++ b/src/Refactoring-Core/RBMetaclass.class.st @@ -5,19 +5,21 @@ I shouldn't be created directly, but always be part of a refactoring namespace. My namespace usally knows me and my non meta class. " Class { - #name : #RBMetaclass, - #superclass : #RBAbstractClass, - #category : #'Refactoring-Core-Model' + #name : 'RBMetaclass', + #superclass : 'RBAbstractClass', + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMetaclass class >> existingNamed: aSymbol [ ^(self named: aSymbol) realName: aSymbol; yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMetaclass class >> existingNamed: aSymbol model: aRBNamespace [ ^ (self named: aSymbol) model: aRBNamespace; @@ -25,58 +27,58 @@ RBMetaclass class >> existingNamed: aSymbol model: aRBNamespace [ yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMetaclass class >> named: aSymbol [ ^(self new) name: aSymbol; yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBMetaclass >> allClassVariableNames [ ^ self instanceSide allClassVariableNames ] -{ #category : #accessing } +{ #category : 'accessing' } RBMetaclass >> allPoolDictionaryNames [ ^ self instanceSide allPoolDictionaryNames ] -{ #category : #accessing } +{ #category : 'accessing' } RBMetaclass >> classSide [ "Return the metaclass of the couple class/metaclass. Useful to avoid explicit test." ^ self ] -{ #category : #testing } +{ #category : 'testing' } RBMetaclass >> directlyDefinesClassVariable: aString [ ^ self instanceSide directlyDefinesClassVariable: aString ] -{ #category : #testing } +{ #category : 'testing' } RBMetaclass >> directlyDefinesPoolDictionary: aString [ ^ self instanceSide directlyDefinesPoolDictionary: aString ] -{ #category : #testing } +{ #category : 'testing' } RBMetaclass >> isMeta [ ^true ] -{ #category : #printing } +{ #category : 'printing' } RBMetaclass >> printOn: aStream [ super printOn: aStream. aStream nextPutAll: ' class' ] -{ #category : #initialization } +{ #category : 'initialization' } RBMetaclass >> realName: aSymbol [ self realClass: (self model environment at: aSymbol) classSide ] -{ #category : #printing } +{ #category : 'printing' } RBMetaclass >> storeOn: aStream [ super storeOn: aStream. aStream nextPutAll: ' class' diff --git a/src/Refactoring-Core/RBMethod.class.st b/src/Refactoring-Core/RBMethod.class.st index 6198f62ac38..939ee0d6b10 100644 --- a/src/Refactoring-Core/RBMethod.class.st +++ b/src/Refactoring-Core/RBMethod.class.st @@ -11,8 +11,8 @@ I only implement a small part of CompiledMethod interface, that is used for ref " Class { - #name : #RBMethod, - #superclass : #RBEntity, + #name : 'RBMethod', + #superclass : 'RBEntity', #instVars : [ 'compiledMethod', 'class', @@ -20,10 +20,12 @@ Class { 'source', 'isFromTrait' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMethod class >> for: aRBClass fromMethod: aCompiledMethod andSelector: aSymbol [ ^ self new modelClass: aRBClass; @@ -32,7 +34,7 @@ RBMethod class >> for: aRBClass fromMethod: aCompiledMethod andSelector: aSymbol yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMethod class >> for: aRBClass source: aString selector: aSelector [ ^(self new) modelClass: aRBClass; @@ -41,17 +43,17 @@ RBMethod class >> for: aRBClass source: aString selector: aSelector [ yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> argumentNames [ ^ self ast argumentNames ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> ast [ ^ self parseTree ] -{ #category : #compiling } +{ #category : 'compiling' } RBMethod >> compileTree: aBRMethodNode [ | method sourceCode change | sourceCode := aBRMethodNode newSource. @@ -67,17 +69,17 @@ RBMethod >> compileTree: aBRMethodNode [ ^ change ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> isFromTrait [ ^ isFromTrait ifNil: [ isFromTrait := false ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> isFromTrait: anObject [ isFromTrait := anObject ] -{ #category : #private } +{ #category : 'private' } RBMethod >> literal: anObject containsReferenceTo: aSymbol [ anObject = aSymbol ifTrue: [ ^ true ]. @@ -86,40 +88,40 @@ RBMethod >> literal: anObject containsReferenceTo: aSymbol [ ^ anObject anySatisfy: [ :each | self literal: each containsReferenceTo: aSymbol ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> method [ ^compiledMethod ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> method: aCompiledMethod [ compiledMethod := aCompiledMethod. self isFromTrait: compiledMethod isFromTrait ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> methodClass [ ^ class ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> modelClass [ ^class ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> modelClass: aRBClass [ class := aRBClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> package [ compiledMethod ifNotNil: [ ^ compiledMethod package name ]. ^ class category ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> parseTree [ | tree | tree := self parserClass @@ -129,17 +131,17 @@ RBMethod >> parseTree [ ^ tree ] -{ #category : #testing } +{ #category : 'testing' } RBMethod >> parseTreeSearcherClass [ ^ RBParseTreeSearcher ] -{ #category : #testing } +{ #category : 'testing' } RBMethod >> parserTreeSearcher [ ^ self parseTreeSearcherClass new ] -{ #category : #printing } +{ #category : 'printing' } RBMethod >> printOn: aStream [ class printOn: aStream. aStream @@ -147,12 +149,12 @@ RBMethod >> printOn: aStream [ nextPutAll: self selector ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> protocols [ ^ self modelClass protocolsFor: self selector ] -{ #category : #testing } +{ #category : 'testing' } RBMethod >> refersToClassNamed: aSymbol [ | searcher | searcher := self parserTreeSearcher. @@ -161,7 +163,7 @@ RBMethod >> refersToClassNamed: aSymbol [ or: [ self refersToSymbol: aSymbol ] ] -{ #category : #testing } +{ #category : 'testing' } RBMethod >> refersToSymbol: aSymbol [ | searcher | searcher := self parserTreeSearcher. @@ -179,7 +181,7 @@ RBMethod >> refersToSymbol: aSymbol [ ^ searcher executeTree: self parseTree initialAnswer: false ] -{ #category : #testing } +{ #category : 'testing' } RBMethod >> refersToVariable: aString [ | searcher tree | tree := self parseTree. @@ -196,22 +198,22 @@ RBMethod >> refersToVariable: aString [ ^ searcher executeTree: self parseTree initialAnswer: false ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> selector [ ^ selector ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> selector: aSymbol [ selector := aSymbol ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> source [ ^ source ifNil: [ source := (class realClass sourceCodeAt: selector) asString ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethod >> source: aString [ source := aString ] diff --git a/src/Refactoring-Core/RBMethodName.class.st b/src/Refactoring-Core/RBMethodName.class.st index ad89ed43d4f..11a73521370 100644 --- a/src/Refactoring-Core/RBMethodName.class.st +++ b/src/Refactoring-Core/RBMethodName.class.st @@ -12,8 +12,8 @@ RBMethodName selector: 'color:' arguments:{'aColor'}. (RBMethodName selector:'color' arguments:{}) isValid. " Class { - #name : #RBMethodName, - #superclass : #Model, + #name : 'RBMethodName', + #superclass : 'Model', #instVars : [ 'selector', 'arguments', @@ -21,10 +21,12 @@ Class { 'permutation', 'renameMap' ], - #category : #'Refactoring-Core-Support' + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMethodName class >> selector: aSymbol arguments: stringCollection [ ^ self new selector: aSymbol; @@ -32,18 +34,18 @@ RBMethodName class >> selector: aSymbol arguments: stringCollection [ yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> arguments [ ^arguments ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> arguments: nameCollection [ arguments := nameCollection. self changed: #arguments ] -{ #category : #testing } +{ #category : 'testing' } RBMethodName >> isValid [ "Return whether the receiver looks like a method with a selector in sync with the arguments in a possible class" @@ -51,31 +53,31 @@ RBMethodName >> isValid [ and: [ selector numArgs = arguments size ]] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> newArgs [ ^ newArgs ifNil: [ newArgs := { } ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> newArgs: anObject [ newArgs := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> permutation [ ^ permutation ifNil: [ permutation := 1 to: arguments size ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> permutation: anObject [ permutation := anObject ] -{ #category : #printing } +{ #category : 'printing' } RBMethodName >> printOn: aStream [ | argumentStream | self isValid @@ -89,24 +91,24 @@ RBMethodName >> printOn: aStream [ aStream space; nextPutAll: argumentStream next ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> renameMap [ ^ renameMap ifNil: [ renameMap := { } ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> renameMap: anObject [ renameMap := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> selector [ ^selector ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodName >> selector: aSymbol [ selector := aSymbol asSymbol. self changed: #selector diff --git a/src/Refactoring-Core/RBMethodRefactoring.class.st b/src/Refactoring-Core/RBMethodRefactoring.class.st index f181f7aa6e4..f6c5bce0440 100644 --- a/src/Refactoring-Core/RBMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBMethodRefactoring.class.st @@ -4,21 +4,23 @@ I am an abstract base class for method refactorings. I only provide a helper method for generating selector names. " Class { - #name : #RBMethodRefactoring, - #superclass : #RBRefactoring, + #name : 'RBMethodRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'class' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBMethodRefactoring class >> isAbstract [ ^ self == RBMethodRefactoring ] -{ #category : #accessing } +{ #category : 'accessing' } RBMethodRefactoring >> methodClass [ ^ class ] diff --git a/src/Refactoring-Core/RBMoveMethodRefactoring.class.st b/src/Refactoring-Core/RBMoveMethodRefactoring.class.st index 31b6e0846f3..b819d864bdd 100644 --- a/src/Refactoring-Core/RBMoveMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBMoveMethodRefactoring.class.st @@ -30,8 +30,8 @@ Color>>#isBlack ``` " Class { - #name : #RBMoveMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBMoveMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'variable', @@ -40,10 +40,12 @@ Class { 'hasOnlySelfReturns', 'selfVariableName' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveMethodRefactoring class >> model: aRBSmalltalk selector: aSymbol class: aClass variable: aVariableName [ ^ self new model: aRBSmalltalk; @@ -51,20 +53,20 @@ RBMoveMethodRefactoring class >> model: aRBSmalltalk selector: aSymbol class: aC yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveMethodRefactoring class >> selector: aSymbol class: aClass variable: aVariableName [ ^ self new selector: aSymbol class: aClass variable: aVariableName; yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> abstractVariables [ self generateChangesFor: self abstractVariablesRefactoring. parseTree := self abstractVariablesRefactoring parseTree ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> abstractVariablesRefactoring [ ^RBAbstractVariablesRefactoring model: self model @@ -74,13 +76,13 @@ RBMoveMethodRefactoring >> abstractVariablesRefactoring [ ignoring: variable ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> addSelfReturn [ self hasOnlySelfReturns ifTrue: [^self]. parseTree addSelfReturn ] -{ #category : #private } +{ #category : 'private' } RBMoveMethodRefactoring >> buildParseTree [ parseTree := ( class parseTreeForSelector: selector ) copy. @@ -88,7 +90,7 @@ RBMoveMethodRefactoring >> buildParseTree [ parseTree doSemanticAnalysis ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> checkAssignmentsToVariable [ | searcher | variable @@ -103,13 +105,13 @@ RBMoveMethodRefactoring >> checkAssignmentsToVariable [ expandMacrosWith: variable) ] ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> checkForPrimitiveMethod [ parseTree isPrimitive ifTrue: [self refactoringError: 'Cannot move primitive methods'] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> checkForSuperReferences [ | searcher | searcher := self parseTreeSearcher. @@ -121,7 +123,7 @@ RBMoveMethodRefactoring >> checkForSuperReferences [ refactoringError: 'Cannot move the method since it has a super message send.' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> checkTemporaryVariableNames [ | varNames | varNames := parseTree allDefinedVariables. @@ -137,7 +139,7 @@ RBMoveMethodRefactoring >> checkTemporaryVariableNames [ with: name)]]] ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> compileDelegatorMethod [ | statementNode delegatorNode tree | delegatorNode := RBMessageNode @@ -154,13 +156,13 @@ RBMoveMethodRefactoring >> compileDelegatorMethod [ class compileTree: tree ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> compileNewMethods [ moveToClasses do: [:each | each compile: parseTree newSource withAttributesFrom: (class methodFor: selector)] ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> getArgumentNameForSelf [ self needsToReplaceSelfReferences ifFalse: [^self]. @@ -182,7 +184,7 @@ RBMoveMethodRefactoring >> getArgumentNameForSelf [ whileTrue: [] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBMoveMethodRefactoring >> getClassForGlobalOrClassVariable [ | definingClass type | definingClass := class whoDefinesClassVariable: (variable ifNil: ['']). @@ -195,7 +197,7 @@ RBMoveMethodRefactoring >> getClassForGlobalOrClassVariable [ moveToClasses ifNil: [ self refactoringError: 'Method not moved' ] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBMoveMethodRefactoring >> getClassesForInstanceVariable [ | definingClass typer types | @@ -209,7 +211,7 @@ RBMoveMethodRefactoring >> getClassesForInstanceVariable [ moveToClasses ifNil: [ self refactoringError: 'Method not moved' ] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBMoveMethodRefactoring >> getClassesForTemporaryVariable [ | types | @@ -220,7 +222,7 @@ RBMoveMethodRefactoring >> getClassesForTemporaryVariable [ moveToClasses ifNil: [ self refactoringError: 'Method not moved' ] ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBMoveMethodRefactoring >> getClassesToMoveTo [ self isMovingToArgument ifTrue: [self getClassesForTemporaryVariable] @@ -231,7 +233,7 @@ RBMoveMethodRefactoring >> getClassesToMoveTo [ moveToClasses ifEmpty: [self refactoringError: 'No classes selected, method not moved.'] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> getNewMethodName [ | newSelector parameters alreadyDefined methodName newMethodName | @@ -271,7 +273,7 @@ RBMoveMethodRefactoring >> getNewMethodName [ andArguments: ( parameters collect: [ :each | RBVariableNode named: each ] ) asArray ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> hasOnlySelfReturns [ ^ hasOnlySelfReturns @@ -286,7 +288,7 @@ RBMoveMethodRefactoring >> hasOnlySelfReturns [ ifNotNil: [ hasOnlySelfReturns ] ] -{ #category : #testing } +{ #category : 'testing' } RBMoveMethodRefactoring >> hasSelfReferences [ | searcher | searcher := self parseTreeSearcher. @@ -296,24 +298,24 @@ RBMoveMethodRefactoring >> hasSelfReferences [ ^ searcher executeTree: parseTree initialAnswer: false ] -{ #category : #testing } +{ #category : 'testing' } RBMoveMethodRefactoring >> isMovingToArgument [ ^(parseTree arguments collect: [:each | each name]) includes: variable ] -{ #category : #testing } +{ #category : 'testing' } RBMoveMethodRefactoring >> isMovingToInstVar [ ^self isMovingToArgument not and: [(class whoDefinesInstanceVariable: variable) notNil] ] -{ #category : #testing } +{ #category : 'testing' } RBMoveMethodRefactoring >> needsToReplaceSelfReferences [ ^self hasSelfReferences or: [self abstractVariablesRefactoring hasVariablesToAbstract] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition withBlock: @@ -328,7 +330,7 @@ RBMoveMethodRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> privateTransform [ self abstractVariables; @@ -339,7 +341,7 @@ RBMoveMethodRefactoring >> privateTransform [ compileDelegatorMethod ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> removeArgument [ "Removes the excess argument if any. This argument is the variable which is @@ -357,7 +359,7 @@ RBMoveMethodRefactoring >> removeArgument [ removeAt: removeIndex; yourself) asArray] ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> replaceSelfReferences [ | replacer | self needsToReplaceSelfReferences ifTrue: [ @@ -369,7 +371,7 @@ RBMoveMethodRefactoring >> replaceSelfReferences [ parseTree := replacer tree] ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> replaceVariableReferences [ | replacer | replacer := self parseTreeRewriter. @@ -378,14 +380,14 @@ RBMoveMethodRefactoring >> replaceVariableReferences [ parseTree := replacer tree ] -{ #category : #initialization } +{ #category : 'initialization' } RBMoveMethodRefactoring >> selector: aSymbol class: aClass variable: aVariableName [ selector := aSymbol. class := self classObjectFor: aClass. variable := aVariableName ] -{ #category : #printing } +{ #category : 'printing' } RBMoveMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -400,7 +402,7 @@ RBMoveMethodRefactoring >> storeOn: aStream [ nextPutAll: ''')' ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodRefactoring >> verifyTemporaryVariableDoesNotOverride [ (parseTree allDefinedVariables includes: selfVariableName) ifTrue: [ ^ false ]. diff --git a/src/Refactoring-Core/RBMoveMethodToClassRefactoring.class.st b/src/Refactoring-Core/RBMoveMethodToClassRefactoring.class.st index ad8d4f96c25..7b87a354056 100644 --- a/src/Refactoring-Core/RBMoveMethodToClassRefactoring.class.st +++ b/src/Refactoring-Core/RBMoveMethodToClassRefactoring.class.st @@ -11,22 +11,24 @@ method " Class { - #name : #RBMoveMethodToClassRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBMoveMethodToClassRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'method' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveMethodToClassRefactoring class >> method: aMethod class: aClass [ ^ self new method: aMethod class: aClass; yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveMethodToClassRefactoring class >> model: aRBSmalltalk method: aMethod class: aClass [ ^ self new model: aRBSmalltalk; @@ -34,7 +36,7 @@ RBMoveMethodToClassRefactoring class >> model: aRBSmalltalk method: aMethod clas yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassRefactoring >> classModelOf: aClass [ | classModel | @@ -45,18 +47,18 @@ RBMoveMethodToClassRefactoring >> classModelOf: aClass [ ^classModel ] -{ #category : #initialization } +{ #category : 'initialization' } RBMoveMethodToClassRefactoring >> method: aMethod class: aClass [ method := aMethod. class := self classObjectFor: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodToClassRefactoring >> preconditions [ ^(RBCondition definesSelector: method selector in: class) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassRefactoring >> privateTransform [ | oldClass newClass rbMethod originalProtocol | oldClass := self classModelOf: method methodClass. @@ -72,7 +74,7 @@ RBMoveMethodToClassRefactoring >> privateTransform [ withProtocol: originalProtocol) ] -{ #category : #printing } +{ #category : 'printing' } RBMoveMethodToClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBMoveMethodToClassSideRefactoring.class.st b/src/Refactoring-Core/RBMoveMethodToClassSideRefactoring.class.st index 5fe49a3b4b9..3be4e3058da 100644 --- a/src/Refactoring-Core/RBMoveMethodToClassSideRefactoring.class.st +++ b/src/Refactoring-Core/RBMoveMethodToClassSideRefactoring.class.st @@ -33,15 +33,17 @@ RBTransformationRuleTestData class >> rewriteUsing: searchReplacer ``` " Class { - #name : #RBMoveMethodToClassSideRefactoring, - #superclass : #RBMoveMethodToClassRefactoring, + #name : 'RBMoveMethodToClassSideRefactoring', + #superclass : 'RBMoveMethodToClassRefactoring', #instVars : [ 'parseTree' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #refactoring } +{ #category : 'refactoring' } RBMoveMethodToClassSideRefactoring >> accessorsFor: variableName [ ^ RBCreateAccessorsForVariableTransformation @@ -51,7 +53,7 @@ RBMoveMethodToClassSideRefactoring >> accessorsFor: variableName [ classVariable: false ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> addMethod: rbMethod to: aClass toProtocol: protocol [ aClass addMethod: rbMethod. self generateChangesFor: @@ -61,20 +63,20 @@ RBMoveMethodToClassSideRefactoring >> addMethod: rbMethod to: aClass toProtocol: withProtocol: protocol) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodToClassSideRefactoring >> applicabilityPreconditions [ ^ (RBCondition isMetaclass: class) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodToClassSideRefactoring >> breakingChangePreconditions [ ^ (RBCondition definesSelector: method selector in: class classSide) not ] -{ #category : #checking } +{ #category : 'checking' } RBMoveMethodToClassSideRefactoring >> checkVariableNamed: aString [ (class whoDefinesInstanceVariable: aString) ifNotNil: [^ true]. @@ -83,7 +85,7 @@ RBMoveMethodToClassSideRefactoring >> checkVariableNamed: aString [ ^ (self parseTree allDefinedVariables includes: aString) ] -{ #category : #refactoring } +{ #category : 'refactoring' } RBMoveMethodToClassSideRefactoring >> generateChanges [ self applicabilityPreconditions check ifFalse: [ @@ -97,7 +99,7 @@ RBMoveMethodToClassSideRefactoring >> generateChanges [ ^ self changes ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> getNewInstSideSource [ | sender | sender := ''. @@ -109,7 +111,7 @@ RBMoveMethodToClassSideRefactoring >> getNewInstSideSource [ ^ self class ', sender ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> getNewSource [ | rewriter node temp | @@ -126,7 +128,7 @@ RBMoveMethodToClassSideRefactoring >> getNewSource [ ifFalse: [ ^ node sourceCode ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> getTempName [ | aString counter tempName | counter := 0. @@ -138,7 +140,7 @@ RBMoveMethodToClassSideRefactoring >> getTempName [ ^ tempName ] -{ #category : #accessing } +{ #category : 'accessing' } RBMoveMethodToClassSideRefactoring >> parseTree [ parseTree @@ -148,13 +150,13 @@ RBMoveMethodToClassSideRefactoring >> parseTree [ ^ parseTree doSemanticAnalysis ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveMethodToClassSideRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> privateTransform [ | oldClass newClass rbMethod rbMethod2 newSource originalProtocol newSource2 | @@ -172,7 +174,7 @@ RBMoveMethodToClassSideRefactoring >> privateTransform [ self addMethod: rbMethod2 to: oldClass toProtocol: originalProtocol ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> removeInstVariableReferences [ | rbMethod references | @@ -190,7 +192,7 @@ RBMoveMethodToClassSideRefactoring >> removeInstVariableReferences [ self convertMethod: method selector for: class using: replacer ] ] -{ #category : #printing } +{ #category : 'printing' } RBMoveMethodToClassSideRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -204,7 +206,7 @@ RBMoveMethodToClassSideRefactoring >> storeOn: aStream [ nextPutAll: ')' ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveMethodToClassSideRefactoring >> temporaryName [ | aString counter tempName | counter := 0. diff --git a/src/Refactoring-Core/RBMoveVariableDefinitionToSmallestValidScopeRefactoring.class.st b/src/Refactoring-Core/RBMoveVariableDefinitionToSmallestValidScopeRefactoring.class.st index ef5070918d2..eee2014e468 100644 --- a/src/Refactoring-Core/RBMoveVariableDefinitionToSmallestValidScopeRefactoring.class.st +++ b/src/Refactoring-Core/RBMoveVariableDefinitionToSmallestValidScopeRefactoring.class.st @@ -4,8 +4,8 @@ I am a refactoring for moving the definition of a variable to the block/scope wh For a method temporary variable declared but not initialized in the method scope and only used within a block, the definition can be moved to the block using this variable. " Class { - #name : #RBMoveVariableDefinitionToSmallestValidScopeRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBMoveVariableDefinitionToSmallestValidScopeRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'interval', @@ -14,10 +14,12 @@ Class { 'blockNodes', 'definingNode' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring class >> bindTight: anInterval in: aClass selector: aSelector [ ^ self new class: aClass @@ -25,7 +27,7 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring class >> bindTight: anIn interval: anInterval ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring class >> model: aRBSmalltalk bindTight: anInterval in: aClass selector: aSelector [ ^ self new model: aRBSmalltalk; @@ -35,7 +37,7 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring class >> model: aRBSmall yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> checkNodes: sequenceNodes [ (sequenceNodes anySatisfy: [:each | RBReadBeforeWrittenTester isVariable: name readBeforeWrittenIn: each]) @@ -50,7 +52,7 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> checkNodes: sequenceN ^true ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> checkParseTree [ | node | @@ -68,14 +70,14 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> checkParseTree [ ifFalse: [ self refactoringError: 'Variable is possibly read before written' ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> class: aClass selector: aSelector interval: anInterval [ interval := anInterval. class := self classObjectFor: aClass. selector := aSelector ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition withBlock: @@ -95,14 +97,14 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> privateTransform [ definingNode removeTemporaryNamed: name. blockNodes do: [:each | each body addTemporaryNamed: name]. class compileTree: parseTree ] -{ #category : #printing } +{ #category : 'printing' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -116,7 +118,7 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> subblocksIn: aParseTree [ | searcher | searcher := self parseTreeSearcher. @@ -131,7 +133,7 @@ RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> subblocksIn: aParseTr initialAnswer: OrderedCollection new ] -{ #category : #transforming } +{ #category : 'transforming' } RBMoveVariableDefinitionToSmallestValidScopeRefactoring >> usesDirectly: aParseTree [ | searcher | searcher := self parseTreeSearcher. diff --git a/src/Refactoring-Core/RBNamespace.class.st b/src/Refactoring-Core/RBNamespace.class.st index 5694e08214a..1a643a2b218 100644 --- a/src/Refactoring-Core/RBNamespace.class.st +++ b/src/Refactoring-Core/RBNamespace.class.st @@ -47,8 +47,8 @@ Note, some of my methods for querying method senders and implementors don't work " Class { - #name : #RBNamespace, - #superclass : #RBEntity, + #name : 'RBNamespace', + #superclass : 'RBEntity', #instVars : [ 'changes', 'environment', @@ -62,10 +62,12 @@ Class { 'changedPackages', 'removedPackages' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBNamespace class >> onEnvironment: aBrowserEnvironment [ ^self basicNew environment: aBrowserEnvironment; @@ -73,7 +75,7 @@ RBNamespace class >> onEnvironment: aBrowserEnvironment [ yourself ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> addChangeToClass: aRBClass [ ^ changedClasses at: aRBClass name @@ -82,17 +84,17 @@ RBNamespace >> addChangeToClass: aRBClass [ with: aRBClass classSide) ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> addClassVariable: aString to: aRBClass [ ^changes addClassVariable: aString to: aRBClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> addInstanceVariable: aString to: aRBClass [ ^changes addInstanceVariable: aString to: aRBClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> addPackageNamed: aSymbol [ | change pkg | change := changes addPackageNamed: aSymbol. @@ -103,18 +105,18 @@ RBNamespace >> addPackageNamed: aSymbol [ ^change ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> addPool: aString to: aRBClass [ ^changes addPool: aString to: aRBClass ] -{ #category : #adding } +{ #category : 'adding' } RBNamespace >> addProtocolNamed: aString in: aClass [ ^ changes addProtocolNamed: aString in: aClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allClassesDo: aBlock [ | seen evalBlock | @@ -146,7 +148,7 @@ RBNamespace >> allClassesDo: aBlock [ ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allClassesInPackages: aColl do: aBlock [ | seen evalBlock | @@ -178,49 +180,49 @@ RBNamespace >> allClassesInPackages: aColl do: aBlock [ ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allImplementorsOf: aSelector [ ^ implementorsCache at: aSelector ifAbsentPut: [ self privateImplementorsOf: aSelector ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allImplementorsOf: aSelector do: aBlock [ (self allImplementorsOf: aSelector) do: aBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allImplementorsOf: aSelector inPackages: aColl [ ^ implementorsCache at: aSelector ifAbsentPut: [ self privateImplementorsOf: aSelector in: aColl ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesTo: aSymbol [ ^ sendersCache at: aSymbol ifAbsentPut: [ self privateReferencesTo: aSymbol ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesTo: aSymbol do: aBlock [ (self allReferencesTo: aSymbol) do: aBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesTo: aSymbol in: classes [ | classNames | classNames := classes collect: [ :cls | cls name ]. ^ (self allReferencesTo: aSymbol) select: [ :ref | classNames includes: ref modelClass name ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesTo: aSymbol inPackages: aColl [ ^ sendersCache at: aSymbol ifAbsentPut: [ self privateReferencesTo: aSymbol inPackages: aColl ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesTo: aSymbol inPackages: aColl do: aBlock [ (self allReferencesTo: aSymbol inPackages: aColl) do: aBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesToClass: aRBClass do: aBlock [ self allClassesDo: [ :each | @@ -228,7 +230,7 @@ RBNamespace >> allReferencesToClass: aRBClass do: aBlock [ do: [:sel | aBlock value: (each methodFor: sel)] ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> allReferencesToClass: aRBClass inPackages: aColl do: aBlock [ self allClassesInPackages: aColl do: [:each | @@ -236,13 +238,13 @@ RBNamespace >> allReferencesToClass: aRBClass inPackages: aColl do: aBlock [ do: [:sel | aBlock value: (each methodFor: sel)]] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> category: aString for: aClass [ ^ changes addChange: (RBClassCategoryChange category: aString for: aClass) ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> changeClass: aRBClass [ changedClasses at: aRBClass name @@ -252,12 +254,12 @@ RBNamespace >> changeClass: aRBClass [ self flushCaches ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> changes [ ^changes ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> classFor: aBehavior [ aBehavior ifNil: [ ^ nil ]. @@ -266,12 +268,12 @@ RBNamespace >> classFor: aBehavior [ ifFalse: [ self classNamed: aBehavior instanceSide name ] ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> classNameFor: aBehavior [ ^ aBehavior instanceSide name ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> classNamed: aSymbol [ | class classes index | aSymbol ifNil: [ ^ nil ]. @@ -289,7 +291,7 @@ RBNamespace >> classNamed: aSymbol [ ^ class ifNotNil: [ class classSide ] ] -{ #category : #converting } +{ #category : 'converting' } RBNamespace >> classObjectFor: anObject [ (anObject isBehavior or: [anObject isTrait]) @@ -299,7 +301,7 @@ RBNamespace >> classObjectFor: anObject [ ^ anObject ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> classesReferencingClass: aRBClass [ | classes | @@ -308,12 +310,12 @@ RBNamespace >> classesReferencingClass: aRBClass [ ^ classes ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> comment: aString in: aClass [ ^ changes comment: aString in: aClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> compile: aString in: aRBClass classified: aSymbol [ | change | change := changes @@ -324,7 +326,7 @@ RBNamespace >> compile: aString in: aRBClass classified: aSymbol [ ^change ] -{ #category : #transforming } +{ #category : 'transforming' } RBNamespace >> convertClasses: classSet select: aBlock using: searchReplacer [ classSet do: [ :aClass | @@ -332,7 +334,7 @@ RBNamespace >> convertClasses: classSet select: aBlock using: searchReplacer [ aClass convertMethod: selector using: searchReplacer ]] ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> createNewClassFor: aBehavior [ | nonMeta meta className rbType rbMetaType | className := aBehavior instanceSide name. @@ -350,14 +352,14 @@ RBNamespace >> createNewClassFor: aBehavior [ ^changedClasses at: className put: (Array with: nonMeta with: meta) ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> createNewPackageFor: aPackage [ | package | package := modelFactory rbPackage existingNamed: aPackage model: self. ^changedPackages at: aPackage put: (Array with: package) ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> defineClass: aString [ | change newClass newClassName | @@ -387,7 +389,7 @@ RBNamespace >> defineClass: aString [ ^ change ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> defineClass: aString withComment: aCommentString [ | change newClass | @@ -397,33 +399,33 @@ RBNamespace >> defineClass: aString withComment: aCommentString [ ^ change ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> description [ ^ self changes name ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> description: aString [ self changes name: aString ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> environment [ ^ environment ifNil: [ environment := RBBrowserEnvironment new] ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> environment: aBrowserEnvironment [ environment := aBrowserEnvironment ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> flushCaches [ implementorsCache := IdentityDictionary new. sendersCache := IdentityDictionary new ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> hasCreatedClassFor: aBehavior [ | className | className := self classNameFor: aBehavior. @@ -431,22 +433,22 @@ RBNamespace >> hasCreatedClassFor: aBehavior [ or: [changedClasses includesKey: className] ] -{ #category : #testing } +{ #category : 'testing' } RBNamespace >> hasPackageRemoved: aSymbol [ ^removedPackages includes: aSymbol ] -{ #category : #testing } +{ #category : 'testing' } RBNamespace >> hasRemoved: aSymbol [ ^removedClasses includes: aSymbol ] -{ #category : #testing } +{ #category : 'testing' } RBNamespace >> includesClassNamed: aSymbol [ ^(self classNamed: aSymbol) notNil ] -{ #category : #testing } +{ #category : 'testing' } RBNamespace >> includesGlobal: aSymbol [ (self hasRemoved: aSymbol) ifTrue: [^false]. (self includesClassNamed: aSymbol) ifTrue: [^true]. @@ -454,13 +456,13 @@ RBNamespace >> includesGlobal: aSymbol [ ^true ] -{ #category : #testing } +{ #category : 'testing' } RBNamespace >> includesPackageNamed: aSymbol [ ^ (self packageNamed: aSymbol) isNotNil ] -{ #category : #initialization } +{ #category : 'initialization' } RBNamespace >> initialize [ super initialize. changes := changeFactory compositeRefactoryChange onSystemDictionary: self environment. @@ -474,7 +476,7 @@ RBNamespace >> initialize [ sendersCache := IdentityDictionary new ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> markAsRemoved: aClassName [ removedClasses @@ -482,14 +484,14 @@ RBNamespace >> markAsRemoved: aClassName [ add: aClassName, ' class' ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> markPackageAsRemoved: aPackageName [ removedPackages add: aPackageName ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> metaclassNamed: aSymbol [ | class | @@ -508,17 +510,17 @@ RBNamespace >> metaclassNamed: aSymbol [ ^ nil ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> name [ ^changes name ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> name: aString [ ^changes name: aString ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> packageNamed: aSymbol [ aSymbol ifNil: [ ^ nil ]. (self hasPackageRemoved: aSymbol) ifTrue: [ ^ nil ]. @@ -527,7 +529,7 @@ RBNamespace >> packageNamed: aSymbol [ ^ (self createNewPackageFor: aSymbol) first ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> performChange: aCompositeRefactoryChange around: aBlock [ | oldChanges | changes addChange: aCompositeRefactoryChange. @@ -537,7 +539,7 @@ RBNamespace >> performChange: aCompositeRefactoryChange around: aBlock [ ^aCompositeRefactoryChange ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateImplementorsOf: aSelector [ | classes | classes := Set new. @@ -547,7 +549,7 @@ RBNamespace >> privateImplementorsOf: aSelector [ ^ classes ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateImplementorsOf: aSelector in: packages [ | classes | classes := Set new. @@ -557,7 +559,7 @@ RBNamespace >> privateImplementorsOf: aSelector in: packages [ ^ classes ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateReferencesTo: aSelector [ | methods | methods := OrderedCollection new. @@ -568,7 +570,7 @@ RBNamespace >> privateReferencesTo: aSelector [ ^ methods ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateReferencesTo: aSelector in: classes [ | methods | methods := OrderedCollection new. @@ -579,7 +581,7 @@ RBNamespace >> privateReferencesTo: aSelector in: classes [ ^ methods ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateReferencesTo: aSelector inPackages: aColl [ | methods | methods := OrderedCollection new. @@ -590,7 +592,7 @@ RBNamespace >> privateReferencesTo: aSelector inPackages: aColl [ ^ methods ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> privateRootClasses [ | classes | @@ -603,12 +605,12 @@ RBNamespace >> privateRootClasses [ ^ classes ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> removeClass: aRBClass [ self removeClassNamed: aRBClass name ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removeClassKeepingSubclassesNamed: aSymbol [ removedClasses add: aSymbol; @@ -619,7 +621,7 @@ RBNamespace >> removeClassKeepingSubclassesNamed: aSymbol [ ^changes removeClassNamed: aSymbol ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> removeClassNamed: aSymbol [ (self classNamed: aSymbol) subclasses do: [:each | self removeClassNamed: each name]. @@ -632,36 +634,36 @@ RBNamespace >> removeClassNamed: aSymbol [ ^changes removeClassNamed: aSymbol ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removeClassVariable: aString from: aRBClass [ ^changes removeClassVariable: aString from: aRBClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removeInstanceVariable: aString from: aRBClass [ ^changes removeInstanceVariable: aString from: aRBClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removeMethod: aSelector from: aRBClass [ self flushCaches. ^changes removeMethod: aSelector from: aRBClass ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removePackageNamed: aString [ self flushCaches. ^ changes removePackageNamed: aString ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> removeProtocolNamed: aString in: aClass [ ^ changes removeProtocolNamed: aString in: aClass ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> renameClass: aRBClass to: aSymbol around: aBlock [ | change value dict | change := changeFactory renameClass: aRBClass to: aSymbol. @@ -682,7 +684,7 @@ RBNamespace >> renameClass: aRBClass to: aSymbol around: aBlock [ ^ change ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> renameInstanceVariable: oldName to: newName in: aRBClass around: aBlock [ ^self performChange: (changeFactory renameInstanceVariable: oldName @@ -691,7 +693,7 @@ RBNamespace >> renameInstanceVariable: oldName to: newName in: aRBClass around: around: aBlock ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> renamePackage: aRBPackage to: aSymbol [ | change value dict | change := changeFactory renamePackage: aRBPackage to: aSymbol. @@ -707,7 +709,7 @@ RBNamespace >> renamePackage: aRBPackage to: aSymbol [ ^ change ] -{ #category : #changes } +{ #category : 'changes' } RBNamespace >> reparentClasses: aRBClassCollection to: newClass [ aRBClassCollection do: [:aClass | @@ -715,7 +717,7 @@ RBNamespace >> reparentClasses: aRBClassCollection to: newClass [ to: newClass name)] ] -{ #category : #'private - changes' } +{ #category : 'private - changes' } RBNamespace >> replaceClassNameIn: definitionString to: aSymbol [ | parseTree | parseTree := self parserClass parseExpression: definitionString. @@ -723,12 +725,12 @@ RBNamespace >> replaceClassNameIn: definitionString to: aSymbol [ ^parseTree formattedCode ] -{ #category : #accessing } +{ #category : 'accessing' } RBNamespace >> rootClasses [ ^ rootClasses ifNil: [ rootClasses := self privateRootClasses] ] -{ #category : #transforming } +{ #category : 'transforming' } RBNamespace >> selector: aSelector in: aClass classified: aProtocol [ ^ changes @@ -737,20 +739,20 @@ RBNamespace >> selector: aSelector in: aClass classified: aProtocol [ classified: aProtocol ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> unmarkAsRemoved: newClassName [ removedClasses remove: newClassName ifAbsent: [ ]; remove: newClassName , ' class' ifAbsent: [ ] ] -{ #category : #private } +{ #category : 'private' } RBNamespace >> unmarkPackageAsRemoved: newPackageName [ removedPackages remove: newPackageName ifAbsent: [ ] ] -{ #category : #'accessing - classes' } +{ #category : 'accessing - classes' } RBNamespace >> whichCategoryIncludes: aSymbol [ ^self environment whichCategoryIncludes: aSymbol ] diff --git a/src/Refactoring-Core/RBNegationCondition.class.st b/src/Refactoring-Core/RBNegationCondition.class.st index efebd964ebd..6116c23bba4 100644 --- a/src/Refactoring-Core/RBNegationCondition.class.st +++ b/src/Refactoring-Core/RBNegationCondition.class.st @@ -7,41 +7,43 @@ Checking this conditions holds true, if my condition is false. " Class { - #name : #RBNegationCondition, - #superclass : #RBAbstractCondition, + #name : 'RBNegationCondition', + #superclass : 'RBAbstractCondition', #instVars : [ 'condition' ], - #category : #'Refactoring-Core-Conditions' + #category : 'Refactoring-Core-Conditions', + #package : 'Refactoring-Core', + #tag : 'Conditions' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBNegationCondition class >> on: aCondition [ ^self new condition: aCondition ] -{ #category : #checking } +{ #category : 'checking' } RBNegationCondition >> check [ ^condition check not ] -{ #category : #initialization } +{ #category : 'initialization' } RBNegationCondition >> condition: aCondition [ condition := aCondition. self errorMacro: condition errorMacro ] -{ #category : #private } +{ #category : 'private' } RBNegationCondition >> errorBlockFor: aBoolean [ ^condition errorBlockFor: aBoolean not ] -{ #category : #private } +{ #category : 'private' } RBNegationCondition >> errorStringFor: aBoolean [ ^condition errorStringFor: aBoolean not ] -{ #category : #printing } +{ #category : 'printing' } RBNegationCondition >> printOn: aStream [ aStream nextPutAll: 'NOT '; print: condition diff --git a/src/Refactoring-Core/RBPackage.class.st b/src/Refactoring-Core/RBPackage.class.st index 5af737f9dba..bcfb2959134 100644 --- a/src/Refactoring-Core/RBPackage.class.st +++ b/src/Refactoring-Core/RBPackage.class.st @@ -3,24 +3,26 @@ I represent a package for the refactoring framework. " Class { - #name : #RBPackage, - #superclass : #RBEntity, + #name : 'RBPackage', + #superclass : 'RBEntity', #instVars : [ 'model', 'name', 'realPackage' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPackage class >> existingNamed: aSymbol [ ^(self named: aSymbol) realPackageFor: aSymbol; yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPackage class >> existingNamed: aSymbol model: aRBNamespace [ ^ (self named: aSymbol) model: aRBNamespace; @@ -28,50 +30,50 @@ RBPackage class >> existingNamed: aSymbol model: aRBNamespace [ yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPackage class >> named: aSymbol [ ^(self new) name: aSymbol; yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> model [ ^ model ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> model: anObject [ model := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> name [ ^ name ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> name: anObject [ name := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> realPackage [ ^ realPackage ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> realPackage: anObject [ realPackage := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackage >> realPackageFor: aSymbol [ self realPackage: ( self model environment packageAt: aSymbol ifAbsent: [nil] ) ] diff --git a/src/Refactoring-Core/RBPackageRefactoring.class.st b/src/Refactoring-Core/RBPackageRefactoring.class.st index 8d044b5df9d..c23d6fc85fc 100644 --- a/src/Refactoring-Core/RBPackageRefactoring.class.st +++ b/src/Refactoring-Core/RBPackageRefactoring.class.st @@ -4,22 +4,24 @@ I am an abstract base class for package refactorings. All that I provide is the package name, my subclass refactorings are operating on, and a instance creation method for setting the package name and an initial namespace model. " Class { - #name : #RBPackageRefactoring, - #superclass : #RBRefactoring, + #name : 'RBPackageRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'packageName', 'newName' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBPackageRefactoring class >> isAbstract [ ^ self == RBPackageRefactoring ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPackageRefactoring class >> model: aRBModel packageName: aName [ ^ self new model: aRBModel; @@ -27,37 +29,37 @@ RBPackageRefactoring class >> model: aRBModel packageName: aName [ yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPackageRefactoring class >> packageName: aName [ ^ self new packageName: aName ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackageRefactoring >> newName [ ^ newName ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackageRefactoring >> newName: anObject [ newName := anObject ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackageRefactoring >> packageName [ ^ packageName ] -{ #category : #accessing } +{ #category : 'accessing' } RBPackageRefactoring >> packageName: anObject [ packageName := anObject ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPackageRefactoring >> preconditions [ ^ RBCondition diff --git a/src/Refactoring-Core/RBPrettyPrintCodeTransformation.class.st b/src/Refactoring-Core/RBPrettyPrintCodeTransformation.class.st index 2e14a532c3a..85781b0cfa2 100644 --- a/src/Refactoring-Core/RBPrettyPrintCodeTransformation.class.st +++ b/src/Refactoring-Core/RBPrettyPrintCodeTransformation.class.st @@ -4,18 +4,20 @@ I am a refactoring for reformat the source code of all methods in this environme I have no precondition. " Class { - #name : #RBPrettyPrintCodeTransformation, - #superclass : #RBRefactoring, - #category : #'Refactoring-Core-Transformation-Unused' + #name : 'RBPrettyPrintCodeTransformation', + #superclass : 'RBRefactoring', + #category : 'Refactoring-Core-Transformation-Unused', + #package : 'Refactoring-Core', + #tag : 'Transformation-Unused' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBPrettyPrintCodeTransformation >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBPrettyPrintCodeTransformation >> privateTransform [ | source tree formatted | self model diff --git a/src/Refactoring-Core/RBProtectInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBProtectInstanceVariableRefactoring.class.st index b6e80871226..af9a6c01b86 100644 --- a/src/Refactoring-Core/RBProtectInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBProtectInstanceVariableRefactoring.class.st @@ -5,12 +5,14 @@ If a class defines methods for reading and writing instance variables, they are Omit method that are redefined in subclasses. " Class { - #name : #RBProtectInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBProtectInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBProtectInstanceVariableRefactoring >> getterSetterMethods [ | matcher | matcher := self parseTreeSearcher. @@ -31,7 +33,7 @@ RBProtectInstanceVariableRefactoring >> getterSetterMethods [ ^ matcher answer ] -{ #category : #transforming } +{ #category : 'transforming' } RBProtectInstanceVariableRefactoring >> inline: aSelector [ self onError: [self generateChangesFor: (RBInlineAllSendersRefactoring @@ -41,12 +43,12 @@ RBProtectInstanceVariableRefactoring >> inline: aSelector [ do: [] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBProtectInstanceVariableRefactoring >> preconditions [ ^RBCondition definesInstanceVariable: variableName in: class ] -{ #category : #transforming } +{ #category : 'transforming' } RBProtectInstanceVariableRefactoring >> privateTransform [ self setOption: #inlineExpression toUse: [:ref :string | true]. self getterSetterMethods do: [:each | self inline: each] diff --git a/src/Refactoring-Core/RBProtocolRegexTransformation.class.st b/src/Refactoring-Core/RBProtocolRegexTransformation.class.st index bdd46fa114a..9b24c1a9f64 100644 --- a/src/Refactoring-Core/RBProtocolRegexTransformation.class.st +++ b/src/Refactoring-Core/RBProtocolRegexTransformation.class.st @@ -4,12 +4,14 @@ I am a regex refactoring renaming protocol names. See comment of superclass for a nice script to be adapated to package names. " Class { - #name : #RBProtocolRegexTransformation, - #superclass : #RBRegexRefactoring, - #category : #'Refactoring-Core-Transformation-Unused' + #name : 'RBProtocolRegexTransformation', + #superclass : 'RBRegexRefactoring', + #category : 'Refactoring-Core-Transformation-Unused', + #package : 'Refactoring-Core', + #tag : 'Transformation-Unused' } -{ #category : #transforming } +{ #category : 'transforming' } RBProtocolRegexTransformation >> privateTransform [ | replacement | diff --git a/src/Refactoring-Core/RBPullUpClassVariableRefactoring.class.st b/src/Refactoring-Core/RBPullUpClassVariableRefactoring.class.st index 61f4cbd13b2..0f60ff6b20b 100644 --- a/src/Refactoring-Core/RBPullUpClassVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBPullUpClassVariableRefactoring.class.st @@ -2,17 +2,19 @@ I am a refactoring for moving a class variable up to the superclass. " Class { - #name : #RBPullUpClassVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBPullUpClassVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpClassVariableRefactoring >> preconditions [ ^(RBCondition isMetaclass: class) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpClassVariableRefactoring >> privateTransform [ | subclass | subclass := self subclassDefiningVariable. @@ -20,7 +22,7 @@ RBPullUpClassVariableRefactoring >> privateTransform [ class addClassVariable: variableName ] -{ #category : #'private - accessing' } +{ #category : 'private - accessing' } RBPullUpClassVariableRefactoring >> subclassDefiningVariable [ | subclasses | subclasses := class allSubclasses diff --git a/src/Refactoring-Core/RBPullUpInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBPullUpInstanceVariableRefactoring.class.st index f14bafa80a0..4ebd2f9bfee 100644 --- a/src/Refactoring-Core/RBPullUpInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBPullUpInstanceVariableRefactoring.class.st @@ -2,12 +2,14 @@ I am a refactoring for moving a instance variable up to the superclass. " Class { - #name : #RBPullUpInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBPullUpInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpInstanceVariableRefactoring >> preconditions [ ^RBCondition withBlock: [(class hierarchyDefinesInstanceVariable: variableName) @@ -21,7 +23,7 @@ RBPullUpInstanceVariableRefactoring >> preconditions [ true] ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpInstanceVariableRefactoring >> privateTransform [ class allSubclasses do: [:each | diff --git a/src/Refactoring-Core/RBPullUpMethodRefactoring.class.st b/src/Refactoring-Core/RBPullUpMethodRefactoring.class.st index 541f8da59f2..9d9f29831e3 100644 --- a/src/Refactoring-Core/RBPullUpMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBPullUpMethodRefactoring.class.st @@ -8,17 +8,19 @@ If the method already exists and the superclass is abstract or not referenced an " Class { - #name : #RBPullUpMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBPullUpMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'removeDuplicates', 'selectors', 'targetSuperclass' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPullUpMethodRefactoring class >> model: aRBSmalltalk pullUp: selectorCollection from: aClass [ ^ self new model: aRBSmalltalk; @@ -26,7 +28,7 @@ RBPullUpMethodRefactoring class >> model: aRBSmalltalk pullUp: selectorCollectio yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPullUpMethodRefactoring class >> model: aRBSmalltalk pullUp: selectorCollection from: aClass to: aSuperClass [ ^ self new model: aRBSmalltalk; @@ -34,19 +36,19 @@ RBPullUpMethodRefactoring class >> model: aRBSmalltalk pullUp: selectorCollectio yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPullUpMethodRefactoring class >> pullUp: selectorCollection from: aClass [ ^ self new pullUp: selectorCollection from: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPullUpMethodRefactoring class >> pullUp: selectorCollection from: aClass to: aSuperClass [ ^ self new pullUp: selectorCollection from: aClass to: aSuperClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkBackReferencesTo: aSelector [ "If `aSelector` is defined in `targetSuperclass` or one of its superclasses check for super sends to `aSelector` in `targetSuperclass` hierarchy. @@ -77,12 +79,12 @@ RBPullUpMethodRefactoring >> checkBackReferencesTo: aSelector [ with: definingClass)]]]] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkClassVars [ selectors do: [:each | self checkClassVarsFor: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkClassVarsFor: aSelector [ "Checks if `aSelector` refers to any of the class variables." @@ -95,12 +97,12 @@ RBPullUpMethodRefactoring >> checkClassVarsFor: aSelector [ with: class) ] ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkInstVars [ selectors do: [:each | self checkInstVarsFor: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkInstVarsFor: aSelector [ "Checks if `aSelector` refers to one of the instance variables and offers to perform `PushUpInstanceVariableRefactoring` refactoring such variables exist." @@ -117,7 +119,7 @@ RBPullUpMethodRefactoring >> checkInstVarsFor: aSelector [ So do you want to push up anyway?' ] ]] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkSiblingSuperSendsFrom: aRBClass [ "Checks if `aRBClass` selector sends super message to one of the methods selected to be push up from the `class`. @@ -146,13 +148,13 @@ RBPullUpMethodRefactoring >> checkSiblingSuperSendsFrom: aRBClass [ aRBClass allSubclasses do: [:each | self checkSiblingSuperSendsFrom: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkSuperMessages [ self checkSuperSendsFromPushedUpMethods. self checkSuperSendsFromSiblings ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkSuperSendsFromPushedUpMethods [ "Check if one of the selectors sends a super message to a method defined in `targetSuperclass`." @@ -168,7 +170,7 @@ RBPullUpMethodRefactoring >> checkSuperSendsFromPushedUpMethods [ expandMacrosWith: each)]] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkSuperSendsFromSiblings [ "Checks if a class in the `targetClass` subclasses (except for `class` and its subclasses) send super message to one of the selected messages." @@ -178,7 +180,7 @@ RBPullUpMethodRefactoring >> checkSuperSendsFromSiblings [ siblings do: [:aRBClass | self checkSiblingSuperSendsFrom: aRBClass] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> checkSuperclass [ "Checks if one of the methods to push up is overriden from the `targetSuperclass`. If there are overrides and `targetSuperclass` is not abstract a pop-up warns the user. @@ -204,7 +206,7 @@ RBPullUpMethodRefactoring >> checkSuperclass [ overrideSelectors do: [ :each | self checkBackReferencesTo: each ] ] -{ #category : #private } +{ #category : 'private' } RBPullUpMethodRefactoring >> copyDownMethod: aSelector [ | oldProtocol oldSource superclassDefiner subclasses refactoring | superclassDefiner := targetSuperclass whoDefinesMethod: aSelector. @@ -241,12 +243,12 @@ RBPullUpMethodRefactoring >> copyDownMethod: aSelector [ withProtocol: oldProtocol)] ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> copyDownMethods [ selectors do: [:each | self copyDownMethod: each] ] -{ #category : #actions } +{ #category : 'actions' } RBPullUpMethodRefactoring >> generateChanges [ super generateChanges. @@ -254,7 +256,7 @@ RBPullUpMethodRefactoring >> generateChanges [ ^ self changes ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> preconditions [ self requestSuperClass. ^(selectors inject: (RBCondition hasSuperclass: class) @@ -267,7 +269,7 @@ RBPullUpMethodRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> privateTransform [ self copyDownMethods; @@ -276,7 +278,7 @@ RBPullUpMethodRefactoring >> privateTransform [ removeDuplicateMethods ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> pullUp: aSelector [ | source refactoring | source := class sourceCodeFor: aSelector. @@ -294,12 +296,12 @@ RBPullUpMethodRefactoring >> pullUp: aSelector [ withProtocol: (class protocolsFor: aSelector)) ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> pullUp: selectorCollection from: aClass [ self pullUp: selectorCollection from: aClass to: aClass superclass ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> pullUp: selectorCollection from: aClass to: aSuperClass [ self setOption: #superClass toUse: [ :ref | ]. class := self classObjectFor: aClass. @@ -308,12 +310,12 @@ RBPullUpMethodRefactoring >> pullUp: selectorCollection from: aClass to: aSuperC removeDuplicates := false ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> pullUpMethods [ selectors do: [:each | self pullUp: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> pushUpVariable: aVariable [ | refactoring | refactoring := RBPullUpInstanceVariableRefactoring @@ -323,12 +325,12 @@ RBPullUpMethodRefactoring >> pushUpVariable: aVariable [ self generateChangesFor: refactoring ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> removeDuplicateMethods [ selectors do: [:each | self removeDuplicatesOf: each] ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> removeDuplicatesOf: aSelector [ | tree | tree := targetSuperclass parseTreeForSelector: aSelector. @@ -347,27 +349,27 @@ RBPullUpMethodRefactoring >> removeDuplicatesOf: aSelector [ each removeMethod: aSelector]]] ] -{ #category : #transforming } +{ #category : 'transforming' } RBPullUpMethodRefactoring >> removePulledUpMethods [ selectors do: [:each | class removeMethod: each] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPullUpMethodRefactoring >> requestSuperClass [ ^(self options at: #superClass) value: self ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> selectors [ ^ selectors ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> selectors: aList [ selectors := aList ] -{ #category : #printing } +{ #category : 'printing' } RBPullUpMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -378,7 +380,7 @@ RBPullUpMethodRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> superClass: anObject [ (anObject allSubclasses includes: class realClass ) ifFalse: [ self refactoringError: @@ -386,7 +388,7 @@ RBPullUpMethodRefactoring >> superClass: anObject [ targetSuperclass := self classObjectFor: anObject ] -{ #category : #initialization } +{ #category : 'initialization' } RBPullUpMethodRefactoring >> targetClass [ ^ class ] diff --git a/src/Refactoring-Core/RBPushDownClassVariableRefactoring.class.st b/src/Refactoring-Core/RBPushDownClassVariableRefactoring.class.st index abbe5019266..d3884a551ad 100644 --- a/src/Refactoring-Core/RBPushDownClassVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBPushDownClassVariableRefactoring.class.st @@ -4,15 +4,17 @@ 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 : #RBPushDownClassVariableRefactoring, - #superclass : #RBVariableRefactoring, + #name : 'RBPushDownClassVariableRefactoring', + #superclass : 'RBVariableRefactoring', #instVars : [ 'destinationClass' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownClassVariableRefactoring >> findDestinationClass [ | classes | classes := class withAllSubclasses reject: [ :each | @@ -31,7 +33,7 @@ RBPushDownClassVariableRefactoring >> findDestinationClass [ ^ destinationClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownClassVariableRefactoring >> preconditions [ "Preconditions are that only one subclass refers to the class variable." @@ -41,7 +43,7 @@ RBPushDownClassVariableRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownClassVariableRefactoring >> privateTransform [ class removeClassVariable: variableName. @@ -49,13 +51,13 @@ RBPushDownClassVariableRefactoring >> privateTransform [ destinationClass addClassVariable: variableName ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownClassVariableRefactoring >> signalMultipleReferenceError [ self signalReferenceError: ('Multiple subclasses reference <1s>' expandMacrosWith: variableName) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownClassVariableRefactoring >> signalReferenceError: errorString [ class realClass @@ -72,7 +74,7 @@ RBPushDownClassVariableRefactoring >> signalReferenceError: errorString [ ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownClassVariableRefactoring >> signalStillReferencedError [ self signalReferenceError: ('<1p> has references to <2s>' expandMacrosWith: class diff --git a/src/Refactoring-Core/RBPushDownInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBPushDownInstanceVariableRefactoring.class.st index 5ac68d35c1f..2729b7cec63 100644 --- a/src/Refactoring-Core/RBPushDownInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBPushDownInstanceVariableRefactoring.class.st @@ -4,12 +4,14 @@ I am a refactoring for moving a instance variable down to my subclasses. My precondition verifies that the moved variable is not referenced in the methods of the original class. " Class { - #name : #RBPushDownInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBPushDownInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownInstanceVariableRefactoring >> preconditions [ | references | @@ -24,7 +26,7 @@ RBPushDownInstanceVariableRefactoring >> preconditions [ ^ ( RBCondition definesInstanceVariable: variableName in: class ) & references not ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownInstanceVariableRefactoring >> privateTransform [ class removeInstanceVariable: variableName. class subclasses do: [:each | each addInstanceVariable: variableName] diff --git a/src/Refactoring-Core/RBPushDownMethodRefactoring.class.st b/src/Refactoring-Core/RBPushDownMethodRefactoring.class.st index 33c12fb646c..0eeb78fe2e3 100644 --- a/src/Refactoring-Core/RBPushDownMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBPushDownMethodRefactoring.class.st @@ -6,16 +6,18 @@ My preconditions verify that this method isn't refered as a super send in the s " Class { - #name : #RBPushDownMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBPushDownMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selectors', 'classes' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPushDownMethodRefactoring class >> model: aRBSmalltalk pushDown: selectorCollection from: aClass [ ^ self new model: aRBSmalltalk; @@ -23,7 +25,7 @@ RBPushDownMethodRefactoring class >> model: aRBSmalltalk pushDown: selectorColle yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPushDownMethodRefactoring class >> model: aRBSmalltalk pushDown: selectorCollection from: aClass in: classes [ ^ self new model: aRBSmalltalk; @@ -31,25 +33,25 @@ RBPushDownMethodRefactoring class >> model: aRBSmalltalk pushDown: selectorColle yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPushDownMethodRefactoring class >> pushDown: selectorCollection from: aClass [ ^ self new pushDown: selectorCollection from: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBPushDownMethodRefactoring class >> pushDown: selectorCollection from: aClass in: classes [ ^ self new pushDown: selectorCollection from: aClass in: classes ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> allClasses [ ^ classes ifNil: [ class subclasses ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownMethodRefactoring >> applicabilityPreconditions [ "Check that all selectors are defined in `class`" @@ -59,7 +61,7 @@ RBPushDownMethodRefactoring >> applicabilityPreconditions [ cond & (RBCondition definesSelector: each in: class) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownMethodRefactoring >> breakingChangePreconditions [ "Check that that none of the subclasses of `class` is doing a supercall to any of the selectors that will be pushed down. @@ -78,14 +80,14 @@ RBPushDownMethodRefactoring >> breakingChangePreconditions [ ^ condition ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> classes: aCollection [ classes := aCollection collect: [ :cls | self classObjectFor: cls. ] ] -{ #category : #actions } +{ #category : 'actions' } RBPushDownMethodRefactoring >> generateChanges [ self applicabilityPreconditions check ifFalse: [ @@ -101,19 +103,19 @@ RBPushDownMethodRefactoring >> generateChanges [ ^ self changes ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownMethodRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> privateTransform [ selectors do: [:each | self pushDown: each]. selectors do: [:each | class removeMethod: each] ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> pushDown: aSelector [ | code protocols refactoring | @@ -134,30 +136,30 @@ RBPushDownMethodRefactoring >> pushDown: aSelector [ withProtocol: protocols) ] ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBPushDownMethodRefactoring >> pushDown: selectorCollection from: aClass [ class := self classObjectFor: aClass. selectors := selectorCollection ] -{ #category : #initialization } +{ #category : 'initialization' } RBPushDownMethodRefactoring >> pushDown: selectorCollection from: aClass in: aCollection [ class := self classObjectFor: aClass. selectors := selectorCollection. self classes: aCollection ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> selectors [ ^ selectors ] -{ #category : #transforming } +{ #category : 'transforming' } RBPushDownMethodRefactoring >> selectors: aList [ selectors := aList ] -{ #category : #printing } +{ #category : 'printing' } RBPushDownMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -168,7 +170,7 @@ RBPushDownMethodRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBPushDownMethodRefactoring >> targetClass [ ^ class ] diff --git a/src/Refactoring-Core/RBRefactoring.class.st b/src/Refactoring-Core/RBRefactoring.class.st index 1198ea285cd..003bcb44163 100644 --- a/src/Refactoring-Core/RBRefactoring.class.st +++ b/src/Refactoring-Core/RBRefactoring.class.st @@ -25,37 +25,39 @@ A RBRefactoringManager is used to collect the executed refactorings and provide " Class { - #name : #RBRefactoring, - #superclass : #RBAbstractTransformation, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBRefactoring', + #superclass : 'RBAbstractTransformation', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBRefactoring class >> isAbstract [ ^ self == RBRefactoring ] -{ #category : #'accessing signal' } +{ #category : 'accessing signal' } RBRefactoring class >> preconditionSignal [ ^ RBRefactoringError , RBRefactoringWarning ] -{ #category : #converting } +{ #category : 'converting' } RBRefactoring >> asRefactoring [ self deprecated: 'This method is a no-op and can be removed' transformWith: '`@rec asRefactoring' -> '`@rec'. ^ self ] -{ #category : #testing } +{ #category : 'testing' } RBRefactoring >> canReferenceVariable: aString in: aClass [ (aClass definesVariable: aString) ifTrue: [^true]. (self model includesGlobal: aString asSymbol) ifTrue: [^true]. ^(self poolVariableNamesFor: aClass) includes: aString ] -{ #category : #support } +{ #category : 'support' } RBRefactoring >> checkClass: aRBClass selector: aSelector using: aMatcher [ | parseTree | parseTree := aRBClass parseTreeForSelector: aSelector. @@ -63,7 +65,7 @@ RBRefactoring >> checkClass: aRBClass selector: aSelector using: aMatcher [ ^aMatcher answer ] -{ #category : #private } +{ #category : 'private' } RBRefactoring >> classObjectFor: anObject [ (anObject isBehavior or: [ anObject isTrait ]) ifTrue: [ @@ -73,7 +75,7 @@ RBRefactoring >> classObjectFor: anObject [ ^ anObject ] -{ #category : #support } +{ #category : 'support' } RBRefactoring >> convertAllReferencesToClass: aRBClass using: searchReplacer [ self model allReferencesToClass: aRBClass do: @@ -84,7 +86,7 @@ RBRefactoring >> convertAllReferencesToClass: aRBClass using: searchReplacer [ using: searchReplacer] ] -{ #category : #support } +{ #category : 'support' } RBRefactoring >> convertClasses: classSet select: aBlock using: searchReplacer [ classSet do: [:aClass | @@ -96,7 +98,7 @@ RBRefactoring >> convertClasses: classSet select: aBlock using: searchReplacer [ using: searchReplacer]] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoring >> copyOptionsFrom: aDictionary [ | dict | dict := self options. @@ -111,7 +113,7 @@ RBRefactoring >> copyOptionsFrom: aDictionary [ self options: dict ] -{ #category : #transforming } +{ #category : 'transforming' } RBRefactoring >> generateChangesFor: aRefactoring [ "I will generate changes and save them in the model, BUT I will not apply them! Use me when a refactorings is composed of multiple other refactorings" @@ -122,7 +124,7 @@ RBRefactoring >> generateChangesFor: aRefactoring [ aRefactoring generateChanges ] -{ #category : #private } +{ #category : 'private' } RBRefactoring >> onError: aBlock do: errorBlock [ ^aBlock on: self class preconditionSignal do: @@ -131,7 +133,7 @@ RBRefactoring >> onError: aBlock do: errorBlock [ ex return: nil] ] -{ #category : #removing } +{ #category : 'removing' } RBRefactoring >> removeReturnsOf: parseTree [ | rewriter | rewriter := self parseTreeRewriter. @@ -141,7 +143,7 @@ RBRefactoring >> removeReturnsOf: parseTree [ ^ parseTree ] -{ #category : #utilities } +{ #category : 'utilities' } RBRefactoring >> safeMethodNameFor: aClass basedOn: aString [ "Creates an unused method name containing aString" @@ -161,7 +163,7 @@ RBRefactoring >> safeMethodNameFor: aClass basedOn: aString [ ^ newString asSymbol ] -{ #category : #private } +{ #category : 'private' } RBRefactoring >> safeVariableNameFor: aClass temporaries: allTempVars basedOn: aString [ | baseString i newString | newString := baseString := aString. @@ -173,7 +175,7 @@ RBRefactoring >> safeVariableNameFor: aClass temporaries: allTempVars basedOn: a ^ newString ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoring >> setOption: aSymbol toUse: aBlock [ | dict | dict := self options. @@ -182,13 +184,13 @@ RBRefactoring >> setOption: aSymbol toUse: aBlock [ self options: dict ] -{ #category : #transforming } +{ #category : 'transforming' } RBRefactoring >> transform [ self deprecated: 'Use privateTransform instead' transformWith: '`@rec transform' -> '`@rec privateTransform' ] -{ #category : #private } +{ #category : 'private' } RBRefactoring >> uniqueMethodNameFor: anInteger [ | before after index name | before := 'a'. @@ -202,7 +204,7 @@ RBRefactoring >> uniqueMethodNameFor: anInteger [ ^name asSymbol ] -{ #category : #utilities } +{ #category : 'utilities' } RBRefactoring >> whichVariableNode: aParseTree inInterval: anInterval name: aName [ | matcher block | matcher := self parseTreeSearcher. diff --git a/src/Refactoring-Core/RBRefactoringError.class.st b/src/Refactoring-Core/RBRefactoringError.class.st index ea299094c12..f38279077ff 100644 --- a/src/Refactoring-Core/RBRefactoringError.class.st +++ b/src/Refactoring-Core/RBRefactoringError.class.st @@ -2,7 +2,9 @@ The receiver is signaled whenever a precondition of a refactoring is violated. " Class { - #name : #RBRefactoringError, - #superclass : #Error, - #category : #'Refactoring-Core-Support' + #name : 'RBRefactoringError', + #superclass : 'Error', + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } diff --git a/src/Refactoring-Core/RBRefactoringWarning.class.st b/src/Refactoring-Core/RBRefactoringWarning.class.st index 69c3524cea2..28c5f860e41 100644 --- a/src/Refactoring-Core/RBRefactoringWarning.class.st +++ b/src/Refactoring-Core/RBRefactoringWarning.class.st @@ -3,28 +3,30 @@ The receiver is a warning that usually requires the user to validate. This is us The action block, if defined, might help the user to resolve the issue. " Class { - #name : #RBRefactoringWarning, - #superclass : #Notification, + #name : 'RBRefactoringWarning', + #superclass : 'Notification', #instVars : [ 'actionBlock' ], - #category : #'Refactoring-Core-Support' + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } -{ #category : #signalling } +{ #category : 'signalling' } RBRefactoringWarning class >> signal: aString with: aBlock [ ^ self new actionBlock: aBlock; signal: aString ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoringWarning >> actionBlock [ ^ actionBlock ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoringWarning >> actionBlock: anObject [ actionBlock := anObject diff --git a/src/Refactoring-Core/RBRefactoryTyper.class.st b/src/Refactoring-Core/RBRefactoryTyper.class.st index 49b2d085f0e..08fd972444a 100644 --- a/src/Refactoring-Core/RBRefactoryTyper.class.st +++ b/src/Refactoring-Core/RBRefactoryTyper.class.st @@ -45,8 +45,8 @@ RBRefactoryTyper typesFor: 'var' in: (RBParser parseExpression: 'var squared') m " Class { - #name : #RBRefactoryTyper, - #superclass : #Object, + #name : 'RBRefactoryTyper', + #superclass : 'Object', #instVars : [ 'model', 'class', @@ -57,17 +57,19 @@ Class { 'methodName', 'selectorLookup' ], - #category : #'Refactoring-Core-Support' + #category : 'Refactoring-Core-Support', + #package : 'Refactoring-Core', + #tag : 'Support' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRefactoryTyper class >> newFor: aRBNamespace [ ^ self new model: aRBNamespace; yourself ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper class >> typesFor: variableName in: aParseTree model: aRBSmalltalk [ | searcher messages | searcher := RBParseTreeSearcher new. @@ -83,7 +85,7 @@ RBRefactoryTyper class >> typesFor: variableName in: aParseTree model: aRBSmallt findTypeFor: messages ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> backpointersDictionary [ "Create a special dictionary, because the host systems wrongly treats #abc and 'abc' as equal." @@ -93,7 +95,7 @@ RBRefactoryTyper >> backpointersDictionary [ yourself ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> backpointersSetWith: anObject [ "Create a special set, because the host systems wrongly treats #abc and 'abc' as equal." @@ -104,12 +106,12 @@ RBRefactoryTyper >> backpointersSetWith: anObject [ yourself ] -{ #category : #printing } +{ #category : 'printing' } RBRefactoryTyper >> collectionNameFor: aString [ ^'-<1s>-' expandMacrosWith: aString ] -{ #category : #'equivalence classes' } +{ #category : 'equivalence classes' } RBRefactoryTyper >> computeEquivalenceClassesForMethodsAndVars [ | searcher | backpointers := self backpointersDictionary. @@ -126,7 +128,7 @@ RBRefactoryTyper >> computeEquivalenceClassesForMethodsAndVars [ self executeSearch: searcher ] -{ #category : #selectors } +{ #category : 'selectors' } RBRefactoryTyper >> computeMessagesSentToVariables [ | searcher | variableMessages := Dictionary new. @@ -154,13 +156,13 @@ RBRefactoryTyper >> computeMessagesSentToVariables [ self executeSearch: searcher ] -{ #category : #'computing types' } +{ #category : 'computing types' } RBRefactoryTyper >> computeTypes [ variableMessages keysAndValuesDo: [:key :value | variableTypes at: key put: (self findTypeFor: value)] ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> executeSearch: searcher [ class withAllSubclasses do: [:each | @@ -173,7 +175,7 @@ RBRefactoryTyper >> executeSearch: searcher [ parseTree notNil ifTrue: [searcher executeTree: parseTree]]] ] -{ #category : #'computing types' } +{ #category : 'computing types' } RBRefactoryTyper >> findTypeFor: selectorCollection [ ^selectorCollection inject: self rootClasses into: @@ -182,7 +184,7 @@ RBRefactoryTyper >> findTypeFor: selectorCollection [ with: (selectorLookup at: each ifAbsentPut: [self implementorsOf: each])] ] -{ #category : #assignments } +{ #category : 'assignments' } RBRefactoryTyper >> guessTypeFromAssignment: aNode [ | type set newType | @@ -215,19 +217,19 @@ RBRefactoryTyper >> guessTypeFromAssignment: aNode [ ( bestGuesses at: aNode variable name ifAbsentPut: [ Set new ] ) add: newType ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> guessTypesFor: anInstVarName [ ^bestGuesses at: anInstVarName ifAbsent: [self typesFor: anInstVarName] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> guessTypesFor: anInstVarName in: aClass [ class = aClass ifFalse: [self runOn: aClass]. ^bestGuesses at: anInstVarName ifAbsent: [self typesFor: anInstVarName in: aClass] ] -{ #category : #'computing types' } +{ #category : 'computing types' } RBRefactoryTyper >> implementorsOf: aSelector [ | classes | classes := OrderedCollection new. @@ -240,7 +242,7 @@ RBRefactoryTyper >> implementorsOf: aSelector [ ^classes ] -{ #category : #'computing types' } +{ #category : 'computing types' } RBRefactoryTyper >> implementorsOf: aSelector in: aClass storeIn: classes [ (aClass directlyDefinesMethod: aSelector) ifTrue: @@ -254,7 +256,7 @@ RBRefactoryTyper >> implementorsOf: aSelector in: aClass storeIn: classes [ storeIn: classes] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRefactoryTyper >> initialize [ model := RBClassModelFactory rbNamespace new. class := model classFor: Object. @@ -264,7 +266,7 @@ RBRefactoryTyper >> initialize [ bestGuesses := Dictionary new ] -{ #category : #'equivalence classes' } +{ #category : 'equivalence classes' } RBRefactoryTyper >> merge: aName [ | set1 set2 | set1 := backpointers at: methodName ifAbsent: [nil]. @@ -274,27 +276,27 @@ RBRefactoryTyper >> merge: aName [ set2 do: [:each | backpointers at: each put: set1] ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> model [ ^model ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> model: aRBSmalltalk [ model := aRBSmalltalk ] -{ #category : #'selectors-collections' } +{ #category : 'selectors-collections' } RBRefactoryTyper >> parseTreeSearcher [ ^ self parseTreeSearcherClass new ] -{ #category : #selectors } +{ #category : 'selectors' } RBRefactoryTyper >> parseTreeSearcherClass [ ^ RBParseTreeSearcher ] -{ #category : #printing } +{ #category : 'printing' } RBRefactoryTyper >> printOn: aStream [ aStream nextPutAll: class name; @@ -312,7 +314,7 @@ RBRefactoryTyper >> printOn: aStream [ cr] ] -{ #category : #printing } +{ #category : 'printing' } RBRefactoryTyper >> printType: aClass for: aString on: aStream [ | name colTypes | colTypes := #(). @@ -329,7 +331,7 @@ RBRefactoryTyper >> printType: aClass for: aString on: aStream [ colTypes ifNotEmpty: [aStream nextPut: $)] ] -{ #category : #printing } +{ #category : 'printing' } RBRefactoryTyper >> printTypeFor: aString on: aStream [ | types | types := (self guessTypesFor: aString) @@ -344,7 +346,7 @@ RBRefactoryTyper >> printTypeFor: aString on: aStream [ on: aStream] ] -{ #category : #'selectors-collections' } +{ #category : 'selectors-collections' } RBRefactoryTyper >> processCollectionFor: key messagesTo: aName in: aBlock [ | searcher | searcher := self parseTreeSearcher. @@ -363,7 +365,7 @@ RBRefactoryTyper >> processCollectionFor: key messagesTo: aName in: aBlock [ ifAbsentPut: [ Set new ]) ] -{ #category : #'selectors-collections' } +{ #category : 'selectors-collections' } RBRefactoryTyper >> processCollectionMessagesFor: variableName in: aParseTree [ | parent block | aParseTree isMessage @@ -403,7 +405,7 @@ RBRefactoryTyper >> processCollectionMessagesFor: variableName in: aParseTree [ in: block ] ] -{ #category : #'equivalence classes' } +{ #category : 'equivalence classes' } RBRefactoryTyper >> processNode: aNode [ (aNode isVariable and: [class instanceVariableNames includes: aNode name]) ifTrue: [^self merge: aNode name]. @@ -427,7 +429,7 @@ RBRefactoryTyper >> processNode: aNode [ ifFalse: [self processNode: each body statements last]]]] ] -{ #category : #'computing types' } +{ #category : 'computing types' } RBRefactoryTyper >> refineTypes: aClassCollection with: anotherClassCollection [ | classSet | classSet := Set new. @@ -441,7 +443,7 @@ RBRefactoryTyper >> refineTypes: aClassCollection with: anotherClassCollection [ ^classSet ] -{ #category : #assignments } +{ #category : 'assignments' } RBRefactoryTyper >> refineTypesByLookingAtAssignments [ | searcher needsSearch | needsSearch := false. @@ -457,12 +459,12 @@ RBRefactoryTyper >> refineTypesByLookingAtAssignments [ ifTrue: [ self executeSearch: searcher ] ] -{ #category : #private } +{ #category : 'private' } RBRefactoryTyper >> rootClasses [ ^ model rootClasses ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> runOn: aClass [ variableTypes := Dictionary new. variableMessages := Dictionary new. @@ -477,12 +479,12 @@ RBRefactoryTyper >> runOn: aClass [ refineTypesByLookingAtAssignments ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> selectedClass: aClass [ class := model classFor: aClass ] -{ #category : #assignments } +{ #category : 'assignments' } RBRefactoryTyper >> typeFor: anObject [ anObject isString ifTrue: [ ^ String ]. @@ -493,18 +495,18 @@ RBRefactoryTyper >> typeFor: anObject [ ifFalse: [ anObject class ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> typesFor: anInstVarName [ ^variableTypes at: anInstVarName ifAbsent: [Set new] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> typesFor: anInstVarName in: aClass [ class = aClass ifFalse: [self runOn: aClass]. ^variableTypes at: anInstVarName ifAbsent: [Set new] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRefactoryTyper >> typesFor: variableName in: aParseTree model: aRBSmalltalk [ | searcher messages | searcher := self parseTreeSearcher. diff --git a/src/Refactoring-Core/RBRegexRefactoring.class.st b/src/Refactoring-Core/RBRegexRefactoring.class.st index 9609ba1ca30..b7d30142454 100644 --- a/src/Refactoring-Core/RBRegexRefactoring.class.st +++ b/src/Refactoring-Core/RBRegexRefactoring.class.st @@ -33,21 +33,23 @@ RBClassRegexRefactoring new " Class { - #name : #RBRegexRefactoring, - #superclass : #RBRefactoring, + #name : 'RBRegexRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'matchers' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBRegexRefactoring class >> isAbstract [ ^ self == RBRegexRefactoring ] -{ #category : #private } +{ #category : 'private' } RBRegexRefactoring >> execute: aString [ "Perform all searches on aString and return the transformation." @@ -56,7 +58,7 @@ RBRegexRefactoring >> execute: aString [ into: [ :string :assoc | self execute: string replace: assoc key with: assoc value ] ] -{ #category : #private } +{ #category : 'private' } RBRegexRefactoring >> execute: aString replace: aRegex with: aReadStream [ | stream | ^ aRegex copy: aString translatingMatchesUsing: [ :match | @@ -71,19 +73,19 @@ RBRegexRefactoring >> execute: aString replace: aRegex with: aReadStream [ stream contents ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRegexRefactoring >> initialize [ super initialize. matchers := OrderedCollection new ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRegexRefactoring >> preconditions [ ^ self trueCondition ] -{ #category : #searching } +{ #category : 'searching' } RBRegexRefactoring >> replace: aFindString with: aReplaceString [ "Replace all matches of aFindString (regular expression) with aReplaceString, where $0 references the whole match, and $1..$9 the matched groups. Central method of the regex based refactoring. To be used in collaboration with renameClasses and others @@ -98,7 +100,7 @@ RBRegexRefactoring >> replace: aFindString with: aReplaceString [ self replace: aFindString with: aReplaceString ignoreCase: false ] -{ #category : #searching } +{ #category : 'searching' } RBRegexRefactoring >> replace: aFindString with: aReplaceString ignoreCase: aBoolean [ "Replace all matches of aFindString (regular expression) with aReplaceString, where $0 references the whole match, and $1..$9 the matched groups. See replace:with: comment too." diff --git a/src/Refactoring-Core/RBRemoveAllSendersRefactoring.class.st b/src/Refactoring-Core/RBRemoveAllSendersRefactoring.class.st index 83082ef43e3..0b5e7ecc39e 100644 --- a/src/Refactoring-Core/RBRemoveAllSendersRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveAllSendersRefactoring.class.st @@ -37,43 +37,45 @@ RBRefactoryTestDataApp >> caller1 ``` " Class { - #name : #RBRemoveAllSendersRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBRemoveAllSendersRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #removing } +{ #category : 'removing' } RBRemoveAllSendersRefactoring class >> model: aModel removeSendersOf: aSelector [ ^ self new model: aModel; removeSendersOf: aSelector ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveAllSendersRefactoring class >> removeSendersOf: aSelector [ ^ self new removeSendersOf: aSelector ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveAllSendersRefactoring >> messagePattern [ ^ 'self ' , (self buildSelectorString: selector) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveAllSendersRefactoring >> preconditions [ ^ self trueCondition ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveAllSendersRefactoring >> privateTransform [ self removeSelfSenders ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveAllSendersRefactoring >> removeMethod: aMethod of: node [ self generateChangesFor: (RBRemoveSenderRefactoring model: self model @@ -82,7 +84,7 @@ RBRemoveAllSendersRefactoring >> removeMethod: aMethod of: node [ forClass: aMethod methodClass) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveAllSendersRefactoring >> removeSelfSenders [ | flag | flag := false. @@ -98,12 +100,12 @@ RBRemoveAllSendersRefactoring >> removeSelfSenders [ ] ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveAllSendersRefactoring >> removeSendersOf: aSelector [ selector := aSelector ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveAllSendersRefactoring >> selfSendIn: aTree [ | searcher nodes | nodes := OrderedCollection new. @@ -115,7 +117,7 @@ RBRemoveAllSendersRefactoring >> selfSendIn: aTree [ ^ nodes ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveAllSendersRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRemoveClassPushingStateToSubclassesRefactoring.class.st b/src/Refactoring-Core/RBRemoveClassPushingStateToSubclassesRefactoring.class.st index a9613606ccc..37ef9f7dc5b 100644 --- a/src/Refactoring-Core/RBRemoveClassPushingStateToSubclassesRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveClassPushingStateToSubclassesRefactoring.class.st @@ -15,15 +15,17 @@ transf := (RBRemoveClassPushingStateToSubclassesRefactoring ``` " Class { - #name : #RBRemoveClassPushingStateToSubclassesRefactoring, - #superclass : #RBRemoveClassRefactoring, + #name : 'RBRemoveClassPushingStateToSubclassesRefactoring', + #superclass : 'RBRemoveClassRefactoring', #instVars : [ 'refactorings' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactoringPushDownClassVarsOf: class [ class classVariableNames do: [ :e | refactorings add: (RBPushDownClassVariableRefactoring @@ -32,7 +34,7 @@ RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactoringPushDownCla ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactoringPushDownInstVarsOf: class [ class instanceVariableNames do: [ :e | @@ -43,12 +45,12 @@ RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactoringPushDownIns class: class) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactoringPushDownMethodsOf: class [ refactorings add: (RBPushDownMethodRefactoring pushDown: class selectors from: class) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactorings [ "I mimick a composite refactoring. In the future I will take advantage of the new cool RBCompositeRefactoring." @@ -61,13 +63,13 @@ RBRemoveClassPushingStateToSubclassesRefactoring >> createRefactorings [ self createRefactoringPushDownClassVarsOf: class] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRemoveClassPushingStateToSubclassesRefactoring >> initialize [ super initialize. refactorings := OrderedCollection new ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassPushingStateToSubclassesRefactoring >> preconditions [ ^ classNames inject: self trueCondition into: [ :sum :each | @@ -81,7 +83,7 @@ RBRemoveClassPushingStateToSubclassesRefactoring >> preconditions [ "& ( self preconditionEmptyOrHasNoSubclasses: aClassOrTrait )" ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> privateTransform [ self createRefactorings. refactorings do: [ :ref | ref generateChanges ]. @@ -89,7 +91,7 @@ RBRemoveClassPushingStateToSubclassesRefactoring >> privateTransform [ self removeClasses ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassPushingStateToSubclassesRefactoring >> removeClasses [ classNames do: [:each | self model removeClassKeepingSubclassesNamed: each] ] diff --git a/src/Refactoring-Core/RBRemoveClassRefactoring.class.st b/src/Refactoring-Core/RBRemoveClassRefactoring.class.st index 998781eb701..e6777bae06c 100644 --- a/src/Refactoring-Core/RBRemoveClassRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveClassRefactoring.class.st @@ -6,28 +6,30 @@ My precondition verifies that the class name exists in this namespace and the cl If this class is ""empty"" (has no methods and no variables), any subclass is reparented to the superclass of this class. It is not allowed to remove non-empty classes when it has subclasses. " Class { - #name : #RBRemoveClassRefactoring, - #superclass : #RBRefactoring, + #name : 'RBRemoveClassRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'classNames' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'error messages' } +{ #category : 'error messages' } RBRemoveClassRefactoring class >> cannotRemoveTopLevelClassErrorMesssage [ ^ 'Cannot remove top level class' , String cr , 'when it has subclasses' ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveClassRefactoring class >> classNames: aClassNameCollection [ ^ self new classNames: aClassNameCollection ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveClassRefactoring class >> model: aRBSmalltalk classNames: aClassNameCollection [ ^ self new model: aRBSmalltalk; @@ -35,19 +37,19 @@ RBRemoveClassRefactoring class >> model: aRBSmalltalk classNames: aClassNameColl yourself ] -{ #category : #initialization } +{ #category : 'initialization' } RBRemoveClassRefactoring >> classNames: aClassNameCollection [ classNames := aClassNameCollection ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> environmentWithUsersOf: aClassable [ ^ RBClassEnvironment onEnvironment: RBBrowserEnvironment new classes: (self model classesReferencingClass: aClassable) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditionEmptyOrHasNoSubclasses: aClass [ ^ (RBCondition hasSubclasses: aClass excluding: classNames) not | @@ -56,7 +58,7 @@ RBRemoveClassRefactoring >> preconditionEmptyOrHasNoSubclasses: aClass [ ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditionHasNoReferences: aClass [ | referencingClassNames | @@ -67,7 +69,7 @@ RBRemoveClassRefactoring >> preconditionHasNoReferences: aClass [ yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditionHasNoUsers: aClassOrTrait [ ^ (RBCondition withBlock: [ @@ -79,12 +81,12 @@ RBRemoveClassRefactoring >> preconditionHasNoUsers: aClassOrTrait [ yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditionIsNotMetaclass: aClass [ ^ ((RBCondition isMetaclass: aClass) errorMacro: 'Cannot remove just the metaclass') not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditionNoTopClasses: aClass [ ^ RBCondition @@ -92,7 +94,7 @@ RBRemoveClassRefactoring >> preconditionNoTopClasses: aClass [ errorString: 'Cannot remove top level classwhen it has subclasses' ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> preconditions [ ^ classNames inject: self trueCondition into: [ :sum :each | @@ -107,14 +109,14 @@ RBRemoveClassRefactoring >> preconditions [ & (self preconditionHasNoUsers: aClassOrTrait)) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassRefactoring >> privateTransform [ self reparentSubclasses; removeClasses ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> refactoringAwareReferencesTo: aClass [ "Return the references to the class taking into account that some references may be created by other classes that should be removed by the refactoring." @@ -122,7 +124,7 @@ RBRemoveClassRefactoring >> refactoringAwareReferencesTo: aClass [ collect: [ :each | each name ]) copyWithoutAll: classNames ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassRefactoring >> refactoringAwareUsesOf: aClass [ "Return the 'symbol use' to the class taking into account that some uses may be created by other classes that should be removed by the refactoring." @@ -130,12 +132,12 @@ RBRemoveClassRefactoring >> refactoringAwareUsesOf: aClass [ collect: [ :each | each methodClass name ]) copyWithoutAll: classNames ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassRefactoring >> removeClasses [ classNames do: [:each | self model removeClassNamed: each] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassRefactoring >> reparentSubclasses [ classNames do: [:each | @@ -144,7 +146,7 @@ RBRemoveClassRefactoring >> reparentSubclasses [ self model reparentClasses: class subclasses copy to: class superclass] ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRemoveClassVariableRefactoring.class.st b/src/Refactoring-Core/RBRemoveClassVariableRefactoring.class.st index f3bee7ae8ba..f1756637d90 100644 --- a/src/Refactoring-Core/RBRemoveClassVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveClassVariableRefactoring.class.st @@ -4,12 +4,14 @@ I am a refactoring for removing class variables. My precondition verifies that there is no reference to this class variable. " Class { - #name : #RBRemoveClassVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBRemoveClassVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveClassVariableRefactoring >> preconditions [ ^ ( RBCondition isMetaclass: class ) not @@ -37,7 +39,7 @@ RBRemoveClassVariableRefactoring >> preconditions [ ] ) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveClassVariableRefactoring >> privateTransform [ class removeClassVariable: variableName ] diff --git a/src/Refactoring-Core/RBRemoveInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBRemoveInstanceVariableRefactoring.class.st index 0cd74edbb34..f46ffdcaefc 100644 --- a/src/Refactoring-Core/RBRemoveInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveInstanceVariableRefactoring.class.st @@ -1,33 +1,35 @@ Class { - #name : #RBRemoveInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBRemoveInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveInstanceVariableRefactoring class >> model: aNamespace remove: variable from: class [ ^ self model: aNamespace variable: variable class: class ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveInstanceVariableRefactoring class >> remove: variable from: class [ ^ self variable: variable class: class ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveInstanceVariableRefactoring >> applicabilityPreconditions [ ^ RBCondition directlyDefinesInstanceVariable: variableName asString in: class ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveInstanceVariableRefactoring >> breakingChangePreconditions [ ^ (RBCondition hierarchyOf: class referencesInstanceVariable: variableName) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveInstanceVariableRefactoring >> generateChanges [ self applicabilityPreconditions check ifFalse: [ @@ -41,20 +43,20 @@ RBRemoveInstanceVariableRefactoring >> generateChanges [ ^ self changes ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveInstanceVariableRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveInstanceVariableRefactoring >> privateTransform [ class removeInstanceVariable: variableName ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveInstanceVariableRefactoring >> refactoredClass [ ^ class ] diff --git a/src/Refactoring-Core/RBRemoveMethodRefactoring.class.st b/src/Refactoring-Core/RBRemoveMethodRefactoring.class.st index 39ba7b43432..9f47792a158 100644 --- a/src/Refactoring-Core/RBRemoveMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveMethodRefactoring.class.st @@ -4,16 +4,18 @@ I am a refactoring for removing a method. My preconditions verify that this method is not referenced anywhere. " Class { - #name : #RBRemoveMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBRemoveMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'transformation' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveMethodRefactoring class >> model: aRBNamespace selector: aSelector from: aClass [ ^ self new @@ -22,14 +24,14 @@ RBRemoveMethodRefactoring class >> model: aRBNamespace selector: aSelector from: yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveMethodRefactoring class >> selector: aSelector from: aClass [ ^ self new selector: aSelector from: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> breakingChangePreconditions [ ^ (RBCondition withBlock: [ @@ -37,7 +39,7 @@ RBRemoveMethodRefactoring >> breakingChangePreconditions [ true ]) & (RBCondition withBlock: [ self senders isEmpty ] errorString: 'Cannot remove method because it has senders') ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkBrowseAllOccurrences: anCollectionOfOccurrences [ | methods callers | methods := anCollectionOfOccurrences collect: [ :c | c key ] as: Set. @@ -63,7 +65,7 @@ RBRemoveMethodRefactoring >> checkBrowseAllOccurrences: anCollectionOfOccurrence self openBrowserOn: env ] ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkBrowseOccurrenceOf: aSelector in: aRBMethod [ self refactoringWarning: @@ -71,14 +73,14 @@ RBRemoveMethodRefactoring >> checkBrowseOccurrenceOf: aSelector in: aRBMethod [ with: [ self openBrowserOn: (RBBrowserEnvironment new referencesTo: aSelector) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkBrowseOccurrences: anCollectionOfOccurrences [ ^ anCollectionOfOccurrences size = 1 ifTrue: [ self checkBrowseOccurrenceOf: anCollectionOfOccurrences first key in: anCollectionOfOccurrences first value ] ifFalse: [ self checkBrowseAllOccurrences: anCollectionOfOccurrences ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkReferencesToAnyOf: aSelector [ | occurrences | @@ -87,7 +89,7 @@ RBRemoveMethodRefactoring >> checkReferencesToAnyOf: aSelector [ ^ self checkBrowseOccurrences: occurrences ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkReferencesToSuperSendsToAnyOf: superMessages [ [superMessages isEmpty] whileFalse: [self @@ -96,7 +98,7 @@ RBRemoveMethodRefactoring >> checkReferencesToSuperSendsToAnyOf: superMessages [ superMessages remove: superMessages first] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> checkSuperMethods [ @@ -110,7 +112,7 @@ RBRemoveMethodRefactoring >> checkSuperMethods [ ifFalse: [self checkReferencesToAnyOf: selector]. ] -{ #category : #executing } +{ #category : 'executing' } RBRemoveMethodRefactoring >> generateChanges [ transformation applicabilityPreconditions check ifFalse: [ @@ -122,7 +124,7 @@ RBRemoveMethodRefactoring >> generateChanges [ ^ self removeMethodChanges ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> justSendsSuper: aSelector [ | matcher parseTree superclass | @@ -148,7 +150,7 @@ RBRemoveMethodRefactoring >> justSendsSuper: aSelector [ ^ ( matcher answer anySatisfy: [ :each | each isSelfVariable not ]) not ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> preconditions [ transformation checkPreconditions. @@ -156,25 +158,25 @@ RBRemoveMethodRefactoring >> preconditions [ ^ self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveMethodRefactoring >> privateTransform [ transformation privateTransform ] -{ #category : #actions } +{ #category : 'actions' } RBRemoveMethodRefactoring >> removeMethodChanges [ self privateTransform. ^ self changes ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveMethodRefactoring >> selector [ ^ selector ] -{ #category : #initialization } +{ #category : 'initialization' } RBRemoveMethodRefactoring >> selector: aSelector from: aClass [ class := self classObjectFor: aClass. @@ -185,13 +187,13 @@ RBRemoveMethodRefactoring >> selector: aSelector from: aClass [ from: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> senders [ ^ self sendersExcluding: { selector } ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> sendersExcluding: aSelectorsCollection [ | occurrences | @@ -204,13 +206,13 @@ RBRemoveMethodRefactoring >> sendersExcluding: aSelectorsCollection [ ^ occurrences ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> sendersOf: aSelector [ ^ self model allReferencesTo: aSelector ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -221,7 +223,7 @@ RBRemoveMethodRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodRefactoring >> superclassEquivalentlyDefines: aSelector [ | superTree myTree | diff --git a/src/Refactoring-Core/RBRemoveMethodsInHierarchyRefactoring.class.st b/src/Refactoring-Core/RBRemoveMethodsInHierarchyRefactoring.class.st index 276845b24d8..fdd7ca93303 100644 --- a/src/Refactoring-Core/RBRemoveMethodsInHierarchyRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveMethodsInHierarchyRefactoring.class.st @@ -12,22 +12,24 @@ Script ``` " Class { - #name : #RBRemoveMethodsInHierarchyRefactoring, - #superclass : #RBCompositeRefactoring, + #name : 'RBRemoveMethodsInHierarchyRefactoring', + #superclass : 'RBCompositeRefactoring', #instVars : [ 'selectors', 'class' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #removing } +{ #category : 'removing' } RBRemoveMethodsInHierarchyRefactoring class >> selectors: aSelectorsCollection from: aClass [ ^ self new selectors: aSelectorsCollection from: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodsInHierarchyRefactoring >> applicabilityPreconditions [ ^ selectors @@ -35,7 +37,7 @@ RBRemoveMethodsInHierarchyRefactoring >> applicabilityPreconditions [ into: [ :cond :sel | cond & (RBCondition definesSelector: sel in: class) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveMethodsInHierarchyRefactoring >> delete: aSelectorsCollection in: aClass [ | containingMethods | @@ -48,14 +50,14 @@ RBRemoveMethodsInHierarchyRefactoring >> delete: aSelectorsCollection in: aClass from: aClass) ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveMethodsInHierarchyRefactoring >> initializeRefactorings [ class withAllSubclasses do: [ :aClass | self delete: selectors in: aClass ] ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveMethodsInHierarchyRefactoring >> selectors: aSelectorsCollection from: aClass [ class := self classObjectFor: aClass. @@ -64,7 +66,7 @@ RBRemoveMethodsInHierarchyRefactoring >> selectors: aSelectorsCollection from: a self initializeRefactorings ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveMethodsInHierarchyRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRemoveMethodsRefactoring.class.st b/src/Refactoring-Core/RBRemoveMethodsRefactoring.class.st index 35244120425..ca20639dba2 100644 --- a/src/Refactoring-Core/RBRemoveMethodsRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveMethodsRefactoring.class.st @@ -6,16 +6,18 @@ My preconditions verify that methods to be removed are not referenced anywhere. " Class { - #name : #RBRemoveMethodsRefactoring, - #superclass : #RBCompositeRefactoring, + #name : 'RBRemoveMethodsRefactoring', + #superclass : 'RBCompositeRefactoring', #instVars : [ 'selectors', 'class' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveMethodsRefactoring class >> model: aRBNamespace selectors: aSelectorsCollection from: aClass [ ^ self new @@ -24,7 +26,7 @@ RBRemoveMethodsRefactoring class >> model: aRBNamespace selectors: aSelectorsCol from: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveMethodsRefactoring class >> selectors: aSelectorsCollection from: aClass [ ^ self new @@ -32,7 +34,7 @@ RBRemoveMethodsRefactoring class >> selectors: aSelectorsCollection from: aClass from: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodsRefactoring >> applicabilityPreconditions [ ^ selectors @@ -40,7 +42,7 @@ RBRemoveMethodsRefactoring >> applicabilityPreconditions [ into: [ :cond :sel | cond & (RBCondition definesSelector: sel in: class) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveMethodsRefactoring >> breakingChangePreconditions [ refactorings do: [ :ref | ref checkSuperMethods ]. @@ -51,20 +53,20 @@ RBRemoveMethodsRefactoring >> breakingChangePreconditions [ 'Some of the methods have senders outside of the methods being removed' ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveMethodsRefactoring >> removeMethodChanges [ refactorings do: [ :ref | ref privateTransform ]. ^ self changes ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveMethodsRefactoring >> selectors [ ^ selectors ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveMethodsRefactoring >> selectors: aCollection from: aClass [ selectors := aCollection. @@ -76,7 +78,7 @@ RBRemoveMethodsRefactoring >> selectors: aCollection from: aClass [ from: aClass ] ] -{ #category : #private } +{ #category : 'private' } RBRemoveMethodsRefactoring >> senders [ ^ (refactorings collect: [ :ref | ref sendersExcluding: selectors ]) flattened diff --git a/src/Refactoring-Core/RBRemoveParameterRefactoring.class.st b/src/Refactoring-Core/RBRemoveParameterRefactoring.class.st index 17dc382e380..a88653caa9c 100644 --- a/src/Refactoring-Core/RBRemoveParameterRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveParameterRefactoring.class.st @@ -7,16 +7,18 @@ Any sender of the prior selector will be changed to the new. If the method contains more than one argument, I request the user to choose one of the arguments. " Class { - #name : #RBRemoveParameterRefactoring, - #superclass : #RBChangeMethodNameRefactoring, + #name : 'RBRemoveParameterRefactoring', + #superclass : 'RBChangeMethodNameRefactoring', #instVars : [ 'parameterIndex', 'argument' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveParameterRefactoring class >> model: aRBSmalltalk removeParameter: aString in: aClass selector: aSelector [ ^ self new model: aRBSmalltalk; @@ -26,7 +28,7 @@ RBRemoveParameterRefactoring class >> model: aRBSmalltalk removeParameter: aStri yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveParameterRefactoring class >> removeParameter: aString in: aClass selector: aSelector [ ^ self new removeParameter: aString @@ -34,7 +36,7 @@ RBRemoveParameterRefactoring class >> removeParameter: aString in: aClass select selector: aSelector ] -{ #category : #validating } +{ #category : 'validating' } RBRemoveParameterRefactoring >> applyValidations [ | tree | @@ -55,7 +57,7 @@ RBRemoveParameterRefactoring >> applyValidations [ 'Cannot remove parameters of infix selectors' ] ] -{ #category : #private } +{ #category : 'private' } RBRemoveParameterRefactoring >> computeNewSelector [ | keywords | @@ -66,14 +68,14 @@ RBRemoveParameterRefactoring >> computeNewSelector [ ^ (String streamContents: [ :str | keywords do: [ :each | str nextPutAll: each ] ]) asSymbol ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveParameterRefactoring >> getNewSelector [ self applyValidations. permutation := (1 to: oldSelector numArgs) copyWithout: parameterIndex. ^ newSelector ifNil: [ newSelector := self computeNewSelector ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveParameterRefactoring >> hasReferencesToTemporaryIn: each [ | tree | @@ -83,7 +85,7 @@ RBRemoveParameterRefactoring >> hasReferencesToTemporaryIn: each [ ^ tree references: ( tree argumentNames at: parameterIndex ) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveParameterRefactoring >> myConditions [ | imps | imps := self model allImplementorsOf: oldSelector. @@ -96,19 +98,19 @@ RBRemoveParameterRefactoring >> myConditions [ errorString: 'This argument is still referenced in at least one implementor!!')] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveParameterRefactoring >> newSelector: aSelector [ newSelector := aSelector ] -{ #category : #initialization } +{ #category : 'initialization' } RBRemoveParameterRefactoring >> removeParameter: aString in: aClass selector: aSelector [ oldSelector := aSelector. class := self classObjectFor: aClass. argument := aString ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveParameterRefactoring >> storeOn: aStream [ aStream nextPut: $(. diff --git a/src/Refactoring-Core/RBRemoveSenderRefactoring.class.st b/src/Refactoring-Core/RBRemoveSenderRefactoring.class.st index f94655b5b3d..4b0442e99ec 100644 --- a/src/Refactoring-Core/RBRemoveSenderRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveSenderRefactoring.class.st @@ -41,12 +41,14 @@ RBRefactoryTestDataApp >> caller1 " Class { - #name : #RBRemoveSenderRefactoring, - #superclass : #RBInlineMethodFromComponentRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBRemoveSenderRefactoring', + #superclass : 'RBInlineMethodFromComponentRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveSenderRefactoring class >> model: aRBSmalltalk remove: anInterval inMethod: aSelector forClass: aClass [ ^ self new model: aRBSmalltalk; @@ -56,7 +58,7 @@ RBRemoveSenderRefactoring class >> model: aRBSmalltalk remove: anInterval inMeth yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveSenderRefactoring class >> remove: anInterval inMethod: aSelector forClass: aClass [ ^ self new remove: anInterval @@ -64,14 +66,14 @@ RBRemoveSenderRefactoring class >> remove: anInterval inMethod: aSelector forCla forClass: aClass ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveSenderRefactoring >> findSelectedMessage [ super findSelectedMessage. sourceMessage isDirectlyUsed ifTrue: [ self refactoringError: 'The sender is directly used' ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveSenderRefactoring >> inlineParseTree [ | aSymbol | @@ -82,13 +84,13 @@ RBRemoveSenderRefactoring >> inlineParseTree [ body: ( RBSequenceNode statements: #())] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveSenderRefactoring >> nameOfTheClassOfTheMethodToInline [ ^ 'Object' ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveSenderRefactoring >> preconditions [ ^ (RBCondition withBlock: [class ifNil: [self refactoringError: 'Invalid class name']. true]) & @@ -104,7 +106,7 @@ RBRemoveSenderRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveSenderRefactoring >> privateTransform [ self inlineParseTree. self renameConflictingTemporaries. @@ -115,14 +117,14 @@ RBRemoveSenderRefactoring >> privateTransform [ compileMethod ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveSenderRefactoring >> remove: anInterval inMethod: aSelector forClass: aClass [ sourceSelector := aSelector. class := self classObjectFor: aClass. sourceInterval := anInterval ] -{ #category : #printing } +{ #category : 'printing' } RBRemoveSenderRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRemoveSharedVariableRefactoring.class.st b/src/Refactoring-Core/RBRemoveSharedVariableRefactoring.class.st index 3fea4f617a7..78458f0a1a0 100644 --- a/src/Refactoring-Core/RBRemoveSharedVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBRemoveSharedVariableRefactoring.class.st @@ -1,22 +1,24 @@ Class { - #name : #RBRemoveSharedVariableRefactoring, - #superclass : #RBVariableRefactoring, - #category : #'Refactoring-Core-Refactorings' + #name : 'RBRemoveSharedVariableRefactoring', + #superclass : 'RBVariableRefactoring', + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRemoveSharedVariableRefactoring class >> model: aNamespace remove: variable from: class [ ^ self model: aNamespace variable: variable class: class ] -{ #category : #removing } +{ #category : 'removing' } RBRemoveSharedVariableRefactoring class >> remove: variable from: class [ ^ self variable: variable class: class ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveSharedVariableRefactoring >> applicabilityPreconditions [ ^ ( RBCondition isMetaclass: class ) not @@ -24,7 +26,7 @@ RBRemoveSharedVariableRefactoring >> applicabilityPreconditions [ ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveSharedVariableRefactoring >> breakingChangePreconditions [ ^ (RBCondition @@ -32,7 +34,7 @@ RBRemoveSharedVariableRefactoring >> breakingChangePreconditions [ referencesSharedVariable: variableName) not ] -{ #category : #actions } +{ #category : 'actions' } RBRemoveSharedVariableRefactoring >> generateChanges [ self applicabilityPreconditions check ifFalse: [ @@ -46,18 +48,18 @@ RBRemoveSharedVariableRefactoring >> generateChanges [ ^ self changes ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRemoveSharedVariableRefactoring >> preconditions [ ^ self applicabilityPreconditions & self breakingChangePreconditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBRemoveSharedVariableRefactoring >> privateTransform [ class removeClassVariable: variableName ] -{ #category : #accessing } +{ #category : 'accessing' } RBRemoveSharedVariableRefactoring >> refactoredClass [ ^ class diff --git a/src/Refactoring-Core/RBRenameArgumentOrTemporaryRefactoring.class.st b/src/Refactoring-Core/RBRenameArgumentOrTemporaryRefactoring.class.st index 26ba41d298a..b97a0c111e5 100644 --- a/src/Refactoring-Core/RBRenameArgumentOrTemporaryRefactoring.class.st +++ b/src/Refactoring-Core/RBRenameArgumentOrTemporaryRefactoring.class.st @@ -7,8 +7,8 @@ The variable declaration and all references in this method are renamed. My precondition verifies that the new name is a valid variable name and not an existing instance or a class variable name " Class { - #name : #RBRenameArgumentOrTemporaryRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBRenameArgumentOrTemporaryRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'interval', @@ -16,10 +16,12 @@ Class { 'newName', 'parseTree' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameArgumentOrTemporaryRefactoring class >> model: aRBSmalltalk renameTemporaryFrom: anInterval to: newName in: aClass selector: aSelector [ ^ self new model: aRBSmalltalk; @@ -30,7 +32,7 @@ RBRenameArgumentOrTemporaryRefactoring class >> model: aRBSmalltalk renameTempor yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameArgumentOrTemporaryRefactoring class >> renameTemporaryFrom: anInterval to: newName in: aClass selector: aSelector [ ^ self new class: aClass @@ -39,7 +41,7 @@ RBRenameArgumentOrTemporaryRefactoring class >> renameTemporaryFrom: anInterval newName: newName ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameArgumentOrTemporaryRefactoring >> class: aClass selector: aSelector interval: anInterval newName: aString [ class := self classObjectFor: aClass. selector := aSelector. @@ -47,7 +49,7 @@ RBRenameArgumentOrTemporaryRefactoring >> class: aClass selector: aSelector inte newName := aString ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameArgumentOrTemporaryRefactoring >> preconditions [ ^ (RBCondition withBlock: [ | methodSource | @@ -61,7 +63,7 @@ RBRenameArgumentOrTemporaryRefactoring >> preconditions [ & (RBCondition definesInstanceVariable: newName in: class) not & (RBCondition definesClassVariable: newName in: class) not ] -{ #category : #tranforming } +{ #category : 'tranforming' } RBRenameArgumentOrTemporaryRefactoring >> privateTransform [ | definingNode variableNode | parseTree := class parseTreeForSelector: selector. @@ -76,7 +78,7 @@ RBRenameArgumentOrTemporaryRefactoring >> privateTransform [ class compileTree: parseTree ] -{ #category : #tranforming } +{ #category : 'tranforming' } RBRenameArgumentOrTemporaryRefactoring >> renameNode: aParseTree [ (aParseTree whoDefines: newName) ifNotNil: [ self refactoringError: newName asString , ' is already defined' ]. @@ -85,7 +87,7 @@ RBRenameArgumentOrTemporaryRefactoring >> renameNode: aParseTree [ (self parseTreeRewriterClass rename: oldName to: newName) executeTree: aParseTree ] -{ #category : #printing } +{ #category : 'printing' } RBRenameArgumentOrTemporaryRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRenameClassRefactoring.class.st b/src/Refactoring-Core/RBRenameClassRefactoring.class.st index a0f43943290..fba07f2f183 100644 --- a/src/Refactoring-Core/RBRenameClassRefactoring.class.st +++ b/src/Refactoring-Core/RBRenameClassRefactoring.class.st @@ -11,16 +11,18 @@ Example (RBRenameClassRefactoring rename: 'RBRenameClassRefactoring' to: 'RBRenameClassRefactoring2') execute " Class { - #name : #RBRenameClassRefactoring, - #superclass : #RBClassRefactoring, + #name : 'RBRenameClassRefactoring', + #superclass : 'RBClassRefactoring', #instVars : [ 'newName', 'class' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameClassRefactoring class >> model: aRBSmalltalk rename: aClass to: aNewName [ ^ self new model: aRBSmalltalk; @@ -28,21 +30,21 @@ RBRenameClassRefactoring class >> model: aRBSmalltalk rename: aClass to: aNewNam yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameClassRefactoring class >> rename: aClassName to: aNewName [ ^ self new className: aClassName newName: aNewName ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameClassRefactoring >> className: aName newName: aNewName [ className := aName asSymbol. class := self model classNamed: className. newName := aNewName asSymbol ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameClassRefactoring >> preconditions [ ^((RBCondition withBlock: [class notNil and: [class isMeta not]]) & (RBCondition isValidClassName: newName) @@ -50,7 +52,7 @@ RBRenameClassRefactoring >> preconditions [ (RBCondition withBlock: [ self refactoringError: newName , ' is not a valid class name']) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameClassRefactoring >> privateTransform [ self model renameClass: class @@ -58,7 +60,7 @@ RBRenameClassRefactoring >> privateTransform [ around: [self renameReferences] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameClassRefactoring >> renameReferences [ | replacer | @@ -71,10 +73,10 @@ RBRenameClassRefactoring >> renameReferences [ self refactoringError: newName , ' is already defined in hierarchy of ' , method modelClass printString ]. (method method ifNil: [ false ] - ifNotNil: #isFromTrait) ifFalse: [ self convertMethod: method selector for: method modelClass using: replacer ] ] + ifNotNil: [ :m | m isFromTrait]) ifFalse: [ self convertMethod: method selector for: method modelClass using: replacer ] ] ] -{ #category : #printing } +{ #category : 'printing' } RBRenameClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRenameClassVariableRefactoring.class.st b/src/Refactoring-Core/RBRenameClassVariableRefactoring.class.st index 4b858327749..fe6efe5350e 100644 --- a/src/Refactoring-Core/RBRenameClassVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBRenameClassVariableRefactoring.class.st @@ -6,15 +6,17 @@ I rename the class variable in the class definition and in all methods refering My precondition verifies that the new variable is valid and not yet used in the whole class hierarchy. " Class { - #name : #RBRenameClassVariableRefactoring, - #superclass : #RBVariableRefactoring, + #name : 'RBRenameClassVariableRefactoring', + #superclass : 'RBVariableRefactoring', #instVars : [ 'newName' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameClassVariableRefactoring class >> model: aRBSmalltalk rename: aVarName to: aName in: aClass [ ^ self new model: aRBSmalltalk; @@ -24,7 +26,7 @@ RBRenameClassVariableRefactoring class >> model: aRBSmalltalk rename: aVarName t yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameClassVariableRefactoring class >> rename: aVarName to: aName in: aClass [ ^ self new rename: aVarName @@ -32,17 +34,17 @@ RBRenameClassVariableRefactoring class >> rename: aVarName to: aName in: aClass in: aClass ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameClassVariableRefactoring >> newName [ ^ newName ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameClassVariableRefactoring >> newName: anObject [ newName := anObject ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameClassVariableRefactoring >> preconditions [ ^(RBCondition isMetaclass: class) not & (RBCondition isValidClassVarName: newName asString for: class) @@ -51,7 +53,7 @@ RBRenameClassVariableRefactoring >> preconditions [ & (RBCondition isGlobal: newName asString in: self model) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameClassVariableRefactoring >> privateTransform [ class renameClassVariable: variableName @@ -59,13 +61,13 @@ RBRenameClassVariableRefactoring >> privateTransform [ around: [self renameReferences] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameClassVariableRefactoring >> rename: aVarName to: aName in: aClass [ self variable: aVarName class: aClass. newName := aName ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameClassVariableRefactoring >> renameReferences [ | replacer methods | replacer := self parseTreeRewriterClass @@ -78,7 +80,7 @@ RBRenameClassVariableRefactoring >> renameReferences [ methods do: [ :method | self convertMethod: method selector for: method modelClass using: replacer ] ] -{ #category : #printing } +{ #category : 'printing' } RBRenameClassVariableRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRenameInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBRenameInstanceVariableRefactoring.class.st index 07c9f9e0ab9..60848504ec1 100644 --- a/src/Refactoring-Core/RBRenameInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBRenameInstanceVariableRefactoring.class.st @@ -6,17 +6,19 @@ I rename the instance variable in the class definition, in all methods refering My precondition verifies that the new variable is valid and not yet used in the whole class hierarchy. " Class { - #name : #RBRenameInstanceVariableRefactoring, - #superclass : #RBVariableRefactoring, + #name : 'RBRenameInstanceVariableRefactoring', + #superclass : 'RBVariableRefactoring', #instVars : [ 'newName', 'browsedEnvironment', 'renameAccessors' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameInstanceVariableRefactoring class >> model: aRBNamespace rename: aVarName to: aName in: aClass [ ^ self new model: aRBNamespace; @@ -26,7 +28,7 @@ RBRenameInstanceVariableRefactoring class >> model: aRBNamespace rename: aVarNam yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameInstanceVariableRefactoring class >> model: aRBNamespace rename: aVarName to: aName in: aClass renameAccessors: aBoolean [ ^ self new model: aRBNamespace; @@ -37,7 +39,7 @@ RBRenameInstanceVariableRefactoring class >> model: aRBNamespace rename: aVarNam yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameInstanceVariableRefactoring class >> rename: aVarName to: aName in: aClass [ ^ self new rename: aVarName @@ -45,7 +47,7 @@ RBRenameInstanceVariableRefactoring class >> rename: aVarName to: aName in: aCla in: aClass ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameInstanceVariableRefactoring class >> rename: aVarName to: aName in: aClass renameAccessors: aBoolean [ ^ self new rename: aVarName @@ -54,7 +56,7 @@ RBRenameInstanceVariableRefactoring class >> rename: aVarName to: aName in: aCla renameAccessors: aBoolean ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameInstanceVariableRefactoring >> addNewAccessors [ | refactoring | refactoring := RBCreateAccessorsForVariableTransformation @@ -67,28 +69,28 @@ RBRenameInstanceVariableRefactoring >> addNewAccessors [ createSetterAccessor ] -{ #category : #refactoring } +{ #category : 'refactoring' } RBRenameInstanceVariableRefactoring >> browsedEnvironment [ ^ browsedEnvironment ifNil: [ browsedEnvironment := RBBrowserEnvironment new ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameInstanceVariableRefactoring >> initialize [ super initialize. renameAccessors := false ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameInstanceVariableRefactoring >> newName [ ^ newName ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameInstanceVariableRefactoring >> newName: anObject [ newName := anObject ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameInstanceVariableRefactoring >> preconditions [ ^(RBCondition isValidInstanceVariableName: newName for: class) & (RBCondition definesInstanceVariable: variableName in: class) @@ -96,7 +98,7 @@ RBRenameInstanceVariableRefactoring >> preconditions [ & (RBCondition isGlobal: newName in: self model) not ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameInstanceVariableRefactoring >> privateTransform [ renameAccessors ifTrue: [ self removeOldAccessors @@ -109,7 +111,7 @@ RBRenameInstanceVariableRefactoring >> privateTransform [ self renameAccessorsReferences ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameInstanceVariableRefactoring >> removeOldAccessors [ | oldAccessors | oldAccessors := (class allSelectors @@ -118,29 +120,29 @@ RBRenameInstanceVariableRefactoring >> removeOldAccessors [ oldAccessors do: [ :each | class removeMethod: each selector ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameInstanceVariableRefactoring >> rename: aVarName to: aName in: aClass [ self rename: aVarName to: aName in: aClass renameAccessors: false ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenameInstanceVariableRefactoring >> rename: aVarName to: aName in: aClass renameAccessors: aBoolean [ self variable: aVarName class: aClass. newName := aName. renameAccessors := aBoolean ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameInstanceVariableRefactoring >> renameAccessors [ ^ renameAccessors ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameInstanceVariableRefactoring >> renameAccessors: anObject [ renameAccessors := anObject ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameInstanceVariableRefactoring >> renameAccessorsReferences [ | methods senders | methods := (class allSelectors select: [ :each | (class methodFor: each) isNotNil ] thenCollect: [ :each | each ]) @@ -160,7 +162,7 @@ RBRenameInstanceVariableRefactoring >> renameAccessorsReferences [ withProtocol: each protocols) ] ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenameInstanceVariableRefactoring >> renameReferences [ | replacer classes | replacer := self parseTreeRewriterClass @@ -177,7 +179,7 @@ RBRenameInstanceVariableRefactoring >> renameReferences [ using: replacer ] -{ #category : #printing } +{ #category : 'printing' } RBRenameInstanceVariableRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBRenameMethodRefactoring.class.st b/src/Refactoring-Core/RBRenameMethodRefactoring.class.st index 4c1548c0b75..73873771467 100644 --- a/src/Refactoring-Core/RBRenameMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBRenameMethodRefactoring.class.st @@ -30,15 +30,17 @@ refactoring execute ``` " Class { - #name : #RBRenameMethodRefactoring, - #superclass : #RBChangeMethodNameRefactoring, + #name : 'RBRenameMethodRefactoring', + #superclass : 'RBChangeMethodNameRefactoring', #instVars : [ 'hasPermutedArguments' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameMethodRefactoring class >> model: aRBSmalltalk renameMethod: aSelector in: aClass to: newSelector permutation: aMap [ ^ self new model: aRBSmalltalk; @@ -49,7 +51,7 @@ RBRenameMethodRefactoring class >> model: aRBSmalltalk renameMethod: aSelector i yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenameMethodRefactoring class >> renameMethod: aSelector in: aClass to: newSelector permutation: aMap [ ^ self new renameMethod: aSelector @@ -58,7 +60,7 @@ RBRenameMethodRefactoring class >> renameMethod: aSelector in: aClass to: newSel permutation: aMap ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameMethodRefactoring >> applicabilityPreconditions [ ^ self newNameDoesNotRequireRefactoringPreconditions not & (RBCondition @@ -67,13 +69,13 @@ RBRenameMethodRefactoring >> applicabilityPreconditions [ , ' doesn''t have the correct number of arguments.') ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameMethodRefactoring >> breakingChangePreconditions [ ^ self doesNotOverrideExistingMethodPrecondition ] -{ #category : #actions } +{ #category : 'actions' } RBRenameMethodRefactoring >> generateChanges [ @@ -88,7 +90,7 @@ RBRenameMethodRefactoring >> generateChanges [ ^ self changes ] -{ #category : #testing } +{ #category : 'testing' } RBRenameMethodRefactoring >> hasPermutedArguments [ ^ hasPermutedArguments @@ -96,25 +98,25 @@ RBRenameMethodRefactoring >> hasPermutedArguments [ ifNotNil: [ hasPermutedArguments ] ] -{ #category : #testing } +{ #category : 'testing' } RBRenameMethodRefactoring >> implementorsCanBePrimitives [ ^self hasPermutedArguments not ] -{ #category : #private } +{ #category : 'private' } RBRenameMethodRefactoring >> modifyImplementorParseTree: parseTree in: aClass [ super modifyImplementorParseTree: parseTree in: aClass. self renameArgumentsIn: parseTree ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameMethodRefactoring >> myConditions [ ^RBCondition withBlock: [oldSelector numArgs = newSelector numArgs] errorString: newSelector printString , ' doesn''t have the correct number of arguments.' ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameMethodRefactoring >> newNameDoesNotRequireRefactoringPreconditions [ "this could be part of skippingRefactoringPrecondition meaning that there is no need to execute it." @@ -129,7 +131,7 @@ RBRenameMethodRefactoring >> newNameDoesNotRequireRefactoringPreconditions [ errorString: 'The arguments are <1?:not >permuted') ] -{ #category : #parsing } +{ #category : 'parsing' } RBRenameMethodRefactoring >> parseTreeRewriterInstance [ ^ self hasPermutedArguments @@ -140,18 +142,18 @@ RBRenameMethodRefactoring >> parseTreeRewriterInstance [ with: newSelector ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenameMethodRefactoring >> preconditions [ ^ self newNameDoesNotRequireRefactoringPreconditions | super preconditions ] -{ #category : #accessing } +{ #category : 'accessing' } RBRenameMethodRefactoring >> refactoredClass [ ^ class ] -{ #category : #printing } +{ #category : 'printing' } RBRenameMethodRefactoring >> storeOn: aStream [ aStream nextPut: $(. aStream nextPutAll: self class name. diff --git a/src/Refactoring-Core/RBRenamePackageRefactoring.class.st b/src/Refactoring-Core/RBRenamePackageRefactoring.class.st index 8acc7018bb8..91f94d1efb6 100644 --- a/src/Refactoring-Core/RBRenamePackageRefactoring.class.st +++ b/src/Refactoring-Core/RBRenamePackageRefactoring.class.st @@ -14,15 +14,17 @@ Example ``` " Class { - #name : #RBRenamePackageRefactoring, - #superclass : #RBPackageRefactoring, + #name : 'RBRenamePackageRefactoring', + #superclass : 'RBPackageRefactoring', #instVars : [ 'package' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenamePackageRefactoring class >> model: aRBSmalltalk rename: aSymbol to: aNewName [ ^ self new model: aRBSmalltalk; @@ -30,27 +32,27 @@ RBRenamePackageRefactoring class >> model: aRBSmalltalk rename: aSymbol to: aNew yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBRenamePackageRefactoring class >> rename: aString to: aNewName [ ^ self new packageName: aString newName: aNewName ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenamePackageRefactoring >> manifestClassNameFor: aPackageName [ "Returns a symbol representing a suitable name for a Manifest class for the given package" ^('Manifest', (aPackageName select: [:each | each isAlphaNumeric ])) asSymbol ] -{ #category : #initialization } +{ #category : 'initialization' } RBRenamePackageRefactoring >> packageName: aName newName: aNewName [ packageName := aName asSymbol. package := self model packageNamed: packageName. newName := aNewName asSymbol ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBRenamePackageRefactoring >> preconditions [ ^ super preconditions & (RBCondition withBlock: [ newName ~= packageName ] errorString: 'The new package name is the same as the old package name.') @@ -60,14 +62,14 @@ RBRenamePackageRefactoring >> preconditions [ errorString: 'The system already includes a package named ' , newName) ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenamePackageRefactoring >> privateTransform [ self renamePackage. self renameManifestClass ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenamePackageRefactoring >> renameManifestClass [ |refactoring manifest| manifest := package realPackage packageManifestOrNil. @@ -79,12 +81,12 @@ RBRenamePackageRefactoring >> renameManifestClass [ self generateChangesFor: refactoring] ] -{ #category : #transforming } +{ #category : 'transforming' } RBRenamePackageRefactoring >> renamePackage [ self model renamePackage: package to: newName ] -{ #category : #printing } +{ #category : 'printing' } RBRenamePackageRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBReplaceMessageSendTransformation.class.st b/src/Refactoring-Core/RBReplaceMessageSendTransformation.class.st index 8b827b2d4fe..e13c88a3aee 100644 --- a/src/Refactoring-Core/RBReplaceMessageSendTransformation.class.st +++ b/src/Refactoring-Core/RBReplaceMessageSendTransformation.class.st @@ -20,8 +20,8 @@ All senders of this method are changed by the other. ``` " Class { - #name : #RBReplaceMessageSendTransformation, - #superclass : #RBMethodRefactoring, + #name : 'RBReplaceMessageSendTransformation', + #superclass : 'RBMethodRefactoring', #instVars : [ 'replaceInAllClasses', 'oldSelector', @@ -29,22 +29,24 @@ Class { 'permutation', 'newArgs' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #displaying } +{ #category : 'displaying' } RBReplaceMessageSendTransformation class >> basicMenuItemString [ ^ 'Replace senders' ] -{ #category : #displaying } +{ #category : 'displaying' } RBReplaceMessageSendTransformation class >> isTransformation [ ^ true ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap [ ^ self new model: aRBSmalltalk; @@ -55,7 +57,7 @@ RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: a yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [ ^ self new model: aRBSmalltalk; @@ -67,7 +69,7 @@ RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: a yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean newArgs: anArgsCollection [ ^ self new model: aRBSmalltalk; @@ -80,7 +82,7 @@ RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: a yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: aSelector in: aClass to: newSelector permutation: aMap newArgs: anArgsCollection [ ^ self new model: aRBSmalltalk; @@ -92,7 +94,7 @@ RBReplaceMessageSendTransformation class >> model: aRBSmalltalk replaceMethod: a yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap [ ^self new replaceCallMethod: aSelector @@ -101,7 +103,7 @@ RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aCl permutation: aMap ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean [ ^self new replaceCallMethod: aSelector @@ -111,7 +113,7 @@ RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aCl inAllClasses: aBoolean ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap inAllClasses: aBoolean newArgs: anArgsCollection [ ^self new replaceCallMethod: aSelector @@ -122,7 +124,7 @@ RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aCl newArgs: anArgsCollection ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aClass to: newSelector permutation: aMap newArgs: anArgsCollection [ ^self new replaceCallMethod: aSelector @@ -132,7 +134,7 @@ RBReplaceMessageSendTransformation class >> replaceCallMethod: aSelector in: aCl newArgs: anArgsCollection ] -{ #category : #support } +{ #category : 'support' } RBReplaceMessageSendTransformation >> convertAllReferencesTo: aSymbol of: classes using: searchReplacer [ (self model allReferencesTo: aSymbol in: classes) do: @@ -143,7 +145,7 @@ RBReplaceMessageSendTransformation >> convertAllReferencesTo: aSymbol of: classe using: searchReplacer] ] -{ #category : #support } +{ #category : 'support' } RBReplaceMessageSendTransformation >> convertAllReferencesTo: aSymbol using: searchReplacer [ (self model allReferencesTo: aSymbol) @@ -154,25 +156,25 @@ RBReplaceMessageSendTransformation >> convertAllReferencesTo: aSymbol using: sea thenDo: [ :method | self convertMethod: method selector for: method modelClass using: searchReplacer ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBReplaceMessageSendTransformation >> newArgs [ ^ newArgs ifNil: [ newArgs := { } ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBReplaceMessageSendTransformation >> newArgs: anArgsCollection [ newArgs := anArgsCollection ] -{ #category : #private } +{ #category : 'private' } RBReplaceMessageSendTransformation >> newSelectorString [ ^ self buildSelectorString: newSelector withPermuteMap: permutation andNewArguments: newArgs ] -{ #category : #parsing } +{ #category : 'parsing' } RBReplaceMessageSendTransformation >> parseTreeRewriter [ | rewriteRule oldString newString | @@ -185,7 +187,7 @@ RBReplaceMessageSendTransformation >> parseTreeRewriter [ ^rewriteRule ] -{ #category : #parsing } +{ #category : 'parsing' } RBReplaceMessageSendTransformation >> parseTreeRewriterInstance [ ^ self parseTreeRewriterClass @@ -193,7 +195,7 @@ RBReplaceMessageSendTransformation >> parseTreeRewriterInstance [ with: newSelector ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBReplaceMessageSendTransformation >> preconditions [ | conditions | @@ -211,14 +213,14 @@ RBReplaceMessageSendTransformation >> preconditions [ ^ conditions ] -{ #category : #transforming } +{ #category : 'transforming' } RBReplaceMessageSendTransformation >> privateTransform [ self replaceInAllClasses ifTrue: [ self replaceMessageSends ] ifFalse: [ self replaceMessageSendsIn: {class} ] ] -{ #category : #initialization } +{ #category : 'initialization' } RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap [ oldSelector := aSelector asSymbol. @@ -228,21 +230,21 @@ RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to newArgs := OrderedCollection new. ] -{ #category : #initialization } +{ #category : 'initialization' } RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap inAllClasses: aBoolean [ self replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap. replaceInAllClasses := aBoolean ] -{ #category : #initialization } +{ #category : 'initialization' } RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap inAllClasses: aBoolean newArgs: anArgsCollection [ self replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap newArgs: anArgsCollection. replaceInAllClasses := aBoolean ] -{ #category : #initialization } +{ #category : 'initialization' } RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to: newSel permutation: aMap newArgs: anArgsCollection [ oldSelector := aSelector asSymbol. @@ -252,17 +254,17 @@ RBReplaceMessageSendTransformation >> replaceCallMethod: aSelector in: aClass to newArgs := anArgsCollection ] -{ #category : #accessing } +{ #category : 'accessing' } RBReplaceMessageSendTransformation >> replaceInAllClasses [ ^ replaceInAllClasses ifNil: [ replaceInAllClasses := false ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBReplaceMessageSendTransformation >> replaceMessageSends [ self convertAllReferencesTo: oldSelector using: self parseTreeRewriter ] -{ #category : #transforming } +{ #category : 'transforming' } RBReplaceMessageSendTransformation >> replaceMessageSendsIn: classes [ self convertAllReferencesTo: oldSelector of: classes using: self parseTreeRewriter ] diff --git a/src/Refactoring-Core/RBSourceRegexTransformation.class.st b/src/Refactoring-Core/RBSourceRegexTransformation.class.st index 8512ede2891..c1ef4d393df 100644 --- a/src/Refactoring-Core/RBSourceRegexTransformation.class.st +++ b/src/Refactoring-Core/RBSourceRegexTransformation.class.st @@ -4,26 +4,28 @@ I am a regex refactoring replacing method sources. See comment of superclass for a nice script to be adapated to method sources. " Class { - #name : #RBSourceRegexTransformation, - #superclass : #RBRegexRefactoring, - #category : #'Refactoring-Core-Transformation-Unused' + #name : 'RBSourceRegexTransformation', + #superclass : 'RBRegexRefactoring', + #category : 'Refactoring-Core-Transformation-Unused', + #package : 'Refactoring-Core', + #tag : 'Transformation-Unused' } -{ #category : #private } +{ #category : 'private' } RBSourceRegexTransformation >> parseMethod: aString [ ^ [ self parserClass parseMethod: aString ] on: Error do: [ :err | nil ] ] -{ #category : #private } +{ #category : 'private' } RBSourceRegexTransformation >> parseSelector: aSelector [ ^ [ self parserClass parseMethodPattern: aSelector ] on: Error do: [ nil ] ] -{ #category : #transforming } +{ #category : 'transforming' } RBSourceRegexTransformation >> privateTransform [ | original replacement protocols | diff --git a/src/Refactoring-Core/RBSplitCascadeRefactoring.class.st b/src/Refactoring-Core/RBSplitCascadeRefactoring.class.st index 6bcbb5d1c41..28e6e8bfa49 100644 --- a/src/Refactoring-Core/RBSplitCascadeRefactoring.class.st +++ b/src/Refactoring-Core/RBSplitCascadeRefactoring.class.st @@ -8,8 +8,8 @@ My preconditions verify that the selector containing the cascaded message send i If the receiver of the cascade expression is a literal or the return value of another message send, I will add another temporary variable for the interim result. " Class { - #name : #RBSplitCascadeRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBSplitCascadeRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'selectedInterval', @@ -19,10 +19,12 @@ Class { 'afterNodes', 'ancestorNode' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSplitCascadeRefactoring class >> model: aNamespace split: anInterval from: aSelector in: aClass [ ^ self new model: aNamespace; @@ -30,14 +32,14 @@ RBSplitCascadeRefactoring class >> model: aNamespace split: anInterval from: aSe yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSplitCascadeRefactoring class >> split: anInterval from: aSelector in: aClass [ ^ self new split: anInterval from: aSelector in: aClass; yourself ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitCascadeRefactoring >> extractReceiver [ | name | (cascadeNode receiver isLiteralNode or: [ cascadeNode receiver isVariable ]) @@ -56,7 +58,7 @@ RBSplitCascadeRefactoring >> extractReceiver [ do: [ :each | each receiver: (RBVariableNode named: name) ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSplitCascadeRefactoring >> findAncestorNode [ "The ancestor node is the node that is contained within the sequence. In most cases this is the cascade itself, but it also can be an assignment or a return node." @@ -69,7 +71,7 @@ RBSplitCascadeRefactoring >> findAncestorNode [ ifFalse: [ self refactoringError: 'To split this cascade, you must extract it to a temporary first' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSplitCascadeRefactoring >> findCascadeNode [ "Find the cascade to be split." @@ -81,7 +83,7 @@ RBSplitCascadeRefactoring >> findCascadeNode [ ifNil: [ self refactoringError: 'The selection doesn''t appear to be within a cascade' ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSplitCascadeRefactoring >> findMessageNodes [ "Find the nodes that form the first part of the cascade and the second part of the cascade." @@ -95,7 +97,7 @@ RBSplitCascadeRefactoring >> findMessageNodes [ ifFalse: [ self refactoringError: 'To set the split boundary place the cursor inbetween two cascaded messages' ] ] -{ #category : #accessing } +{ #category : 'accessing' } RBSplitCascadeRefactoring >> parseTree [ parseTree @@ -105,27 +107,27 @@ RBSplitCascadeRefactoring >> parseTree [ ^ parseTree doSemanticAnalysis ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSplitCascadeRefactoring >> preconditions [ ^ (RBCondition definesSelector: selector in: class) & (RBCondition withBlock: [ self findCascadeNode; findAncestorNode; findMessageNodes. true ]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitCascadeRefactoring >> privateTransform [ self extractReceiver. self splitCascade ] -{ #category : #initialization } +{ #category : 'initialization' } RBSplitCascadeRefactoring >> split: anInterval from: aSelector in: aClass [ class := self classObjectFor: aClass. selector := aSelector. selectedInterval := anInterval ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitCascadeRefactoring >> splitCascade [ ancestorNode parent addNode: (beforeNodes size > 1 @@ -138,7 +140,7 @@ RBSplitCascadeRefactoring >> splitCascade [ class compileTree: ancestorNode methodNode ] -{ #category : #printing } +{ #category : 'printing' } RBSplitCascadeRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBSplitClassRefactoring.class.st b/src/Refactoring-Core/RBSplitClassRefactoring.class.st index 32b199fff82..d855178bbf9 100644 --- a/src/Refactoring-Core/RBSplitClassRefactoring.class.st +++ b/src/Refactoring-Core/RBSplitClassRefactoring.class.st @@ -30,8 +30,8 @@ and every reference to the old vars color / font / style will be replaced by tex " Class { - #name : #RBSplitClassRefactoring, - #superclass : #RBRefactoring, + #name : 'RBSplitClassRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'class', 'instanceVariables', @@ -39,10 +39,12 @@ Class { 'referenceVariableName', 'newClass' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSplitClassRefactoring class >> class: class instanceVariables: instVars newClassName: className referenceVariableName: newVariable [ ^ self new class: class @@ -52,7 +54,7 @@ RBSplitClassRefactoring class >> class: class instanceVariables: instVars newCla yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSplitClassRefactoring class >> model: aRBSmalltalk class: class instanceVariables: instVars newClassName: className referenceVariableName: newVariable [ ^ self new model: aRBSmalltalk; @@ -63,7 +65,7 @@ RBSplitClassRefactoring class >> model: aRBSmalltalk class: class instanceVariab yourself ] -{ #category : #'private - transforming' } +{ #category : 'private - transforming' } RBSplitClassRefactoring >> abstractReferenceTo: each [ | setterMethod replacer accessorRef getterMethod | @@ -88,12 +90,12 @@ RBSplitClassRefactoring >> abstractReferenceTo: each [ (RBRemoveInstanceVariableRefactoring remove: each from: class) ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitClassRefactoring >> abstractVariableReferences [ instanceVariables do: [:each | self abstractReferenceTo: each] ] -{ #category : #'private - transforming' } +{ #category : 'private - transforming' } RBSplitClassRefactoring >> addClass [ self generateChangesFor: (RBInsertNewClassRefactoring model: self model @@ -104,7 +106,7 @@ RBSplitClassRefactoring >> addClass [ newClass := self model classNamed: newClassName asSymbol ] -{ #category : #'private - transforming' } +{ #category : 'private - transforming' } RBSplitClassRefactoring >> addInstanceVariables [ instanceVariables do: [:each | @@ -114,7 +116,7 @@ RBSplitClassRefactoring >> addInstanceVariables [ class: newClass)] ] -{ #category : #initialization } +{ #category : 'initialization' } RBSplitClassRefactoring >> class: aClass instanceVariables: instVars newClassName: className referenceVariableName: newVariable [ class := self model classObjectFor: aClass. instanceVariables := instVars. @@ -122,21 +124,21 @@ RBSplitClassRefactoring >> class: aClass instanceVariables: instVars newClassNam referenceVariableName := newVariable ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitClassRefactoring >> createNewClass [ self addClass; addInstanceVariables ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitClassRefactoring >> createReference [ self generateChangesFor: (RBAddInstanceVariableRefactoring variable: referenceVariableName class: class) ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSplitClassRefactoring >> preconditions [ ^(RBCondition isValidClassName: newClassName) & (RBCondition isGlobal: newClassName in: self model) not @@ -148,7 +150,7 @@ RBSplitClassRefactoring >> preconditions [ not ] -{ #category : #transforming } +{ #category : 'transforming' } RBSplitClassRefactoring >> privateTransform [ self createNewClass; @@ -156,7 +158,7 @@ RBSplitClassRefactoring >> privateTransform [ abstractVariableReferences ] -{ #category : #printing } +{ #category : 'printing' } RBSplitClassRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBSwapMethodRefactoring.class.st b/src/Refactoring-Core/RBSwapMethodRefactoring.class.st index 681cabfd827..6f3f0b75ed8 100644 --- a/src/Refactoring-Core/RBSwapMethodRefactoring.class.st +++ b/src/Refactoring-Core/RBSwapMethodRefactoring.class.st @@ -4,16 +4,18 @@ Move a method from the class to the instance side, or vice versa. Normally this Only instance methods with no instance variable access or class methods with no class instance variable access can be moved. " Class { - #name : #RBSwapMethodRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBSwapMethodRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'target', 'selector' ], - #category : #'Refactoring-Core-Refactorings-Unused' + #category : 'Refactoring-Core-Refactorings-Unused', + #package : 'Refactoring-Core', + #tag : 'Refactorings-Unused' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSwapMethodRefactoring class >> model: aRBSmalltalk swapMethod: aSelector in: aClass [ ^ self new model: aRBSmalltalk; @@ -21,13 +23,13 @@ RBSwapMethodRefactoring class >> model: aRBSmalltalk swapMethod: aSelector in: a yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBSwapMethodRefactoring class >> swapMethod: aSelector in: aClass [ ^ self new swapMethod: aSelector in: aClass ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSwapMethodRefactoring >> checkInstVars [ class instanceVariableNames do: [ :each | (target instanceVariableNames includes: each) ifFalse: [ @@ -36,14 +38,14 @@ RBSwapMethodRefactoring >> checkInstVars [ refactoringError: ('<1p> refers to <2s>, which is not defined in <3p>' expandMacrosWith: selector with: each with: target) ] ] ] ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBSwapMethodRefactoring >> preconditions [ ^ (RBCondition definesSelector: selector in: class) & (RBCondition definesSelector: selector in: target) not & (RBCondition withBlock: [ self checkInstVars. true ]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBSwapMethodRefactoring >> privateTransform [ self generateChangesFor: @@ -54,7 +56,7 @@ RBSwapMethodRefactoring >> privateTransform [ class removeMethod: selector ] -{ #category : #initialization } +{ #category : 'initialization' } RBSwapMethodRefactoring >> swapMethod: aSelector in: aClass [ class := self classObjectFor: aClass. target := self classObjectFor: (class isMeta diff --git a/src/Refactoring-Core/RBTemporaryToInstanceVariableRefactoring.class.st b/src/Refactoring-Core/RBTemporaryToInstanceVariableRefactoring.class.st index 60b632d4993..85bb30a0446 100644 --- a/src/Refactoring-Core/RBTemporaryToInstanceVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBTemporaryToInstanceVariableRefactoring.class.st @@ -65,16 +65,18 @@ MyClassA subclass: #MyClassB ``` " Class { - #name : #RBTemporaryToInstanceVariableRefactoring, - #superclass : #RBMethodRefactoring, + #name : 'RBTemporaryToInstanceVariableRefactoring', + #superclass : 'RBMethodRefactoring', #instVars : [ 'selector', 'temporaryVariableName' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBTemporaryToInstanceVariableRefactoring class >> class: aClass selector: aSelector variable: aVariableName [ ^ self new class: aClass @@ -82,7 +84,7 @@ RBTemporaryToInstanceVariableRefactoring class >> class: aClass selector: aSelec variable: aVariableName ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBTemporaryToInstanceVariableRefactoring class >> model: aRBSmalltalk class: aClass selector: aSelector variable: aVariableName [ ^ self new model: aRBSmalltalk; @@ -92,7 +94,7 @@ RBTemporaryToInstanceVariableRefactoring class >> model: aRBSmalltalk class: aCl yourself ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBTemporaryToInstanceVariableRefactoring >> checkForValidTemporaryVariable [ | parseTree | parseTree := class parseTreeForSelector: selector. @@ -111,14 +113,14 @@ RBTemporaryToInstanceVariableRefactoring >> checkForValidTemporaryVariable [ expandMacrosWith: temporaryVariableName)] ] -{ #category : #initialization } +{ #category : 'initialization' } RBTemporaryToInstanceVariableRefactoring >> class: aClass selector: aSelector variable: aVariableName [ class := self classObjectFor: aClass. selector := aSelector. temporaryVariableName := aVariableName ] -{ #category : #preconditions } +{ #category : 'preconditions' } RBTemporaryToInstanceVariableRefactoring >> preconditions [ ^(RBCondition definesSelector: selector in: class) & (RBCondition definesInstanceVariable: temporaryVariableName asString in: class) not @@ -133,7 +135,7 @@ RBTemporaryToInstanceVariableRefactoring >> preconditions [ true]) ] -{ #category : #transforming } +{ #category : 'transforming' } RBTemporaryToInstanceVariableRefactoring >> privateTransform [ self removeTemporaryOfClass: class. @@ -144,12 +146,12 @@ RBTemporaryToInstanceVariableRefactoring >> privateTransform [ class addInstanceVariable: temporaryVariableName ] -{ #category : #removing } +{ #category : 'removing' } RBTemporaryToInstanceVariableRefactoring >> removeTemporaryOfClass: aClass [ aClass selectors do: [ :aSymbol | self removeTemporaryOfMethod: aSymbol in: aClass ] ] -{ #category : #removing } +{ #category : 'removing' } RBTemporaryToInstanceVariableRefactoring >> removeTemporaryOfMethod: aSelector in: aClass [ | parseTree matcher method | @@ -161,7 +163,7 @@ RBTemporaryToInstanceVariableRefactoring >> removeTemporaryOfMethod: aSelector i method compileTree: matcher tree ] -{ #category : #printing } +{ #category : 'printing' } RBTemporaryToInstanceVariableRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. diff --git a/src/Refactoring-Core/RBTrait.class.st b/src/Refactoring-Core/RBTrait.class.st index 3f595a93db9..59f6eff111f 100644 --- a/src/Refactoring-Core/RBTrait.class.st +++ b/src/Refactoring-Core/RBTrait.class.st @@ -5,30 +5,32 @@ I shouldn't be created directly, but always be part of a refactoring namespace. My namespace usally knows me and my meta class. " Class { - #name : #RBTrait, - #superclass : #RBClass, + #name : 'RBTrait', + #superclass : 'RBClass', #instVars : [ 'users' ], - #category : #'Refactoring-Core-Model' + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } -{ #category : #accessing } +{ #category : 'accessing' } RBTrait >> definesInstanceVariable: aString [ ^ self directlyDefinesInstanceVariable: aString ] -{ #category : #testing } +{ #category : 'testing' } RBTrait >> isTrait [ ^ true ] -{ #category : #accessing } +{ #category : 'accessing' } RBTrait >> superclass [ ^ nil ] -{ #category : #accessing } +{ #category : 'accessing' } RBTrait >> users [ ^ users ifNil: [ users := realClass users collect: [ :e | model classNamed: e name ] ] ] diff --git a/src/Refactoring-Core/RBTraitedMetaclass.class.st b/src/Refactoring-Core/RBTraitedMetaclass.class.st index 604ce5fba9b..0d4c0c952db 100644 --- a/src/Refactoring-Core/RBTraitedMetaclass.class.st +++ b/src/Refactoring-Core/RBTraitedMetaclass.class.st @@ -5,7 +5,9 @@ I shouldn't be created directly, but always be part of a refactoring namespace. My namespace usally knows me and my non meta class. " Class { - #name : #RBTraitedMetaclass, - #superclass : #RBMetaclass, - #category : #'Refactoring-Core-Model' + #name : 'RBTraitedMetaclass', + #superclass : 'RBMetaclass', + #category : 'Refactoring-Core-Model', + #package : 'Refactoring-Core', + #tag : 'Model' } diff --git a/src/Refactoring-Core/RBVariableRefactoring.class.st b/src/Refactoring-Core/RBVariableRefactoring.class.st index dc2b2e976bd..d65cbcb2421 100644 --- a/src/Refactoring-Core/RBVariableRefactoring.class.st +++ b/src/Refactoring-Core/RBVariableRefactoring.class.st @@ -2,22 +2,24 @@ I am an abstract base class of refactorings modifying class or instance variables. " Class { - #name : #RBVariableRefactoring, - #superclass : #RBRefactoring, + #name : 'RBVariableRefactoring', + #superclass : 'RBRefactoring', #instVars : [ 'class', 'variableName' ], - #category : #'Refactoring-Core-Refactorings' + #category : 'Refactoring-Core-Refactorings', + #package : 'Refactoring-Core', + #tag : 'Refactorings' } -{ #category : #testing } +{ #category : 'testing' } RBVariableRefactoring class >> isAbstract [ ^ self == RBVariableRefactoring ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBVariableRefactoring class >> model: aRBSmalltalk variable: aVarName class: aClass [ ^ self new model: aRBSmalltalk; @@ -25,18 +27,18 @@ RBVariableRefactoring class >> model: aRBSmalltalk variable: aVarName class: aCl yourself ] -{ #category : #'instance creation' } +{ #category : 'instance creation' } RBVariableRefactoring class >> variable: aVarName class: aClass [ ^ self new variable: aVarName class: aClass ] -{ #category : #initialization } +{ #category : 'initialization' } RBVariableRefactoring >> refactoredClassName [ ^ class name ] -{ #category : #printing } +{ #category : 'printing' } RBVariableRefactoring >> storeOn: aStream [ aStream nextPut: $(. self class storeOn: aStream. @@ -47,13 +49,13 @@ RBVariableRefactoring >> storeOn: aStream [ aStream nextPut: $) ] -{ #category : #initialization } +{ #category : 'initialization' } RBVariableRefactoring >> variable: aVarName class: aClassName [ class := self classObjectFor: aClassName. variableName := aVarName ] -{ #category : #accessing } +{ #category : 'accessing' } RBVariableRefactoring >> variableName [ ^ variableName diff --git a/src/Refactoring-Core/package.st b/src/Refactoring-Core/package.st index 2cd0d44a7fc..ad4d3483b9d 100644 --- a/src/Refactoring-Core/package.st +++ b/src/Refactoring-Core/package.st @@ -1 +1 @@ -Package { #name : #'Refactoring-Core' } +Package { #name : 'Refactoring-Core' }