Skip to content

Commit

Permalink
ensure the number of images deleted will be visible in the notification
Browse files Browse the repository at this point in the history
fixes #594
  • Loading branch information
demarey committed Mar 1, 2023
1 parent 878d4f3 commit 4a48ae9
Show file tree
Hide file tree
Showing 5 changed files with 50 additions and 8 deletions.
4 changes: 2 additions & 2 deletions src/PharoLauncher-Core/PhLDeleteImageCommand.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -21,13 +21,13 @@ PhLDeleteImageCommand >> canBeExecuted [
^ self imagesPresenter selectedImages notEmpty
]

{ #category : #accessing }
{ #category : #executing }
PhLDeleteImageCommand >> execute [
| images imageNames confirmMessage answer |

images := self imagesPresenter selectedImages.
imageNames := images collect: #name.
confirmMessage := 'Are you sure you want to delete ', (imageNames joinUsing: ', ' last: ' and ').
confirmMessage := 'Are you sure you want to delete {1} images: {2}' format: {images size . (imageNames joinUsing: ', ' last: ' and ')}.
answer := self imagesPresenter newConfirmation
parentWindow: self context window;
message: (confirmMessage withNoLineLongerThan: 60) , '?';
Expand Down
5 changes: 5 additions & 0 deletions src/PharoLauncher-Spec2/PhLImagesPresenter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -376,6 +376,11 @@ PhLImagesPresenter >> selectImageAt: anIndex [
imageTable selectIndex: anIndex
]

{ #category : #'api - selection' }
PhLImagesPresenter >> selectImagesAt: aLisOfIndexes [
imageTable selectIndexes: aLisOfIndexes
]

{ #category : #'api - selection' }
PhLImagesPresenter >> selectedImages [
^ imageTable selectedItems
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ Class {
#category : #'PharoLauncher-Tests-Commands'
}

{ #category : #'as yet unclassified' }
{ #category : #helper }
PhLDeleteImageCommandTest >> createMoreImagesAndEnableSorting [

presenter createImageNamed: 'Zoo'.
Expand Down Expand Up @@ -81,3 +81,26 @@ PhLDeleteImageCommandTest >> testImagesPresenterIsRefreshedWhenImageDeleted [
assertEmpty: images;
assert: (presenter imageLabel beginsWith: 'No image selected')
]

{ #category : #tests }
PhLDeleteImageCommandTest >> testWarningMessageWhenDeletingManyImages [
| command images |
command := PhLDeleteImageCommand new.
command context: presenter.
presenter
createImageNamed: 'Foo';
createImageNamed: 'Bar';
createImageNamed: 'baz';
refresh;
selectImagesAt: #(1 3).

command execute.

images := command imagesPresenter imageNames.
self
assertCollection: images
hasSameElements: #('Bar' 'TestImage').
self
assert: presenter request message
equals: 'Are you sure you want to delete 2 images: baz and Foo?'
]
10 changes: 9 additions & 1 deletion src/PharoLauncher-Tests-Commands/PhLTestConfirmation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,9 @@ Mock for a user confirmation interaction
Class {
#name : #PhLTestConfirmation,
#superclass : #Object,
#instVars : [
'message'
],
#category : #'PharoLauncher-Tests-Commands'
}

Expand All @@ -17,9 +20,14 @@ PhLTestConfirmation >> inform [
self noop
]

{ #category : #accessing }
PhLTestConfirmation >> message [
^ message
]

{ #category : #accessing }
PhLTestConfirmation >> message: aString [
self noop
message := aString
]

{ #category : #private }
Expand Down
14 changes: 10 additions & 4 deletions src/PharoLauncher-Tests-Commands/PhLTestImagesPresenter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -44,12 +44,12 @@ PhLTestImagesPresenter >> hasSingleImageSelected [
^ super hasSingleImageSelected or: [ selection notNil ]
]

{ #category : #acccessing }
{ #category : #accessing }
PhLTestImagesPresenter >> imageLabel [
^ descriptionPanel imageLabel label
]

{ #category : #acccessing }
{ #category : #accessing }
PhLTestImagesPresenter >> imageNames [
^ imageTable items collect: #name
]
Expand All @@ -70,14 +70,14 @@ PhLTestImagesPresenter >> initialize [
request := PhLTestRequest new.
]

{ #category : #acccessing }
{ #category : #accessing }
PhLTestImagesPresenter >> launchConfigurations [
^ launchConfigurationList listItems allButFirst
]

{ #category : #'user interaction' }
PhLTestImagesPresenter >> newConfirmation [
^ PhLTestConfirmation new
^ request := PhLTestConfirmation new
]

{ #category : #'user interaction' }
Expand All @@ -103,6 +103,12 @@ PhLTestImagesPresenter >> refreshLaunchConfigurationList [
launchConfigurationList ifNotNil: [ super refreshLaunchConfigurationList ]
]

{ #category : #accessing }
PhLTestImagesPresenter >> request [

^ request
]

{ #category : #configuring }
PhLTestImagesPresenter >> requestAnswer: answer [
request answer: answer
Expand Down

0 comments on commit 4a48ae9

Please sign in to comment.