diff --git a/src/FileSystem-Core/UnixResolver.class.st b/src/FileSystem-Core/UnixResolver.class.st index 54536910977..34b4f6ab09b 100644 --- a/src/FileSystem-Core/UnixResolver.class.st +++ b/src/FileSystem-Core/UnixResolver.class.st @@ -48,7 +48,9 @@ UnixResolver >> preferences [ { #category : #origins } UnixResolver >> temp [ - ^ '/tmp' asFileReference + +^self directoryFromEnvVariableNamed: 'TMPDIR' or: [ + '/tmp' asFileReference] ] { #category : #origins } diff --git a/src/FileSystem-Core/WindowsResolver.class.st b/src/FileSystem-Core/WindowsResolver.class.st index e83a0cc9fe5..0ee4a2ea0eb 100644 --- a/src/FileSystem-Core/WindowsResolver.class.st +++ b/src/FileSystem-Core/WindowsResolver.class.st @@ -32,5 +32,6 @@ WindowsResolver >> preferences [ { #category : #origins } WindowsResolver >> temp [ - ^ self directoryFromEnvVariableNamed: 'TEMP' or: [ FileLocator C / 'windows' / 'temp' ] + + ^ self resolveString: Smalltalk os getTempPath ] diff --git a/src/FileSystem-Tests-Core/UnixResolverTest.class.st b/src/FileSystem-Tests-Core/UnixResolverTest.class.st index d08952cbe5b..5c695d94821 100644 --- a/src/FileSystem-Tests-Core/UnixResolverTest.class.st +++ b/src/FileSystem-Tests-Core/UnixResolverTest.class.st @@ -13,6 +13,20 @@ UnixResolverTest >> createResolver [ ^ UnixResolver new ] +{ #category : #running } +UnixResolverTest >> testGetTempFromTMPDIR [ + + | expected | + OSPlatform current isUnix ifFalse: [ ^ self skip ]. + + expected := '/tmp/foo'. + OSEnvironment current setEnv: 'TMPDIR' value: expected during: [ + | actual | + actual := self createResolver temp. + self assert: actual fullName equals: expected ] + +] + { #category : #tests } UnixResolverTest >> testXdgParseUserDirLineDocuments [ "Ensure that a path of the form '$HOME/Documents' answers the expected value. diff --git a/src/FileSystem-Tests-Core/WindowsResolverTest.class.st b/src/FileSystem-Tests-Core/WindowsResolverTest.class.st new file mode 100644 index 00000000000..b5ff31c9bd1 --- /dev/null +++ b/src/FileSystem-Tests-Core/WindowsResolverTest.class.st @@ -0,0 +1,22 @@ +" +A WindowsResolverTest is a test class for testing the behavior of WindowsResolver +" +Class { + #name : #WindowsResolverTest, + #superclass : #TestCase, + #category : #'FileSystem-Tests-Core-Resolver' +} + +{ #category : #tests } +WindowsResolverTest >> testResolveTempPathFromTMP [ + + | expected | + OSPlatform current isWindows ifFalse: [ ^ self skip ]. + + expected := 'X:\Temp'. + + OSEnvironment current setEnv: 'TMP' value: expected during: [ + | actual | + actual := WindowsResolver new temp. + self assert: actual fullName equals: expected ] +] diff --git a/src/System-OSEnvironments-Tests/OSEnvironmentTest.class.st b/src/System-OSEnvironments-Tests/OSEnvironmentTest.class.st index 657579e9b23..80d557d42a7 100644 --- a/src/System-OSEnvironments-Tests/OSEnvironmentTest.class.st +++ b/src/System-OSEnvironments-Tests/OSEnvironmentTest.class.st @@ -7,11 +7,24 @@ Class { #category : #'System-OSEnvironments-Tests' } +{ #category : #helper } +OSEnvironmentTest >> envNameForTest [ + + ^ 'PHAROTEST' +] + { #category : #helper } OSEnvironmentTest >> instance [ ^ Smalltalk os environment ] +{ #category : #running } +OSEnvironmentTest >> tearDown [ + + self instance removeKey: self envNameForTest. + super tearDown +] + { #category : #tests } OSEnvironmentTest >> testAsDictionary [ self assert: self instance asDictionary isDictionary @@ -75,6 +88,40 @@ OSEnvironmentTest >> testKeys [ self assert: (env includesKey: keys anyOne) ] +{ #category : #tests } +OSEnvironmentTest >> testSettingEnvValueDuringChangesValueInDuringBlock [ + + | envName expected | + envName := self envNameForTest. + self instance setEnv: envName value: 'Before'. + expected := 'After'. + self instance setEnv: envName value: expected during: [ + | actual | + actual := self instance at: envName. + self assert: actual equals: expected ] +] + +{ #category : #tests } +OSEnvironmentTest >> testSettingEnvValueDuringRevertsValueAfterDuringBlock [ + + | actual envName expected | + envName := self envNameForTest. + self instance setEnv: envName value: 'Before'. + expected := 'After'. + self instance setEnv: envName value: expected during: [ ]. + actual := self instance at: envName. + self assert: actual equals: expected +] + +{ #category : #tests } +OSEnvironmentTest >> testSettingNewEnvValueDuringRemovesItAfterDuringBlock [ + + | envName | + envName := self envNameForTest. + self instance setEnv: envName value: 'During' during: [ ]. + self deny: (self instance includesKey: envName) +] + { #category : #tests } OSEnvironmentTest >> testValues [ | env values | diff --git a/src/System-OSEnvironments/OSEnvironment.class.st b/src/System-OSEnvironments/OSEnvironment.class.st index 75cee9d5dd2..583ba99b218 100644 --- a/src/System-OSEnvironments/OSEnvironment.class.st +++ b/src/System-OSEnvironments/OSEnvironment.class.st @@ -250,6 +250,19 @@ OSEnvironment >> setEnv: nameString value: valueString [ ^ self subclassResponsibility ] +{ #category : #accessing } +OSEnvironment >> setEnv: nameString value: valueString during: aBlock [ + + | oldValue | + oldValue := self at: nameString ifAbsent: [ nil ]. + [ + self setEnv: nameString value: valueString. + aBlock value ] ensure: [ + oldValue + ifNil: [ self removeKey: nameString ] + ifNotNil: [ self setEnv: nameString value: valueString ] ] +] + { #category : #accessing } OSEnvironment >> unsetEnv: string [ "This method calls the the platform specific unset environment routine" diff --git a/src/System-Platforms-Tests/Win32EnvironmentTest.class.st b/src/System-Platforms-Tests/Win32EnvironmentTest.class.st index 405f132611d..e3bfd16769a 100644 --- a/src/System-Platforms-Tests/Win32EnvironmentTest.class.st +++ b/src/System-Platforms-Tests/Win32EnvironmentTest.class.st @@ -1,7 +1,7 @@ Class { #name : #Win32EnvironmentTest, #superclass : #TestCase, - #category : #'System-Platforms-Tests-Win32' + #category : #'System-Platforms-Tests-Windows' } { #category : #tests } diff --git a/src/System-Platforms-Tests/Win32WideStringTest.class.st b/src/System-Platforms-Tests/Win32WideStringTest.class.st index f3a13e544f7..1b60e3111a4 100644 --- a/src/System-Platforms-Tests/Win32WideStringTest.class.st +++ b/src/System-Platforms-Tests/Win32WideStringTest.class.st @@ -1,7 +1,7 @@ Class { #name : #Win32WideStringTest, #superclass : #TestCase, - #category : #'System-Platforms-Tests-Win32' + #category : #'System-Platforms-Tests-Windows' } { #category : #tests } diff --git a/src/System-Platforms-Tests/WinPlatformTest.class.st b/src/System-Platforms-Tests/WinPlatformTest.class.st new file mode 100644 index 00000000000..8138add75eb --- /dev/null +++ b/src/System-Platforms-Tests/WinPlatformTest.class.st @@ -0,0 +1,21 @@ +Class { + #name : #WinPlatformTest, + #superclass : #TestCase, + #category : #'System-Platforms-Tests-Windows' +} + +{ #category : #tests } +WinPlatformTest >> testGetTempPathFromTMP [ + + | value | + OSPlatform current isWindows ifFalse: [ ^ self skip ]. + + value := OSEnvironment current at: 'TMP' ifAbsent: [ nil ]. + [ + | actual expected | + expected := 'X:\Temp\'. + OSEnvironment current at: 'TMP' put: expected. + actual := OSPlatform current getTempPath. + self assert: actual equals: expected ] ensure: [ + value ifNotNil: [ OSEnvironment current at: 'TMP' put: value ] ] +] diff --git a/src/System-Platforms/WinPlatform.class.st b/src/System-Platforms/WinPlatform.class.st index 582af496407..4e342dc6274 100644 --- a/src/System-Platforms/WinPlatform.class.st +++ b/src/System-Platforms/WinPlatform.class.st @@ -71,6 +71,23 @@ WinPlatform >> getErrorMessage: anInteger [ ^ buffer asString ] +{ #category : #'file paths' } +WinPlatform >> getTempPath [ + + | buffer length | + length := self defaultMaximumPathLength. + buffer := (String new: length) asWin32WideString. + self getTempPath: length buffer: buffer. + ^buffer asString +] + +{ #category : #'file paths' } +WinPlatform >> getTempPath: bufferLength buffer: buffer [ + + self ffiCall: #(long GetTempPath2W(long bufferLength, + void* buffer)) +] + { #category : #testing } WinPlatform >> isWindows [ ^ true