Skip to content

Commit

Permalink
Remove SycRemoveClassKeepingSubclassesCommand since we don't have any…
Browse files Browse the repository at this point in the history
… more need of a specific menu item for this.

The existing functionality is preserved by SycRemoveClassCommand using the SycRemoveKeepingSubclassesClassStrategy.
  • Loading branch information
gcorriga committed Jan 4, 2021
1 parent 3c5cc72 commit 4f1be94
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 98 deletions.
2 changes: 1 addition & 1 deletion src/Calypso-NavigationModel/ClyConstantQuery.class.st
Expand Up @@ -70,7 +70,7 @@ ClyConstantQuery >> buildResult: aQueryResult [

{ #category : #execution }
ClyConstantQuery >> checkEmptyResult [
^resultItems notEmpty
^resultItems isEmpty
]

{ #category : #execution }
Expand Down
18 changes: 0 additions & 18 deletions src/Calypso-SystemTools-Core/ClyBrowserMorph.extension.st
Expand Up @@ -64,24 +64,6 @@ ClyBrowserMorph >> confirmUnusedClasses: classes [
^noUsers
]

{ #category : #'*Calypso-SystemTools-Core' }
ClyBrowserMorph >> confirmUnusedClassesExceptInheritance: classes [

| refQuery noUsers answer users |

refQuery := ClyClassReferencesQuery toAny: classes from: self systemScope.
"we need to exclude both the class and instance side of the class"
noUsers := self confirmEmptySystemQuery: refQuery excluding: (classes flatCollect: [ :each | { each . each classSide } ]).

users := (classes flatCollect: [:each | each users]) copyWithoutAll: classes.
users ifNotEmpty: [
noUsers := false.
answer := UIManager default confirm: 'There are users of trait. Show them?'.
answer ifTrue: [ self spawnQueryBrowserOn: (ClyConstantQuery returning: users) ]].

^noUsers
]

{ #category : #'*Calypso-SystemTools-Core' }
ClyBrowserMorph >> confirmUnusedVariables: variables [

Expand Down
5 changes: 0 additions & 5 deletions src/Calypso-SystemTools-Core/ClySystemBrowserContext.class.st
Expand Up @@ -53,11 +53,6 @@ ClySystemBrowserContext >> confirmUnusedClasses: variables [
^tool confirmUnusedClasses: variables
]

{ #category : #'user requests' }
ClySystemBrowserContext >> confirmUnusedClassesExceptInheritance: variables [
^tool confirmUnusedClassesExceptInheritance: variables
]

{ #category : #'user requests' }
ClySystemBrowserContext >> confirmUnusedVariables: variables [
^tool confirmUnusedVariables: variables
Expand Down
14 changes: 13 additions & 1 deletion src/SystemCommands-ClassCommands/SycRemoveClassCommand.class.st
Expand Up @@ -13,7 +13,13 @@ Class {
{ #category : #execution }
SycRemoveClassCommand >> asRefactorings [

^{RBRemoveClassRefactoring classNames: (classes collect: [:each | each name])}
^self asRefactoringsOfClass: RBRemoveClassRefactoring
]

{ #category : #execution }
SycRemoveClassCommand >> asRefactoringsOfClass: aClass [

^{aClass classNames: (classes collect: [:each | each name])}
]

{ #category : #execution }
Expand Down Expand Up @@ -45,6 +51,12 @@ SycRemoveClassCommand >> execute [
removeStrategy execute: self.
]

{ #category : #execution }
SycRemoveClassCommand >> executeRefactoringsAs: aClass [

(self asRefactoringsOfClass: aClass) do: [ :each | each execute ]
]

{ #category : #testing }
SycRemoveClassCommand >> isComplexRefactoring [
^removeStrategy isComplexRefactoring
Expand Down

This file was deleted.

Expand Up @@ -12,9 +12,7 @@ SycRemoveKeepingSubclassesClassStrategy class >> canExecuteWithReferences: hasRe
{ #category : #execution }
SycRemoveKeepingSubclassesClassStrategy >> execute: aSycRemoveClassCommand [

(SycRemoveClassKeepingSubclassesCommand new)
classes: aSycRemoveClassCommand class;
executeRefactorings
aSycRemoveClassCommand executeRefactoringsAs: RBRemoveClassKeepingSubclassesRefactoring
]

{ #category : #testing }
Expand Down

0 comments on commit 4f1be94

Please sign in to comment.