RegressionTests__BinaryIOTests.st
author Claus Gittinger <cg@exept.de>
Mon, 23 Nov 2009 18:44:02 +0100
changeset 554 2498f18d1e95
parent 339 adbb9ff06135
child 555 9ffbf260e086
permissions -rw-r--r--
changed: #testIntegers1

"{ Package: 'exept:regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#BinaryIOTests
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-BinaryStorage'
!

!BinaryIOTests class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    [author:]
        Claus Gittinger (cg@alan)

    [instance variables:]

    [class variables:]

    [see also:]

"
!

history
    "Created: / 09-09-2004 / 13:13:39 / cg"
! !

!BinaryIOTests methodsFor:'initialize / release'!

setUp
    "common setup - invoked before testing."

    super setUp
!

tearDown
    "common cleanup - invoked after testing."

    super tearDown
! !

!BinaryIOTests methodsFor:'tests'!

test1
    |test test2 loaders bytes outStream inStream|

    loaders := OrderedCollection new.

    outStream := ByteArray new writeStream.

    test := [:objWritten |
                objWritten storeBinaryOn:outStream.
                loaders add:[ 
                                    |objRead expected|

                                    expected := objWritten.
                                    objRead := inStream nextObject.
                                    self assert:( objRead = expected ) 
                                 ]
              ].

    test2 := [:val | test value:val. test value:  val negated].

    test value:(1 to:99).
    test value:(1 to:99) asArray.

    bytes := outStream contents.
    inStream := BinaryInputManager on:bytes readStream.

    loaders do:[:action | action value ].

    "
     self run:#test1
     self new test1
    "
!

testByteArrays1
    |objs outStream inStream|

    outStream := ByteArray new writeStream.

    objs := #(
        []
        [1]
        [1 2]
        [1 2 3]
    ).

    objs do:[:written |
        written storeBinaryOn:outStream.
    ].


    inStream := BinaryInputManager on:(outStream contents readStream).

    objs do:[:expected | |read|
        read := inStream nextObject.
        self assert:( read = expected).
    ].

    "
     self run:#testByteArrays1
     self new testByteArrays1
    "
!

testByteArrays2
    |outStream inStream test|

    test := [:obj |
        |written read|

        outStream := ByteArray new writeStream.
        written := obj.
        written storeBinaryOn:outStream.

        inStream := BinaryInputManager on:(outStream contents readStream).

        read := inStream nextObject.
        self assert:( read = written).
    ].

    test value:(1 to:254) asByteArray.
    test value:(1 to:255) asByteArray.
    test value:(0 to:255) asByteArray.

    test value:(ByteArray new:100).
    test value:(ByteArray new:127).
    test value:(ByteArray new:128).
    test value:(ByteArray new:129).
    test value:(ByteArray new:254).
    test value:(ByteArray new:255).
    test value:(ByteArray new:256).
    test value:(ByteArray new:257).
    test value:(ByteArray new:1000).
    test value:(ByteArray new:10000).
    test value:(ByteArray new:100000).
    test value:(ByteArray new:1000000).
    test value:(ByteArray new:10000000).

    "
     self run:#testByteArrays2
     self new testByteArrays2
    "
!

testIntegers1
    |nums outStream bytes inStream|

    outStream := ByteArray new writeStream.

    nums := #(
        0
        1
        127
        128
        129
        254 
        255 
        256 
        16r0FFF 
        16r1000 
        16r1001 
        16r1FFF 
        16r2000 
        16r2001 
        16r3FFF 
        16r4000 
        16r4001 
        16r7FFF 
        16r8000 
        16r8001 
        16rFFFF 
        16r10000 
        16r10001 

        16r3FFFFF 
        16r400000 
        16r400001 
        16r7FFFFF 
        16r800000 
        16r800001 
        16rFFFFFF 
        16r1000000 
        16r1000001 

        16r3FFFFFFF 
        16r40000000 
        16r40000001 
        16r7FFFFFFF 
        16r80000000 
        16r80000001
        16rFFFFFFFF 
        16r100000000 
        16r100000001 

        16r3FFFFFFFFF 
        16r4000000000 
        16r4000000001 
        16r7FFFFFFFFF 
        16r8000000000 
        16r8000000001 
        16rFFFFFFFFFF 
        16r10000000000 
        16r10000000001 

        16r3FFFFFFFFFFF 
        16r400000000000 
        16r400000000001 
        16r7FFFFFFFFFFF 
        16r800000000000 
        16r800000000001 
        16rFFFFFFFFFFFF 
        16r1000000000000 
        16r1000000000001 

        16r3FFFFFFFFFFFFF 
        16r40000000000000 
        16r40000000000001 
        16r7FFFFFFFFFFFFF 
        16r80000000000000 
        16r80000000000001 
        16rFFFFFFFFFFFFFF 
        16r100000000000000 
        16r100000000000001 

        16r3FFFFFFFFFFFFFFF            
        16r4000000000000000 
        16r4000000000000001 
        16r7FFFFFFFFFFFFFFF 
        16r8000000000000000 
        16r8000000000000001 
        16rFFFFFFFFFFFFFFFF 
        16r10000000000000000 
        16r10000000000000001 

        16r3FFFFFFFFFFFFFFFFF 
        16r400000000000000000 
        16r400000000000000001 
        16r7FFFFFFFFFFFFFFFFF 
        16r800000000000000000 
        16r800000000000000001 
        16rFFFFFFFFFFFFFFFFFF 
        16r1000000000000000000 
        16r1000000000000000001 

        16r3FFFFFFFFFFFFFFFFFFF 
        16r40000000000000000000 
        16r40000000000000000001 
        16r7FFFFFFFFFFFFFFFFFFF 
        16r80000000000000000000 
        16r80000000000000000001 
        16rFFFFFFFFFFFFFFFFFFFF 
        16r100000000000000000000 
        16r100000000000000000001 

        16r7FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF 
        16r80000000000000000000000000000000000000 
        16rFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF 
    ).

    nums do:[:written |
        |bytes read|

        bytes := written binaryStoreBytes.
        Transcript show:written.
        Transcript show:' -> '.
        Transcript showCR:bytes.
        read := Object fromBinaryStoreBytes:bytes.
        self assert:(read = written).
    ].

    nums do:[:written |
        |bytes read|

        bytes := written negated binaryStoreBytes.
        Transcript show:written.
        Transcript show:' -> '.
        Transcript showCR:bytes.
        read := Object fromBinaryStoreBytes:bytes.
        self assert:(read = written negated).
    ].

    nums do:[:written |
        written storeBinaryOn:outStream.
        written negated storeBinaryOn:outStream.
    ].

    bytes := outStream contents.
    inStream := BinaryInputManager on:(bytes readStream).

    nums do:[:expected | |read|
        read := inStream nextObject.
        self assert:( read = expected).

        read := inStream nextObject.
        self assert:( read = expected negated).

    ].

    "
     self run:#testIntegers1
     self new testIntegers1
    "
