Skip to content

Commit

Permalink
Add "Remove Import" refactoring and many other refactoring improvements
Browse files Browse the repository at this point in the history
- Reorganise the Change Objects hierarchy significantly and add more unit
tests
- Move remaining refactoring classes in Tools namespace and dev sys
packages, and associated tests, into the Refactory packages. The latter are
now so heavily modified, that keeping the Dolphin additions separate is no
longer useful.
- File out 'mourner' flag in the same way as other special behaviour flags
- Add checkboxes for setting new class type, such as bytes/variable or
abstract, to the Create Subclass dialog. Add more validation to the dialog
so that errors are picked up in advance, rather than later throwing errors
from the class builder.
- The result of the CreateSubclassDialog is now a ClassDetails object that
describes everything about the class to be created, and which can also
describe all the other details of a class that are not currently settable
in this dialog. This is then also used elsewhere in the AddClassRefactoring
and AddClassChange to hold details, and can stand in as a proxy for a class
for source filing purposes too.
- Replace the PoolDictionariesShell (appearing as the 'Pool Dictionaries'
tool in the system launcher) with NamespaceShell, that is basically the
same in terms of presentation. The original functionality to create/delete
pool (now namespaces) and add or remove pool variables (now namespace
variables) is still present, but generally delegated to SmalltalkSystem to
perform using the appropriate refactoring (work still needed for adding
variables though).
  • Loading branch information
blairmcg committed Jun 18, 2022
1 parent 77647b5 commit d2b8d98
Show file tree
Hide file tree
Showing 221 changed files with 3,430 additions and 2,403 deletions.
8 changes: 4 additions & 4 deletions Core/Contributions/IDB/MethodHistoryBrowser.cls
Original file line number Diff line number Diff line change
Expand Up @@ -250,10 +250,10 @@ source
updateHistory
"Get the historic information for the method. Purge consecutive duplicates from the list"

| temp |
Cursor wait showWhile: [temp := self scanner scanForMethodVersions: selector inClass: self methodClass].
history := OrderedCollection with: temp first.
temp do:
| versions |
versions := Cursor wait showWhile: [self scanner scanForMethodVersions: selector inClass: self methodClass].
history := OrderedCollection with: versions first.
versions do:
[:each |
((history last hasSameSourceAs: each) and: [history last sourceFileIndex = each sourceFileIndex])
ifFalse: [history add: each]].
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,13 @@ package setClassNames: #(
#{Refactory.Browser.AddMethodChange}
#{Refactory.Browser.AddSharedVariableChange}
#{Refactory.Browser.BasicRenameClassChange}
#{Refactory.Browser.ChangeSet}
#{Refactory.Browser.ClassAttributeChange}
#{Refactory.Browser.ClassAttributes}
#{Refactory.Browser.ClassCategoryChange}
#{Refactory.Browser.ClassCommentChange}
#{Refactory.Browser.ClassDetails}
#{Refactory.Browser.ClassGuidChange}
#{Refactory.Browser.ClassImportsChange}
#{Refactory.Browser.ClassModificationChange}
#{Refactory.Browser.ClassSpecialBehaviorChange}
#{Refactory.Browser.CompositeRefactoryChange}
#{Refactory.Browser.MoveClassChange}
Expand All @@ -47,7 +47,6 @@ package setClassNames: #(

package setPrerequisites: #(
'..\..\..\..\Object Arts\Dolphin\Base\Dolphin'
'..\Environments\RBEnvironments'
'..\..\RBNamespaces'
'..\..\..\..\Object Arts\Dolphin\System\Compiler\Smalltalk Parser'
).
Expand All @@ -56,14 +55,8 @@ package!

"Class Definitions"!

