Skip to content

Commit

Permalink
fixes #342 Cannot open anymore OS folder X.
Browse files Browse the repository at this point in the history
Also move to use a visitor instead of extension methods
  • Loading branch information
demarey committed Jul 8, 2019
1 parent 1a2b17f commit dab5151
Show file tree
Hide file tree
Showing 9 changed files with 79 additions and 62 deletions.
6 changes: 0 additions & 6 deletions src/PharoLauncher-Core/MacOSPlatform.extension.st

This file was deleted.

18 changes: 0 additions & 18 deletions src/PharoLauncher-Core/OSPlatform.extension.st

This file was deleted.

65 changes: 65 additions & 0 deletions src/PharoLauncher-Core/PhLFileBrowser.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
"
I'm a simple visitor in charge of opening an operating system browser on the provided path string.
"
Class {
#name : #PhLFileBrowser,
#superclass : #OSPlatformVisitor,
#instVars : [
'process',
'vmPath',
'launchInALoginShell',
'imageFile',
'usePharoSettings',
'path'
],
#category : #'PharoLauncher-Core-Model'
}

{ #category : #'instance creation' }
PhLFileBrowser class >> openOn: aFileReferenceOrPathString [

^ self new
path: aFileReferenceOrPathString;
open.
]

{ #category : #action }
PhLFileBrowser >> open [
self visit
]

{ #category : #accessing }
PhLFileBrowser >> path: aFileReferenceOrPathString [
"Opens an OS-specific file and directory browser on ==aFileReference==. If aFileReference is a file, opens the browser on its containing directory instead."
| ref |
aFileReferenceOrPathString isNil ifTrue: [ ^ nil ].
ref := aFileReferenceOrPathString asFileReference.
ref exists ifFalse: [ ^ nil ].

ref := ref isFile ifTrue: [ ref parent ] ifFalse: [ ref ].
(ref isNil or: [ ref exists not ])
ifTrue: [ ^ nil ].

path := ref fullName.
]

{ #category : #visiting }
PhLFileBrowser >> visitMacOS: aPlatform [
^ PhLProcessWrapper new
shellCommand;
addArgument: ('open "{1}"' format: {path});
runUnwatch
]

{ #category : #visiting }
PhLFileBrowser >> visitUnix: aPlatform [
^ PhLProcessWrapper new
shellCommand;
addArgument: ('xdg-open "{1}"' format: {path});
runUnwatch
]

{ #category : #visiting }
PhLFileBrowser >> visitWindows: aPlatform [
^ aPlatform privShellExplore: path
]
2 changes: 1 addition & 1 deletion src/PharoLauncher-Core/PhLImage.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -204,7 +204,7 @@ PhLImage >> setLocation: aFile [

{ #category : #printing }
PhLImage >> showNativeFolder [
OSPlatform current openFileBrowserOn: file
PhLFileBrowser openOn: file
]

{ #category : #accessing }
Expand Down
24 changes: 0 additions & 24 deletions src/PharoLauncher-Core/PhLProcessWrapper.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -17,15 +17,6 @@ Class {
#category : #'PharoLauncher-Core-Download'
}

{ #category : #'execution - public' }
PhLProcessWrapper class >> command: aCommand [
^ Smalltalk os isWindows
ifTrue: [ OSWSWinProcess new
shellCommand: aCommand;
run ]
ifFalse: [ OSProcess command: aCommand utf8Encoded asString ]
]

{ #category : #testing }
PhLProcessWrapper class >> isCommandAvailable: aCommand [
| process |
Expand All @@ -39,21 +30,6 @@ PhLProcessWrapper class >> isCommandAvailable: aCommand [
do: [ ^ false ]
]

{ #category : #'execution - public' }
PhLProcessWrapper class >> waitForLinuxCommand: aCommand timeout: aDuration [
| future externalProcess |

future := [externalProcess := self command: aCommand.
[externalProcess isComplete]
whileFalse: [(Delay forMilliseconds: 50) wait]. ] future.
[ future waitForCompletion: aDuration ]
on: TKTTimeoutException
do: [ :error |
externalProcess isComplete ifFalse:
[ externalProcess sigkill.
PhLProcessTimeOut signal ] ]
]

{ #category : #building }
PhLProcessWrapper >> addArgument: aString [
arguments add: aString
Expand Down
2 changes: 1 addition & 1 deletion src/PharoLauncher-Core/PhLVirtualMachine.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ PhLVirtualMachine >> removeFromSystem [

{ #category : #actions }
PhLVirtualMachine >> showInFolder [
OSPlatform current openFileBrowserOn: self vmStore / name
PhLFileBrowser openOn: self vmStore / name
]

{ #category : #updating }
Expand Down
6 changes: 0 additions & 6 deletions src/PharoLauncher-Core/UnixPlatform.extension.st

This file was deleted.

6 changes: 0 additions & 6 deletions src/PharoLauncher-Core/Win32Platform.extension.st
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
Extension { #name : #Win32Platform }

{ #category : #'*PharoLauncher-Core' }
Win32Platform >> privOpenFileBrowserOn: pathString [
self privShellExplore: pathString

]

{ #category : #'*PharoLauncher-Core' }
Win32Platform >> privShellExecute: lpOperation file: lpFile parameters: lpParameters directory: lpDirectory show: nShowCmd [

Expand Down
12 changes: 12 additions & 0 deletions src/PharoLauncher-Tests-Core/PhLFileBrowserTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
Class {
#name : #PhLFileBrowserTest,
#superclass : #TestCase,
#category : #'PharoLauncher-Tests-Core'
}

{ #category : #tests }
PhLFileBrowserTest >> testCanOpenAFileBrowserOnImageFolder [
| path |
path := Smalltalk image imageDirectory fullName.
PhLFileBrowser openOn: path.
]

0 comments on commit dab5151

Please sign in to comment.