!

testSaveReadBOS

    |obj fn bos child |

    Class withoutUpdatingChangesDo:[
        HierarchicalItem subclass:#XHierarchicalItem
            instanceVariableNames:''
            classVariableNames:''
            poolDictionaries:''
            category:'Views-Support'.
    ].

    obj := XHierarchicalItem  new.
    child := XHierarchicalItem new.
    obj add: child.
    child instVarNamed:#width put:XHierarchicalItem.

    fn := '/tmp/HI' asFilename.
    bos :=  BinaryObjectStorage onNew: (fn writeStream).
    bos nextPut: obj.
obj inspect.
    bos close.

    Class withoutUpdatingChangesDo:[
        XHierarchicalItem addInstVarName:'foo'
    ].

    fn := '/tmp/HI' asFilename.

    bos := BinaryObjectStorage onOld: fn readStream.
    BinaryIOManager requestConversionSignal handle:[:ex|
        | oldObject newClass |

        newClass := ex parameter key.
        oldObject := ex parameter value.
        Transcript showCR: 'converting...'.
        ex proceedWith: (newClass cloneFrom: oldObject).
    ] do:[
        BinaryIOManager invalidClassSignal handle:[:ex2|
            | oldClass newClass proceedClass |

            newClass := Smalltalk at: ex2 parameter name asSymbol.
            oldClass := ex2 parameter.

            Transcript showCR: 'will convert instance of ',oldClass name.
            proceedClass :=(((newClass isSubclassOf: HierarchicalItem) or:[newClass == HierarchicalItem]) ifTrue:[newClass] ifFalse:[oldClass]).
            ex2 proceedWith: proceedClass.
        ] do:[
            obj := bos next.
            obj inspect.
        ].
    ].

    "Created: / 26-09-2007 / 18:21:11 / cg"
    "Modified: / 27-09-2007 / 09:47:32 / cg"
!

testStrings1
    |objs outStream inStream|

    outStream := ByteArray new writeStream.

    objs := #(
        ''
        '1'
        '12'
        '123'
        "/        1         2         3         4         5         6         7         8         9         0         1         2
        '12345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678'

        "/        1         2         3         4         5         6         7         8         9         0         1         2         3         4         5         6         7         8         9         0         1         2         3         4         5
        '123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345'

        "/        1         2         3         4         5         6         7         8         9         0         1         2         3         4         5         6         7         8         9         0         1         2         3         4         5
        '1234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456'

        "/        1         2         3         4         5         6         7         8         9         0         1         2         3         4         5         6         7         8         9         0         1         2         3         4         5
        '12345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567'
    ).

    objs do:[:written |
        written storeBinaryOn:outStream.
    ].


    inStream := BinaryInputManager on:(outStream contents readStream).

    objs do:[:expected | |read|
        read := inStream nextObject.
        self assert:( read = expected).
    ].

    "
     self run:#testStrings1
     self new testStrings1
    "
!

testStrings2
    |outStream inStream test|

    test := [:obj |
        |written read|

        outStream := ByteArray new writeStream.
        written := obj.
        written storeBinaryOn:outStream.

        inStream := BinaryInputManager on:(outStream contents readStream).

        read := inStream nextObject.
        self assert:( read = written).
    ].

    test value:(String new:100).
    test value:(String new:127).
    test value:(String new:128).
    test value:(String new:129).
    test value:(String new:254).
    test value:(String new:255).
    test value:(String new:256).
    test value:(String new:257).
    test value:(String new:1000).
    test value:(String new:10000).
    test value:(String new:100000).
    test value:(String new:1000000).
    test value:(String new:10000000).

    "
     self run:#testStrings2
     self new testStrings2
    "
! !

!BinaryIOTests class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !