Skip to content

Commit

Permalink
Adding a primitive to wait for data on a stream.
Browse files Browse the repository at this point in the history
This is useful when using redirect streams in pipes and command-line tools.
  • Loading branch information
tesonep committed Aug 11, 2020
1 parent 5092e61 commit 1b67e2e
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 1 deletion.
38 changes: 37 additions & 1 deletion src/Files/AbstractBinaryFileStream.class.st
Expand Up @@ -37,7 +37,9 @@ Class {
#instVars : [
'file',
'handle',
'forWrite'
'forWrite',
'semaphore',
'semaphoreIndex'
],
#category : #'Files-Streams'
}
Expand Down Expand Up @@ -255,6 +257,19 @@ AbstractBinaryFileStream >> readInto: readBuffer startingAt: startIndex count: c
^ File read: handle into: readBuffer startingAt: startIndex count: count
]

{ #category : #reading }
AbstractBinaryFileStream >> releaseSemaphores [

"To wait for data to arrival in an stream, it is required to keep a semaphore and this one should be registered in the VM. As this is a constrained resource, the user of wait data should relelease the semaphore when it is not used anymore"

semaphore ifNotNil: [
Smalltalk unregisterExternalObject: semaphore].

semaphoreIndex := nil.
semaphore := nil.

]

{ #category : #initialization }
AbstractBinaryFileStream >> reset [
self position: 0
Expand Down Expand Up @@ -312,3 +327,24 @@ AbstractBinaryFileStream >> upToEnd [
[ (next := self next) isNil ] whileFalse: [
newStream nextPut: next ] ]
]

{ #category : #reading }
AbstractBinaryFileStream >> waitForData [

"Waits for data on a semaphore.
This message is useful for using on streams and pipes.
This message uses a primitive that needs to be available to work.
Also, it uses an external semaphore, so after ending its use please send the message #releaseSemaphores
Ex: [[Stdio stdin atEnd]
whileFalse: [Stdio stdin waitForData.
(Stdio stdin next: 100) printString traceCr]] fork.
"

semaphore ifNil: [ semaphore := Semaphore new].
semaphoreIndex ifNil: [ semaphoreIndex := Smalltalk registerExternalObject: semaphore].

File primitiveWaitForDataOn: handle signalling: semaphoreIndex.
semaphore wait.
]
8 changes: 8 additions & 0 deletions src/Files/File.class.st
Expand Up @@ -830,6 +830,14 @@ File class >> primToPlatformPath: aByteArray [
^self signalError: error for: 'primToPlatformPath:'
]

{ #category : #'primitives-file' }
File class >> primitiveWaitForDataOn: id signalling: semaphoreIndex [

<primitive: 'primitiveWaitForDataWithSemaphore' module: 'FilePlugin' error: ec>

self primitiveFailed
]

{ #category : #'primitives-file' }
File class >> read: id into: byteArray startingAt: startIndex count: count [
"Read up to count bytes of data from this file into the given string or byte array starting at the given index. Answer the number of bytes actually read."
Expand Down

0 comments on commit 1b67e2e

Please sign in to comment.