RegressionTests__PipeStreamTest.st
author Claus Gittinger <cg@exept.de>
Thu, 17 May 2018 23:12:11 +0200
changeset 1935 0b014f108ad8
parent 1906 a7f11abb9d19
child 2009 f99d1003cfd9
permissions -rw-r--r--
initial checkin class: RegressionTests::CacheDictionaryTest added: #testAdd #testAddRemove class: RegressionTests::CacheDictionaryTest class

"{ Encoding: utf8 }"

"{ Package: 'stx:goodies/regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#PipeStreamTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-Streams'
!


!PipeStreamTest methodsFor:'tests'!

testPipeWriteRead
    | makeReader makeWriter count threads ok blocker|

    count := 1000.
    threads := 200.
    "/ There's limit to 50 open files in BCC5.5 libc, sigh.
    OperatingSystem isMSWINDOWSlike ifTrue:[
	threads := 20.
    ].
    ok := true.
    blocker := Semaphore new: 2 - threads.

    makeReader := [:stream |
	    [
		| c |
		c := 0.
		[ stream atEnd ] whileFalse:[
		    stream next.
		    c := c + 1.
		].
		stream close.
		ok := ok and:[ count == c ].
		blocker signal.
	    ]
	].

    makeWriter := [:stream |
	    [
		[
		    count timesRepeat:[stream nextPut: $P]
		] on: Error do:[
		    ok := false
		].
		stream close.
	    ]
	].

    threads timesRepeat:[
	|pipe rs ws|

	pipe := NonPositionableExternalStream makePipe.
	rs := pipe at:1.
	ws := pipe at:2.

	(makeReader value: rs) fork.
	(makeWriter value: ws) fork.
    ].

    blocker wait.
    self assert: ok.

    "Created: / 27-03-2014 / 16:21:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

testReadCheckPipe4
    "readCheck a pipe.
     Do this and interrupt the reading thread heavily"

    | cmd s p count|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        cmd := 'waitfor /T 3 pause'.
    ] ifFalse:[
        cmd := 'sleep 3'.
    ].

    s := PipeStream readingFrom:cmd.

    p := [
        s readWait.
        '   --- testReadCheckPipe4: readWait finished' printCR.
    ] forkAt:7.

    count := 0.
    [p isDead] whileFalse:[
        Delay waitForMilliseconds:5.
        p interruptWith:[count := count + 1].
    ].
    ('   --- testReadCheckPipe4: readWait interrupted <1p> times' expandMacrosWith:count) printCR.

    s close.

    "/ assume that our timer resolution is at least 20Hz (usually it is much better...)
    self assert:(count >= (3 / (1/20))).

    "
     self new testReadCheckPipe4
    "

    "Modified: / 12.8.1998 / 13:42:13 / cg"
!

testReadCheckPipe5
    "readCheck a pipe.
     Do this and interrupt the reading thread heavily"

    | s p count line cmd|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        cmd := 'waitfor /T 3 pause & echo hello'.
    ] ifFalse:[
        cmd := 'sleep 3; echo hello'.
    ].
    s := PipeStream readingFrom:cmd.

    p := [
        s readWait.
        line := s nextLine.
        '   --- testReadCheckPipe5: readWait finished' printCR.
    ] forkAt:7.

    count := 0.
    [p isDead] whileFalse:[
        Delay waitForMilliseconds:5.
        p interruptWith:[count := count + 1].
    ].
    ('   --- testReadCheckPipe5: readWait interrupted <1p> times' expandMacrosWith:count) printCR.

    s close.

    self assert:(line = 'hello').
    "/ assume that our timer resolution is at least 20Hz (usually it is much better...)
    self assert:(count >= (3 / (1/20))).

    "
     self new testReadCheckPipe5
    "

    "Modified: / 12.8.1998 / 13:42:13 / cg"
!

testReadPipe6
    "read a pipe.
     Do this and interrupt the reading thread heavily"

    | s p count error line  cmd|

    error := nil.

    "/ self createTestFile.

    OperatingSystem isMSWINDOWSlike ifTrue:[
        cmd := 'waitfor /T 3 pause'.
    ] ifFalse:[
        cmd := 'sleep 3'.
    ].

    s := PipeStream readingFrom:cmd.

    p := [
        [
            line := s nextLine.
            "/ line printCR.
        ] on: Error do:[:ex|
            error := ex.
        ]
    ] forkAt:7.

    count := 0.
    [p isDead] whileFalse:[
        Delay waitForMilliseconds:5.
        p interruptWith:[count := count + 1].
    ].
    ('   --- testReadPipe6: read interrupted <1p> times' expandMacrosWith:count) printCR.

    s close.

    self assert: error isNil.
    self assert: line isEmptyOrNil.
    "/ assume that our timer resolution is at least 20Hz (usually it is much better...)
    self assert:(count >= (3 / (1/20))).

    "
     self new testReadPipe6
    "

    "Modified: / 12.8.1998 / 13:42:13 / cg"
!

testReadPipe7
    "read a pipe.
     Do this and interrupt the reading thread heavily"

    |s p count error line  cmd|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        cmd := 'waitfor /T 3 pause & echo hello'.
    ] ifFalse:[
        cmd := 'sleep 3; echo hello'.
    ].
    s := PipeStream readingFrom:cmd.

    p := [
        [
            line := s nextLine.
            "/ line printCR.
        ] on: Error do:[:ex|
            error := ex.
        ]
    ] forkAt:7.

    count := 0.
    [p isDead] whileFalse:[
        Delay waitForMilliseconds:5.
        p interruptWith:[count := count + 1].
    ].
    ('   --- read interrupted <1p> times' expandMacrosWith:count) printCR.

    s close.

    self assert: error isNil.
    self assert: line = 'hello'.
    "/ assume that our timer resolution is at least 20Hz (usually it is much better...)
    self assert:(count >= (3 / (1/20))).

    "
     self test7
    "

    "Modified: / 12.8.1998 / 13:42:13 / cg"
! !

!PipeStreamTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !