RegressionTests__FileStreamTest.st
author Claus Gittinger <cg@exept.de>
Wed, 27 Sep 2000 09:51:29 +0200
changeset 76 90adfa44fa2c
parent 75 1a7d48169a36
child 118 2618cf1cd493
permissions -rw-r--r--
checkin from browser

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

Object subclass:#FileStreamTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Tests-Regression'
!


!FileStreamTest class methodsFor:'tests'!

createTestFile
    "create a test file (100k size)"

    |f bytes|

    f := 'testFile' asFilename writeStream binary.
    bytes := ByteArray new:1024.
    1 to:bytes size do:[:i |
	bytes at:i put:(i \\ 256).
    ].

    100 timesRepeat:[
	f nextPutAll:bytes.
    ].

    f close.

    "
     self createTestFile
    "

    "Created: / 12.8.1998 / 13:25:25 / cg"
!

readFileExpecting:expect
    "read test file, expect n bytes"

    |f buffer n nRead|

    f := 'testFile' asFilename readStream binary.
    buffer := ByteArray new:128.

    n := 0.
    [f atEnd] whileFalse:[
	nRead := f nextBytes:128 into:buffer.
	n := n + nRead.
    ].
    f close.
    expect ~~ n ifTrue:[
	self halt:('got <1p>; expected:<2p>' expandMacrosWith:n with:expect)
    ].

    "Created: / 12.8.1998 / 13:29:41 / cg"
    "Modified: / 12.8.1998 / 13:36:40 / cg"
!

runAllTests
    self testRead1.
    self testRead2.
    self testRead3.
    self testReadCheckPipe4.
    self testReadCheckPipe5.
    self testReadPipe6.
    self testReadPipe7.

    "
     self runAllTests
    "
!

testAppend1
    "basic open for appending."

    |file s sz|

    file := Filename newTemporary.
    s := file writeStream.
    s binary.
    s nextPutAll:(1 to:100).
    s close.

    sz := file fileSize.
    sz ~= 100 ifTrue:[self error:'size mismatch'].

    s := file appendingWriteStream.
    s binary.
    s nextPutAll:(101 to:200).
    s close.

    sz := file fileSize.
    sz ~= 200 ifTrue:[self error:'size mismatch'].

    (file binaryContentsOfEntireFile ~= (1 to:200) asByteArray) ifTrue:[
        self error:'contents mismatch'
    ].

    file delete.

    "
     self testAppend1
    "
!

testOpenRead1
    "basic open for reading."

    |sz|

    self createTestFile.

    sz := 'testFile' asFilename fileSize.

    self readFileExpecting:sz.

    "
     self testOpenRead1
    "
!

testRead1
    "read a file - check count read with files size."

    |sz|

    self createTestFile.

    sz := 'testFile' asFilename fileSize.

    self readFileExpecting:sz.

    "
     self test1
    "

    "Modified: / 12.8.1998 / 13:29:55 / cg"
!

testRead2
    "read a file - check count read with files size.
     Do this in 20 threads"

    |sz|

    self createTestFile.

    sz := 'testFile' asFilename fileSize.

    20 timesRepeat:[
        [self readFileExpecting:sz. 'done' printCR.] fork.
    ].

    "
     self test2
    "

    "Modified: / 12.8.1998 / 13:30:55 / cg"
!