Core.Object subclass: #'Refactory.Browser.ChangeSet'
instanceVariableNames: ''
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Core.Object subclass: #'Refactory.Browser.ClassAttributes'
instanceVariableNames: 'className superclassName instanceVariableNames classVariableNames imports classConstants classInstanceVariableNames instanceSpec guid comment categories'
Core.Object subclass: #'Refactory.Browser.ClassDetails'
instanceVariableNames: 'classReference superclassReference instanceVariableNames classVariableNames imports classConstants classInstanceVariableNames instanceSpec guid comment categoryNames package'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
Expand All @@ -87,7 +80,7 @@ Refactory.Browser.RefactoryChange subclass: #'Refactory.Browser.CompositeRefacto
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryChange subclass: #'Refactory.Browser.RefactoryClassChange'
instanceVariableNames: 'classReference'
instanceVariableNames: ''
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
Expand Down Expand Up @@ -123,48 +116,54 @@ Refactory.Browser.RenameVariableChange subclass: #'Refactory.Browser.RenameInsta
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.AddClassChange'
instanceVariableNames: 'definition attributes'
instanceVariableNames: 'definition details'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.ClassModificationChange'
instanceVariableNames: 'classReference'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.BasicRenameClassChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.BasicRenameClassChange'
instanceVariableNames: 'newName'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.ClassAttributeChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.ClassAttributeChange'
instanceVariableNames: ''
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.ClassImportsChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.ClassImportsChange'
instanceVariableNames: 'imports'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.MoveClassChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.MoveClassChange'
instanceVariableNames: 'superclassName'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.RefactoryMethodChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.RefactoryMethodChange'
instanceVariableNames: 'selector'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.RefactoryVariableChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.RefactoryVariableChange'
instanceVariableNames: 'variable'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
classConstants: {}!
Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.RemoveClassChange'
Refactory.Browser.ClassModificationChange subclass: #'Refactory.Browser.RemoveClassChange'
instanceVariableNames: ''
classVariableNames: ''
imports: #()
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
"Filed out from Dolphin Smalltalk"!

Refactory.Browser.RefactoryClassChange subclass: #'Refactory.Browser.AddClassChange'
instanceVariableNames: 'definition attributes'
instanceVariableNames: 'definition details'
classVariableNames: ''
imports: #()
classInstanceVariableNames: ''
Expand All @@ -13,7 +13,7 @@ Refactory.Browser.AddClassChange comment: ''!

= anAddClassChange
self class = anAddClassChange class ifFalse: [^false].
^definition = anAddClassChange definition!
^self definition = anAddClassChange definition!

areSubclassCreationMessageArgumentsValid: aMessageNode
^aMessageNode arguments allSatisfy: [:each | each isLiteralNode or: [each isDynamicArray]]!
Expand All @@ -22,94 +22,99 @@ asUndoOperation
| class |
class := self classReference valueOrNil.
^class isBehavior
ifTrue: [self class definition: class definition]
ifTrue: [self class details: (ClassDetails fromClass: class)]
ifFalse: [RemoveClassChange removeClassName: self changeClassName]!

attributes
^attributes ifNil: [self fillOutDefinition]!

category
^self attributes category!
categoryNames
^self details categoryNames!

changeClassName
^self attributes className!
^self details className!

changeString
^'Define <1d>' << self classReference!

classConstants
^self attributes classConstants!
^self details classConstants!

classReference
self attributes.
^classReference!
^self details classReference!

classReference: aBindingReference
self details classReference: aBindingReference!

classVariableNames
^self attributes classVariableNames!
^self details classVariableNames!

definingSuperclass
^self class!

definition
^definition!
^definition ifNil: [definition := details printString]!

definition: aString
definition := aString!
definition := aString.
^self!

details
^details ifNil: [self fillOutDefinition]!

details: aClassDetails
details := aClassDetails.
^self!

fillOutDefinition
| parseTree |
parseTree := Parser parseExpression: definition onError: [:str :pos | ^self parseDefinitionError].
parseTree := Parser parseExpression: self definition onError: [:str :pos | ^self parseDefinitionError].
parseTree isMessage ifFalse: [^self parseDefinitionError].
(self isValidSubclassCreationMessage: parseTree) ifFalse: [^self parseDefinitionError].
self fillOutDefinitionArguments: parseTree.
^attributes!
^details!

