Skip to content

Commit

Permalink
open a presenter to fix pharo version
Browse files Browse the repository at this point in the history
if absent when image launched
  • Loading branch information
demarey committed Jan 9, 2024
1 parent 9aa544b commit 4c9347e
Show file tree
Hide file tree
Showing 7 changed files with 102 additions and 6 deletions.
6 changes: 6 additions & 0 deletions src/PharoLauncher-Core/PhLImageVersionFileNotFound.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,12 @@ PhLImageVersionFileNotFound >> longDescription [
Please, contact us at http://pharo.org/community'
]

{ #category : #accessing }
PhLImageVersionFileNotFound >> messageText [

^ self longDescription
]

{ #category : #accessing }
PhLImageVersionFileNotFound >> name [
^ 'Image version file ', PhLImage versionFileName , ' not found!'
Expand Down
7 changes: 3 additions & 4 deletions src/PharoLauncher-Core/PhLLaunchConfiguration.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ PhLLaunchConfiguration >> commandString [

{ #category : #querying }
PhLLaunchConfiguration >> defaultVm [
self image pharoVersion.
self image ensurePharoVersion.
^ self image vmManager virtualMachine
]

Expand Down Expand Up @@ -128,8 +128,7 @@ PhLLaunchConfiguration >> initializeWithImage: anImage [
image := anImage.
name := 'new configuration...'.
usePharoSettings := true.
imageArguments := anImage defaultArguments.
image ensurePharoVersion
imageArguments := anImage defaultArguments
]

{ #category : #testing }
Expand Down Expand Up @@ -169,7 +168,7 @@ PhLLaunchConfiguration >> printOn: aStream [
{ #category : #configuring }
PhLLaunchConfiguration >> useSettings: aBoolean [
"Cannot skip Pharo settings before Pharo 3.0"
self image pharoVersion asInteger < 30 ifTrue: [ ^ self ].
self image ensurePharoVersion asInteger < 30 ifTrue: [ ^ self ].

usePharoSettings := aBoolean.
]
Expand Down
3 changes: 2 additions & 1 deletion src/PharoLauncher-Core/PhLLaunchImageCommand.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,8 @@ PhLLaunchImageCommand >> launchConfigurationOfImage: aPhLImage [
{ #category : #executing }
PhLLaunchImageCommand >> launchImage: aPhLImage [
| process launchConfig |


self imagesPresenter ensurePharoVersion.
[ launchConfig := self launchConfigurationOfImage: aPhLImage.
launchConfig useSettings: useSettings.
process := aPhLImage launchWithConfiguration: launchConfig ]
Expand Down
14 changes: 14 additions & 0 deletions src/PharoLauncher-Spec2/PhLImagesPresenter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -233,6 +233,20 @@ PhLImagesPresenter >> ensure: aBoolean [
ifFalse: [ PhLCommandError signal ]
]

{ #category : #computing }
PhLImagesPresenter >> ensurePharoVersion [
| image |
image := self singleImage.
[ image ensurePharoVersion ]
on: PhLImageVersionFileNotFound
do: [ :error | | presenter |
presenter := PhLPharoVersionChooserPresenter new.
presenter openModal.
presenter version ifNil: [ error pass ].
image versionFile
writeStreamDo: [ :stream | stream nextPutAll: presenter version ] ]
]

{ #category : #private }
PhLImagesPresenter >> filter: regexMatcher [

Expand Down
63 changes: 63 additions & 0 deletions src/PharoLauncher-Spec2/PhLPharoVersionChooserPresenter.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,63 @@
"
I'm a simple presenter to fix the version of a Pharo image when no version file exists.
"
Class {
#name : #PhLPharoVersionChooserPresenter,
#superclass : #SpPresenterWithModel,
#traits : 'TPhLInteractionTrait',
#classTraits : 'TPhLInteractionTrait classTrait',
#instVars : [
'versionTable'
],
#category : #'PharoLauncher-Spec2'
}

{ #category : #examples }
PhLPharoVersionChooserPresenter class >> example [

^ self new
openDialog;
yourself
]

{ #category : #layout }
PhLPharoVersionChooserPresenter >> defaultLayout [
^ SpBoxLayout newHorizontal
add: versionTable;
yourself
]

{ #category : #initialization }
PhLPharoVersionChooserPresenter >> initializePresenters [
versionTable := self newTable
addColumn: ((SpStringTableColumn title: 'Pharo version' evaluated: #key) width: 100; yourself);
addColumn: ((SpStringTableColumn
title: 'version string'
evaluated: #value) width: 60; yourself);
showColumnHeaders;
items: self pharoVersions;
yourself
]

{ #category : #initialization }
PhLPharoVersionChooserPresenter >> initializeWindow: aWindowPresenter [

aWindowPresenter
title: 'Choose the Pharo version of the image:';
initialExtent: 300@300;
centered
]

{ #category : #accessing }
PhLPharoVersionChooserPresenter >> pharoVersions [
| maxPharoVersion versions |
maxPharoVersion := 12.
versions := (#(1.2 1.3 1.4) copyWithAll: (2 to: maxPharoVersion)) reversed.

^ versions collect: [ :v | 'Pharo ', v asString -> (v * 10) asInteger asString]
]

{ #category : #versions }
PhLPharoVersionChooserPresenter >> version [
^ versionTable selectedItem value
]
Original file line number Diff line number Diff line change
Expand Up @@ -128,6 +128,19 @@ PhLLaunchImageCommandTest >> testExecutingImageWithScriptShouldSetFlagToShouldNo
self deny: image shouldRunInitializationScript.
]

{ #category : #tests }
PhLLaunchImageCommandTest >> testLaunchImageShouldRaiseExceptionWhenNoPharoVersionFile [

image versionFile ensureDelete.
presenter
unselectAll;
selection: { image }.

self
should: [ image launch ]
raise: PhLImageVersionFileNotFound
]

{ #category : #tests }
PhLLaunchImageCommandTest >> testRecreateAnImageWithoutOpeningItShouldStillExecuteScript [

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ Class {

{ #category : #running }
PhLImagesPresenterTest >> tearDown [
presenter window ifNotNil: #close.
presenter window ifNotNil: [ :window | window close].
super tearDown
]

Expand Down

0 comments on commit 4c9347e

Please sign in to comment.