testRead3
    "read a file - check count read with files size.
     Do this and interrupt the reading thread heavily"

    |sz p count nLoop|

    nLoop := 1000.

    self createTestFile.

    sz := 'testFile' asFilename fileSize.

    p := [
        nLoop timesRepeat:[
            self readFileExpecting:sz.
        ].
    ] forkAt:7.

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

    "
     self test3
    "

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

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

    |sz s p count nLoop|

    nLoop := 1000.

    self createTestFile.

    s := PipeStream readingFrom:'sleep 5'.

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

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

    s close.

    "
     self test4
    "

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

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

    |sz s p count nLoop|

    nLoop := 1000.

    self createTestFile.

    s := PipeStream readingFrom:'sleep 5; echo hello'.

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

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

    s close.

    "
     self test5
    "

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

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

    |sz s p count nLoop|

    nLoop := 1000.

    self createTestFile.

    s := PipeStream readingFrom:'sleep 5'.

    p := [
        'read: ' print. s nextLine printCR.
    ] 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 test6
    "

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

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

    |sz s p count nLoop|

    nLoop := 1000.

    self createTestFile.

    s := PipeStream readingFrom:'sleep 5; echo hello'.

    p := [
        'read: ' print. s nextLine printCR.
    ] 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 test7
    "

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

testRewrite1
    "basic open for writing (with truncation)."

    |file s sz|

    file := Filename newTemporary.
    s := file writeStream.
    s binary.
    s nextPutAll:(1 to:200).
    s close.

    sz := file fileSize.
    sz ~= 200 ifTrue:[self error:'size mismatch'].

    s := file writeStream.
    s binary.
    s nextPutAll:(101 to:200).
    s close.

    sz := file fileSize.
    sz ~= 100 ifTrue:[self error:'size mismatch'].

    (file binaryContentsOfEntireFile ~= (101 to:200) asByteArray) ifTrue:[
        self error:'contents mismatch'
    ].

    file delete.

    "
     self testRewrite1
    "
!

testRewrite2
    "basic open for re-writing (without truncation)."

    |file s sz|

    file := Filename newTemporary.
    s := file writeStream.
    s binary.
    s nextPutAll:(1 to:200).
    s close.

    sz := file fileSize.
    sz ~= 200 ifTrue:[self error:'size mismatch'].

    s := file readWriteStream.
    s binary.
    s nextPutAll:(101 to:200).
    s close.

    sz := file fileSize.
    sz ~= 200 ifTrue:[self error:'size mismatch'].

    (file binaryContentsOfEntireFile ~= 
        ((101 to:200) asByteArray , (101 to:200) asByteArray)) ifTrue:[
        self error:'contents mismatch'
    ].

    file delete.

    "
     self testRewrite2
    "
!

testWrite1
    "basic writing"

    self testWrite:1024.
    self testWrite:2048.
    self testWrite:4096.
    self testWrite:8192.
    self testWrite:8192*2.
    self testWrite:8192*4.
    self testWrite:8192*8.
    self testWrite:8192*16.
    self testWrite:8192*32.
    self testWrite:8192*64.
    self testWrite:8192*128.

    "
     self testWrite1
    "
!

testWrite2
    "basic writing"

    10 timesRepeat:[
        self testWrite1.
    ].

    "
     self testWrite2
    "
!

testWrite3
    "basic writing"

    |interruptor|

    interruptor := [
        [true] whileTrue:[
            Delay waitForMilliseconds:10.
        ].
    ] forkAt:9.

    [
        50 timesRepeat:[
            self testWrite1.
        ].
    ] valueNowOrOnUnwindDo:[
        interruptor terminate
    ].

    "
     self testWrite3
    "
!

testWrite:size
    "basic writing"

    |file s sz buffer byte|

    buffer := ByteArray new:size.
    1 to:buffer size do:[:idx |
        buffer at:idx put:(idx \\ 256)
    ].

    file := Filename newTemporary.
    s := file writeStream.

    s binary.
    s nextPutAll:buffer.
    s close.

    sz := file fileSize.
    sz ~= size ifTrue:[self error:'size mismatch'].

    s := file readStream.
    s binary.
    1 to:size do:[:idx |
        byte := s next.
        byte ~~ (idx \\ 256) ifTrue:[self error:'read data mismatch'].
    ].
    s close.

    (file binaryContentsOfEntireFile ~= buffer) ifTrue:[
        self error:'read data mismatch2'
    ].
    file delete.

    "
     self testWrite:1024
    "
! !

!FileStreamTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !