VDBInternalPipeStream.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 07 Jun 2014 14:42:45 +0100
changeset 1 09b3ef5606e7
parent 0 33a652015a1a
child 3 cff42f8f0f9d
permissions -rw-r--r--
Added simple event log application. Initial stub for application containers (docking panels)

"{ Package: 'jv:vdb' }"

Stream subclass:#VDBInternalPipeStream
	instanceVariableNames:'buffer first last dataAvailable spaceAvailable closed'
	classVariableNames:'DefaultBufferSize'
	poolDictionaries:''
	category:'VDB-Support'
!

!VDBInternalPipeStream class methodsFor:'documentation'!

documentation
"
    not useful on its own, but can be used to talk to a vt100
    terminal view ...
    See example.
"
!

examples
"
                                                                [exBegin]
    |p|

    p := InternalPipeStream new.
    [
        10 timesRepeat:[
            p nextPutLine:'hello'
        ].
    ] fork.

    [
        10 timesRepeat:[
            Transcript showCR:p nextLine
        ].
    ] fork.
                                                                [exEnd]

                                                                [exBegin]
    |userInput elizasOutput top terminal|

    userInput    := InternalPipeStream new.
    elizasOutput := InternalPipeStream new.

    top := StandardSystemView new.
    terminal := VT100TerminalView openOnInput: userInput output:elizasOutput in:top.

    top extent:(terminal preferredExtent).
    top label:'The doctor is in'.
    top iconLabel:'doctor'.
    top open.
    top waitUntilVisible.

    terminal translateNLToCRNL:true.
    terminal inputTranslateCRToNL:true.
    terminal localEcho:true.

    elizasOutput nextPutLine:'Hi, I am Eliza'.
    elizasOutput nextPutLine:'What is your problem ?'.
    elizasOutput nextPutLine:''.
    elizasOutput nextPutAll:'>'.

    [top realized] whileTrue:[
        |line answer matchingRule|

        line := userInput nextLine.
        (#('quit' 'exit' 'end' 'bye') includes:line) ifTrue:[
            top destroy.
            ^ self
        ].

        answer := 'Tell me more.'.
        elizasOutput nextPutLine:answer.
        elizasOutput nextPutAll:'>'.
    ].
                                                                [exEnd]
"
! !

!VDBInternalPipeStream class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    DefaultBufferSize := 1024.

    "Modified: / 07-06-2014 / 00:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBInternalPipeStream class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
!

newWithBufferSize: bufferSize
    ^ self basicNew initializeWithBufferSize: bufferSize

    "Created: / 07-06-2014 / 00:48:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBInternalPipeStream methodsFor:'accessing'!

atEnd
    ^ closed and:[ last == 0 ]

    "Modified: / 07-06-2014 / 01:06:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

close
    closed := true.

    "Modified: / 07-06-2014 / 01:02:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

next
    "return the next element from the stream (might block until something is written)"

    | c |

    last == 0 ifTrue:[ 
        closed ifTrue:[ 
            ^ nil.
        ].
        dataAvailable wait.
    ].
    c := buffer at: first.
    first == last ifTrue:[ 
        first := 1.
        last := 0.
    ] ifFalse:[
       first ~~ buffer size ifTrue:[
           first := first + 1.
       ] ifFalse:[ 
           first := 1.
       ].
    ].
    spaceAvailable signalForAll.
    ^ c

    "Modified: / 07-06-2014 / 01:06:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

nextAvailableBytes:nMax into:aBuffer startingAt:startIndex
    |n idx ch|

    n := 0.
    idx := startIndex.
    [n <= nMax] whileTrue:[
        ch := buffer nextIfEmpty:[^ n ].
        aBuffer at:idx put:ch.
        idx := idx + 1.
        n := n + 1
    ].
    ^ n
!

nextPut:aCharacter
    closed ifTrue:[ 
        self class writeErrorSignal signal:'Pipe stream closed'.
    ].
    
    last > first ifTrue:[ 
        last < buffer size ifTrue:[ 
            last := last + 1.
        ] ifFalse:[
            "/ wrapping around
            first == 1 ifTrue:[ 
                spaceAvailable wait. "/ wait for some space.
            ].
            last := 1.
        ]
    ] ifFalse:[ 
        (last ~~ 0 and:[(last + 1) = (first)]) ifTrue:[ 
            spaceAvailable wait. "/ wait for some space.                
        ].
        last == buffer size ifTrue:[ 
            last := 1.
        ] ifFalse:[
            last := last + 1.
        ].
    ].
    buffer at: last put: aCharacter.
    dataAvailable signalForAll.

    "Modified: / 07-06-2014 / 01:04:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

size
    last == 0 ifTrue:[ ^ 0 ].
    last >= first ifTrue:[ 
        ^ last - first + 1 
    ] ifFalse:[ 
        ^ buffer size - first + 1 + last
    ].

    "Modified: / 07-06-2014 / 01:08:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBInternalPipeStream methodsFor:'initialization'!

initializeWithBufferSize: bufferSize
    buffer := String new: bufferSize.
    first := 1.
    last := 0.

    dataAvailable := Semaphore new.
    spaceAvailable := Semaphore new.

    closed := false

    "Created: / 07-06-2014 / 00:49:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBInternalPipeStream methodsFor:'synchronization'!

readWait
    last == 0 ifTrue:[ 
        dataAvailable wait.
    ].

    "Modified: / 07-06-2014 / 01:09:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


VDBInternalPipeStream initialize!