Skip to content

Commit

Permalink
Pass on comments
Browse files Browse the repository at this point in the history
  • Loading branch information
guillep committed Nov 13, 2018
1 parent 7ab0ef7 commit ebb4382
Show file tree
Hide file tree
Showing 5 changed files with 115 additions and 50 deletions.
60 changes: 47 additions & 13 deletions src/System-OSEnvironments/OSEnvironment.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -110,46 +110,74 @@ OSEnvironment >> associationsDo: aBlock [

{ #category : #accessing }
OSEnvironment >> at: aKey [
"Gets the value of an environment variable called `aKey`
It is the system reponsibility to manage the encoding."
"Gets the value of an environment variable called `aKey`.
Throws a KeyNotFound exception if not found.
It is the system reponsibility to manage the encodings of the argument and return values.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ self at: aKey ifAbsent: [ KeyNotFound signalFor: aKey ]
]

{ #category : #accessing }
OSEnvironment >> at: aKey ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
Execute aBlock if absent.
It is the system reponsibility to manage the encoding.
It is the system reponsibility to manage the encodings of the argument and return values.
Rationale: A common denominator for all platforms providing an already decoded string, because windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

self subclassResponsibility
]

{ #category : #accessing }
OSEnvironment >> at: key ifAbsentPut: aBlock [
"Return the value at the given key.
If key is not included in the receiver store the result
of evaluating aBlock as new value."
OSEnvironment >> at: aKey ifAbsentPut: aBlock [
"Gets the value of an environment variable called `aKey`.
If absent, insert the value given by aBlock.
It is the system reponsibility to manage the encodings of the argument and return values.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ self at: key ifAbsent: [ self at: key put: aBlock value ]
^ self at: aKey ifAbsent: [ self at: aKey put: aBlock value ]
]

{ #category : #accessing }
OSEnvironment >> at: aKey ifPresent: aBlock [
"Gets the value of an environment variable called `aKey` and invoke aBlock with it.
Return nil if absent.
It is the system reponsibility to manage the encodings of the argument and return values.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ aBlock value: (self at: aKey ifAbsent: [ ^ nil ])
]

{ #category : #accessing }
OSEnvironment >> at: key ifPresent: oneArgBlock ifAbsent: absentBlock [
"Lookup the given key in the receiver. If it is present, answer the value of evaluating the oneArgBlock with the value associated with the key, otherwise answer the value of absentBlock."
OSEnvironment >> at: aKey ifPresent: presentBlock ifAbsent: absentBlock [
"Gets the value of an environment variable called `aKey`.
Call presentBlock with it if present.
Execute absentBlock if absent.
It is the system reponsibility to manage the encodings of the argument and return values.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

self at: key ifPresent: [ :v | ^oneArgBlock cull: v ].
self at: aKey ifPresent: [ :v | ^ presentBlock cull: v ].
^absentBlock value
]

{ #category : #accessing }
OSEnvironment >> at: aKey put: aValue [
"Sets the value of an environment variable called `aKey` to `aValue`.
It is the system reponsibility to manage the encodings of both arguments.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ self subclassResponsibility
]

Expand Down Expand Up @@ -211,7 +239,13 @@ OSEnvironment >> platform [
]

{ #category : #accessing }
OSEnvironment >> removeKey: key [
OSEnvironment >> removeKey: aKey [
"Removes the entry `aKey` from the environment variables.
It is the system reponsibility to manage the encoding of the argument.
This is the common denominator API for all platforms.
Rationale: Windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ self subclassResponsibility
]

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,17 +21,12 @@ PlatformIndependentEnvironment class >> isDefaultFor: aPlatform [

{ #category : #accessing }
PlatformIndependentEnvironment >> at: aKey ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
Execute aBlock if absent.
It is the system reponsibility to manage the encoding.
Rationale: A common denominator for all platforms providing an already decoded string, because windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

^ nil
]

{ #category : #accessing }
PlatformIndependentEnvironment >> at: aKey put: aValue [

"Do nothing"
]

Expand All @@ -42,6 +37,5 @@ PlatformIndependentEnvironment >> keysAndValuesDo: aBlock [

{ #category : #accessing }
PlatformIndependentEnvironment >> removeKey: key [

"Do nothing"
]
56 changes: 44 additions & 12 deletions src/System-OSEnvironments/UnixEnvironment.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,11 @@ UnixEnvironment class >> isDefaultFor: aPlatform [
UnixEnvironment >> at: aKey encoding: anEncoding ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
Execute aBlock if absent.
It is the system reponsibility to manage the encoding."
Use `anEncoding` to encode the arguments and return values.
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

| result |
result := self
rawAt: (aKey encodeWith: anEncoding)
Expand All @@ -28,20 +32,27 @@ UnixEnvironment >> at: aKey encoding: anEncoding ifAbsent: aBlock [

{ #category : #accessing }
UnixEnvironment >> at: aKey ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
Execute aBlock if absent.
It is the system reponsibility to manage the encoding."
"See super>>at:ifAbsent:.
Uses a single encoding determined dinamically"

^ self at: aKey encoding: self defaultEncoding ifAbsent: aBlock
]

{ #category : #accessing }
UnixEnvironment >> at: aKey put: aValue [
"See super>>at:put:.
Uses a single encoding determined dinamically"

^ self at: aKey put: aValue encoding: self defaultEncoding
]

{ #category : #accessing }
UnixEnvironment >> at: aKey put: aValue encoding: anEncoding [
"Sets the value of an environment variable called `aKey` to `aValue`.
Use `anEncoding` to encode both arguments.
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

^ self
rawAt: (aKey encodeWith: anEncoding)
Expand Down Expand Up @@ -105,36 +116,57 @@ UnixEnvironment >> keysAndValuesDo: aBlock [
]

{ #category : #accessing }
UnixEnvironment >> rawAt: aKey ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
UnixEnvironment >> rawAt: anEncodedKey ifAbsent: aBlock [
"Gets the value of an environment variable called `anEncodedKey` that is already encoded (i.e., it is a byte array).
Execute aBlock if absent.
It is the system reponsibility to manage the encoding."
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

| rawValue |
rawValue := self basicGetEnvRaw: aKey asString.
rawValue := self basicGetEnvRaw: anEncodedKey asString.
^ rawValue
ifNil: [ aBlock value ]
ifNotNil: [ rawValue asByteArray ].
]

{ #category : #accessing }
UnixEnvironment >> rawAt: anEncodedName put: bytes [
UnixEnvironment >> rawAt: anEncodedKey put: someBytes [
"Sets the value of an environment variable called `anEncodedKey` to `someBytes`.
Both arguments should be already encoded (i.e., they are byte arrays).
^ self setEnv: anEncodedName asString value: bytes asString
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

^ self setEnv: anEncodedKey asString value: someBytes asString
]

{ #category : #accessing }
UnixEnvironment >> rawRemoveKey: key [
^ self unsetEnv: key asString
UnixEnvironment >> rawRemoveKey: anEncodedKey [
"Removes an environment variable called `anEncodedKey` that is already encoded (i.e., it is a byte array).
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

^ self unsetEnv: anEncodedKey asString
]

{ #category : #accessing }
UnixEnvironment >> removeKey: key [
"See super>>removeKey:.
Uses a single encoding determined dinamically"

^ self removeKey: key encoded: self defaultEncoding
]

{ #category : #accessing }
UnixEnvironment >> removeKey: key encoded: anEncoding [
"Removes the entry `aKey` from the environment variables.
Use `anEncoding` to encode the arguments.
This is a *nix specific API.
Rationale: In *nix systems (compared to windows systems) environment variables are stored as raw bytes and can be encoded in different forms."

^ self rawRemoveKey: (key encodeWith: anEncoding)
]

Expand Down
35 changes: 23 additions & 12 deletions src/System-OSEnvironments/Win32Environment.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,24 +14,21 @@ Win32Environment class >> isDefaultFor: aPlatform [

{ #category : #accessing }
Win32Environment >> at: aKey ifAbsent: aBlock [
"Gets the value of an environment variable called `aKey`.
Execute aBlock if absent.
It is the system reponsibility to manage the encoding.
Rationale: A common denominator for all platforms providing an already decoded string, because windows does not (compared to *nix systems) provide a encoded byte representation of the value. Windows has instead its own wide string representation."

"The primitive on Windows currently uses the ascii version of the Windows API.
In such chase try to get value of the environment variable using FFI."
^ self getEnvViaFFI: aKey bufferSize: 500 ifAbsent: aBlock

^ self getEnvVariable: aKey bufferSize: 500 ifAbsent: aBlock
]

{ #category : #accessing }
Win32Environment >> at: aKey put: aValue [
"The primitive on Windows currently uses the ascii version of the Windows API.
In such chase try to set the value of the environment variable using FFI."

| w32Key w32Value return |
w32Key := aKey asWin32WideString.
w32Value := aValue asWin32WideString.
return := OSPlatform current setEnvironmentVariable: w32Key value: w32Value.
return := self setEnvironmentVariable: w32Key value: w32Value.

"From MSDN: If the function fails, the return value is zero."
return = 0 ifTrue: [
Expand All @@ -44,7 +41,7 @@ Win32Environment >> environmentStrings [
]

{ #category : #private }
Win32Environment >> getEnvViaFFI: aVariableName bufferSize: aSize ifAbsent: aBlock [
Win32Environment >> getEnvVariable: aVariableName bufferSize: aSize ifAbsent: aBlock [
| name buffer return |

name := aVariableName asWin32WideString.
Expand All @@ -59,7 +56,7 @@ Win32Environment >> getEnvViaFFI: aVariableName bufferSize: aSize ifAbsent: aBlo

"From MSDN: If lpBuffer is not large enough to hold the data, the return value is the buffer size, in characters,
required to hold the string and its terminating null character and the contents of lpBuffer are undefined."
return > aSize ifTrue: [ ^ self getEnvViaFFI: aVariableName bufferSize: return ifAbsent: aBlock ].
return > aSize ifTrue: [ ^ self getEnvVariable: aVariableName bufferSize: return ifAbsent: aBlock ].

^ buffer asString
]
Expand All @@ -81,13 +78,27 @@ Win32Environment >> keysAndValuesDo: aBlock [
environmentStrings := environmentStrings + nextString size + 1 ] repeat
]

{ #category : #private }
Win32Environment >> removeEnvironmentVariable: nameString [

^ self ffiCall: #( int SetEnvironmentVariableW ( Win32WideString nameString, 0 ) )
]

{ #category : #accessing }
Win32Environment >> removeKey: aKey [

"The primitive on Windows currently uses the ascii version of the Windows API.
In such chase try to get value of the environment variable using FFI."

| return |
return := OSPlatform current removeEnvironmentVariable: aKey asWin32WideString.
return := self removeEnvironmentVariable: aKey asWin32WideString.

"From MSDN: If the function fails, the return value is zero."
return = 0 ifTrue: [
self error: 'An error occurred while removing environment variable ', aKey asString ].
]

{ #category : #private }
Win32Environment >> setEnvironmentVariable: nameString value: valueString [

^ self ffiCall: #( int SetEnvironmentVariableW ( Win32WideString nameString, Win32WideString valueString ) )
]
6 changes: 0 additions & 6 deletions src/System-Platforms/WinPlatform.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -109,12 +109,6 @@ WinPlatform >> multiByteToWideCharacterCodepage: codepage flags: flags input: in
^self ffiCall: #(int MultiByteToWideChar(uint codepage, ulong flags, String input, int inputLen, Win32WideString output, int outputLen ))
]

{ #category : #'environment-variables' }
WinPlatform >> removeEnvironmentVariable: nameString [

^ self ffiCall: #( int SetEnvironmentVariableW ( Win32WideString nameString, 0 ) )
]

{ #category : #'environment-variables' }
WinPlatform >> setEnvironmentVariable: nameString value: valueString [

Expand Down

0 comments on commit ebb4382

Please sign in to comment.