fillOutDefinitionArguments: parseTree
| args keywords pairs |
attributes := ClassAttributes new.
attributes superclassName: (parseTree receiver isVariable
details := ClassDetails new.
details superclassName: (parseTree receiver isVariable
ifTrue: [parseTree receiver name asSymbol]
ifFalse: [parseTree receiver value]).
args := parseTree arguments.
keywords := parseTree selector keywords.
"The new class name is always the 1st argument, but might have differing selector keywords, so look up by position"
attributes
className: (classReference := (args at: 1) value);
details
className: (args at: 1) value;
kindOfSubclass: (keywords at: 1).
classReference := attributes className asQualifiedReference.
pairs := LookupTable new.
keywords with: args do: [:eachKeyword :eachArg | pairs at: eachKeyword put: eachArg].
attributes
details
instanceVariableNames: (self namesIn: (pairs at: 'instanceVariableNames:') value);
classVariableNames: (self namesIn: (pairs at: 'classVariableNames:') value).
(pairs lookup: 'imports:')
ifNil:
[(pairs lookup: 'poolDictionaries:')
ifNotNil: [:arg | attributes imports: (self namesIn: arg value)]]
[(pairs lookup: 'poolDictionaries:') ifNotNil: [:arg | details imports: (self namesIn: arg value)]]
ifNotNil:
[:arg |
attributes imports: (arg children
details imports: (arg children
collect: [:each | BindingReference pathString: each pathString private: each isPrivate])].
(pairs lookup: 'classConstants:')
ifNotNil:
[:arg |
"We defer evaluating the brace array expression until needed, as mostly it is not"
attributes classConstants: arg formattedCode].
details classConstants: arg formattedCode].
(pairs lookup: 'classInstanceVariableNames:')
ifNotNil: [:arg | attributes classInstanceVariableNames: (self namesIn: arg value)].
(pairs lookup: 'category:') ifNotNil: [:arg | attributes category: arg value asSymbol]!
ifNotNil: [:arg | details classInstanceVariableNames: (self namesIn: arg value)].
(pairs lookup: 'category:') ifNotNil: [:arg | details category: arg value]!

getClassAttributes
^self attributes!
getClassDetails
^self details!

hash
^definition hash!
^self definition hash!

imports
^self attributes imports!
^self details imports!

instanceVariableNames
^self attributes instanceVariableNames!
^self details instanceVariableNames!

isValidMessageName: aMessageNode
^##(#(
Expand Down Expand Up @@ -139,48 +144,49 @@ namesIn: aString
^aString subStrings!

parseDefinitionError
classReference := #{Unknown}.
attributes := ClassAttributes new
details := ClassDetails new
className: #Unknown;
yourself!

primitiveExecute
#rbFix. "rbDmm changed "

^self definingSuperclass compilerClass evaluate: definition.




!

printOn: aStream
aStream
nextPutAll: definition;
nextPut: $!!!
^(self definingSuperclass compilerClass evaluate: self definition)
ifNotNil:
[:newClass |
details isNonInstantiable ifTrue: [newClass isNonInstantiable: true].
details guid ifNotNil: [:guid | newClass guid: guid].
details comment ifNotNil: [:comment | newClass comment: comment].
details package ifNotNil: [:package | newClass owningPackage: package].
newClass]!

printOn: aStream
| classDetails |
classDetails := self details.
(classDetails sourceFilerClass on: aStream) fileOutDefinitionOfClass: classDetails!

sourceFilerClass
^Object sourceFilerClass!

superclassName
^self attributes superclassName! !
^self details superclassName! !
!Refactory.Browser.AddClassChange categoriesForMethods!
=!comparing!public! !
areSubclassCreationMessageArgumentsValid:!private!testing! !
asUndoOperation!converting!public! !
attributes!accessing!public! !
category!accessing!public! !
categoryNames!accessing!public! !
changeClassName!accessing!public! !
changeString!printing!public! !
classConstants!accessing!public! !
classReference!accessing!public! !
classReference:!accessing!public! !
classVariableNames!accessing!public! !
definingSuperclass!accessing!private! !
definition!accessing!private! !
definition!accessing!public! !
definition:!initializing!public! !
details!accessing!public! !
details:!initializing!public! !
fillOutDefinition!helpers!private! !
fillOutDefinitionArguments:!helpers!private! !
getClassAttributes!printing!private! !
getClassDetails!printing!private! !
hash!comparing!public! !
imports!accessing!public! !
instanceVariableNames!accessing!public! !
Expand All @@ -197,8 +203,12 @@ superclassName!accessing!public! !
!Refactory.Browser.AddClassChange class methodsFor!

definition: aString
^self new definition: aString! !
^self new definition: aString!

details: aClassDetails
^self new details: aClassDetails! !
!Refactory.Browser.AddClassChange class categoriesForMethods!
definition:!instance creation!public! !
details:!instance creation!public! !
!

Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,9 @@ changeString
changeSymbol
^#addClassConstant:!

mutateAttributes: aClassAttributes
aClassAttributes
classConstants: (aClassAttributes classConstants asDictionary
mutateClassDetails: aClassDetails
aClassDetails
classConstants: (aClassDetails classConstants asDictionary
removeKey: variable key ifAbsent: nil;
add: variable;
yourself) associations
Expand All @@ -34,7 +34,7 @@ primitiveExecute
asUndoOperation!converting!public! !
changeString!printing!public! !
changeSymbol!constants!private! !
mutateAttributes:!helpers!private! !
mutateClassDetails:!helpers!private! !
primitiveExecute!applying!private! !
!

Loading

0 comments on commit d2b8d98

Please sign in to comment.