RegressionTests__WebSocketTest.st
author sr
Wed, 22 Jan 2020 17:27:17 +0100
changeset 2525 e2e38015576c
parent 2524 c3334fc8c2b6
child 2526 e16aa3f08cdb
permissions -rw-r--r--
#BUGFIX by Stefan Reise class: WebSocketTest added: #testCommunicationByteArra500

"{ Encoding: utf8 }"

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

"{ NameSpace: RegressionTests }"

TestCase subclass:#WebSocketTest
	instanceVariableNames:''
	classVariableNames:'ServerWebSocket ClientWebSocket'
	poolDictionaries:''
	category:'tests-Regression-Web'
!

HTTPService subclass:#DemoWebSocketService
	instanceVariableNames:'webSocketCreationCallback'
	classVariableNames:''
	poolDictionaries:''
	privateIn:WebSocketTest
!

!WebSocketTest class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    class:
        <a short class summary here, describing what instances represent>

    responsibilities:    
        <describing what my main role is>

    collaborators:    
        <describing with whom and how I talk to>

    API:
        <public api and main messages>
        
    example:
        <a one-line examples on how to use - can also be in a separate example method>

    implementation:
        <implementation points>

    [author:]
        Stefan Reise

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!WebSocketTest class methodsFor:'actions'!

resetServerAndClientWebsocket
    "
        self resetServerAndClientWebsocket
    "

    ServerWebSocket := nil.
    ClientWebSocket := nil.

    "Created: / 17-01-2020 / 13:37:18 / Stefan Reise"
! !

!WebSocketTest methodsFor:'data'!

allData
    "
        self new allData
    "    

    |allData|

    allData := OrderedCollection new.
    self allDataWithFrameHash pairWiseDo:[:first :second |
        allData add:first.
    ].

    ^ allData

    "Created: / 20-01-2020 / 13:56:05 / Stefan Reise"
    "Modified (comment): / 21-01-2020 / 10:38:54 / Stefan Reise"
!

allDataWithFrameHash
    "
        self new allDataWithFrameHash
    "    

    ^ self dataWithLength0AndFrameHash                      "/ zero data
    , self dataWithLength11AndFrameHash                     "/ just hello world
    , self dataWithLength125AndFrameHash                    "/ last fitting length for the single byte
    , self dataWithLength126AndFrameHash                    "/ first length to put into for 2 bytes according to the protocol
    , self dataWithLength127AndFrameHash                    "/ first length + 1 to put into 2 bytes    
    , self dataWithLength65535AndFrameHash                  "/ last fitting length for 2 bytes
    , self dataWithLength65536AndFrameHash                  "/ first length to put into 8 bytes according to the protocol     
    , self dataWithLength70536AndFrameHash                  "/ random length to put into 8 bytes
    , self dataWithLengthMaxPerFrameAndFrameHash            "/ last fitting length for max frame length
    , self dataWithLengthMaxPerFramePlus1AndFrameHash       "/ first length to put into multiple frames
    , self dataWithLengthMaxTestAndFrameHash                "/ max length for testing

    "Created: / 20-01-2020 / 13:54:14 / Stefan Reise"
    "Modified (comment): / 21-01-2020 / 10:38:30 / Stefan Reise"
!

byteArray100
    ^ ByteArray new:100 * 1024 * 1024

    "Created: / 22-01-2020 / 15:42:28 / Stefan Reise"
!

byteArray500
    ^ ByteArray new:500 * 1024 * 1024

    "Created: / 22-01-2020 / 15:42:32 / Stefan Reise"
!

data100
    ^ String new:100 * 1024 * 1024

    "Created: / 22-01-2020 / 15:40:35 / Stefan Reise"
!

data500
    ^ String new:512 * 1024 * 1024

    "Created: / 22-01-2020 / 15:40:58 / Stefan Reise"
!

dataWithLength0AndFrameHash
    ^ #(
        '' 
        33024
    )

    "Created: / 20-01-2020 / 13:24:23 / Stefan Reise"
!

dataWithLength11AndFrameHash
    ^ #(
        'Hello World' 
        457351956
    )

    "Created: / 20-01-2020 / 13:24:42 / Stefan Reise"
!

dataWithLength125AndFrameHash
    ^ #(
        '12345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345' 
        854990094
    )

    "Created: / 20-01-2020 / 13:21:12 / Stefan Reise"
!

dataWithLength126AndFrameHash
    ^ #(
        '123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456' 
        386953194           
    )

    "Created: / 20-01-2020 / 13:21:15 / Stefan Reise"
!

dataWithLength127AndFrameHash
    ^ #(
        '1234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567' 
        1015153950
    )

    "Created: / 20-01-2020 / 13:21:18 / Stefan Reise"
!

dataWithLength65535AndFrameHash
    |string|

    string := String new:65535.

    ^ Array
        with:string
        with:526675651

    "Created: / 20-01-2020 / 13:21:20 / Stefan Reise"
!

dataWithLength65536AndFrameHash
    |string|

    string := String new:65536.

    ^ Array
        with:string
        with:894588570

    "Created: / 20-01-2020 / 13:21:23 / Stefan Reise"
!

dataWithLength70536AndFrameHash
    |string|

    string := String new:70536.

    ^ Array
        with:string
        with:201475330

    "Created: / 20-01-2020 / 13:21:25 / Stefan Reise"
!

dataWithLengthMaxPerFrameAndFrameHash
    |string|

    string := String new:WebSocketStream maxSizeInByterPerFrame.

    ^ Array
        with:string
        with:656112522

    "Created: / 20-01-2020 / 13:59:13 / Stefan Reise"
!

dataWithLengthMaxPerFramePlus1AndFrameHash
    |string|

    string := String new:WebSocketStream maxSizeInByterPerFrame + 1.

    ^ Array
        with:string
        with:95386507

    "Created: / 20-01-2020 / 14:03:29 / Stefan Reise"
!

dataWithLengthMaxTestAndFrameHash
    |string|

    string := String new:5 * 1024 * 1024. "/ 5mb      

    ^ Array
        with:string
        with:888620042

    "Created: / 20-01-2020 / 14:04:40 / Stefan Reise"
! !

!WebSocketTest methodsFor:'helper'!

communicationWithData:dataArrayOrData
    doAssert:doAssert

    ^ self 
        withData:dataArrayOrData
        do:[:eachData |
            self clientWebSocket nextPut:eachData.
            doAssert ifTrue:[
                self assert:self serverWebSocket next = eachData.
            ].

            self serverWebSocket nextPut:eachData.
            doAssert ifTrue:[
                self assert:self clientWebSocket next = eachData.
            ].
        ]

    "Created: / 22-01-2020 / 16:19:34 / Stefan Reise"
!

maskAndUnmaskData:dataArrayOrData
    doAssert:doAssert

    |webSocket mask eachDataAsByteArray eachMasked eachUnmasked|

    webSocket := WebSocketStream new.
    mask := #[12 214 166 43]. 

    ^ self 
        withData:dataArrayOrData
        do:[:eachByteArrayOrString |
            eachDataAsByteArray := eachByteArrayOrString asByteArray.

            eachMasked := webSocket
                maskOrUnmaskPayload:eachDataAsByteArray 
                withMask:mask.

            eachUnmasked := webSocket
                maskOrUnmaskPayload:eachMasked 
                withMask:mask.         

            doAssert ifTrue:[
                self assert:eachUnmasked = eachDataAsByteArray.
            ].
        ]

    "Created: / 22-01-2020 / 16:22:41 / Stefan Reise"
!

withData:dataArrayOrData
    do:aBlock

    |startTimestamp dataArray timeDurationUsed|

    startTimestamp := Timestamp now.

    dataArray := dataArrayOrData.
    (dataArrayOrData firstIfEmpty:nil) isCollection ifFalse:[
        dataArray := Array with:dataArrayOrData.
    ].

    dataArray do:aBlock.

    timeDurationUsed := Timestamp now - startTimestamp. 
    Transcript showCR:timeDurationUsed printString.

    ^ timeDurationUsed

    "Created: / 22-01-2020 / 16:21:30 / Stefan Reise"
! !

!WebSocketTest methodsFor:'queries'!

clientWebSocket
    ClientWebSocket isNil ifTrue:[
        self setupServerAndClientWebsocket.
    ].

    ^ ClientWebSocket

    "Created: / 17-01-2020 / 13:23:11 / Stefan Reise"
!

serverWebSocket
    ServerWebSocket isNil ifTrue:[
        self setupServerAndClientWebsocket.
    ].

    ^ ServerWebSocket

    "Created: / 17-01-2020 / 13:23:15 / Stefan Reise"
! !

!WebSocketTest methodsFor:'setup'!

setupServerAndClientWebsocket
    "
        self resetServerAndClientWebsocket
    "

    |response|   

    DemoWebSocketService start
        webSocketCreationCallback:[:newWebSocket |
            ServerWebSocket := newWebSocket.
        ].

    response := HTTPInterface 
        get:('ws://localhost:%1%2'
            bindWith:DemoWebSocketService defaultPort
            with:DemoWebSocketService linkName).

    response isErrorResponse ifTrue:[
        self error:'failed to connect'.
    ]. 

    ClientWebSocket := response webSocket.

    "Created: / 17-01-2020 / 13:21:28 / Stefan Reise"
    "Modified: / 20-01-2020 / 18:08:26 / Stefan Reise"
! !

!WebSocketTest methodsFor:'tests'!

testCommunication
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    self 
        communicationWithData:self allData
        doAssert:true.

    "Created: / 17-01-2020 / 13:24:24 / Stefan Reise"
    "Modified: / 22-01-2020 / 16:25:01 / Stefan Reise"
!

testCommunication100
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    self 
        communicationWithData:self data100
        doAssert:true.

    "Created: / 22-01-2020 / 16:39:15 / Stefan Reise"
!

testCommunication500
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    self 
        communicationWithData:self data500
        doAssert:true.

    "Created: / 22-01-2020 / 16:39:19 / Stefan Reise"
!

testCommunicationByteArra500
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    self 
        communicationWithData:self byteArray500
        doAssert:true.

    "Created: / 22-01-2020 / 17:26:59 / Stefan Reise"
!

testCommunicationSmallFrameSize
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    |maxSizeInByterPerFrameBefore|

    maxSizeInByterPerFrameBefore := WebSocketStream maxSizeInByterPerFrame.
    WebSocketStream maxSizeInByterPerFrame:1024. 

    self 
        communicationWithData:self allData
        doAssert:true.

    WebSocketStream maxSizeInByterPerFrame:maxSizeInByterPerFrameBefore.

    "Created: / 22-01-2020 / 16:17:28 / Stefan Reise"
!

testCommunicationWithDelay
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket              

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxSizeInByterPerFrame:1024. 
        WebSocketStream maxSizeInByterPerFrame:nil.      
    "

    self allData do:[:data |
        self clientWebSocket nextPut:data.
    ].

    Delay waitForSeconds:2.

    self allData do:[:data |
        self assert:self serverWebSocket next = data.
        self serverWebSocket nextPut:data.
    ].

    Delay waitForSeconds:2.  

    self allData do:[:data |
        self assert:self clientWebSocket next = data.
    ].

    "Created: / 21-01-2020 / 11:26:23 / Stefan Reise"
    "Modified (comment): / 22-01-2020 / 16:37:22 / Stefan Reise"
!

testEncoding
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket           

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.   
    "

    |serverWebSocket clientWebSocket 
     decodeBlock
     maxSizeInByterPerFrameBefore|

    serverWebSocket := self serverWebSocket.
    clientWebSocket := self clientWebSocket.    

    decodeBlock := 
        [:eachWebSocket :eachFrame |
            ((eachWebSocket decodeFrameHybi17:eachFrame) payload ? '') asString
        ].

    [        
        "inside #allDataWithFrameHash is #dataWithLengthMaxPerFrameAndFrameHash,
         which hash do depent on the #maxSizeInByterPerFrame,
         so set the value, which was used when the hast has been recored"
        maxSizeInByterPerFrameBefore := WebSocketStream maxSizeInByterPerFrame.
        WebSocketStream maxSizeInByterPerFrame:512 * 1024. 

        self allDataWithFrameHash
            pairWiseDo:[:eachData :eachExpectedHashForServer |
                |eachFrame|

                "server -> client"
                eachFrame := serverWebSocket encodeFrameHybi17Text:eachData.
                self assert:eachFrame hash = eachExpectedHashForServer. 
                self assert:eachData = (decodeBlock value:clientWebSocket value:eachFrame). 

                "client -> server"
                eachFrame := clientWebSocket encodeFrameHybi17Text:eachData.
                "/ not able to check against hash from client requests, because they are masked randomly
                self assert:eachData = (decodeBlock value:serverWebSocket value:eachFrame).   
            ].
    ] ensure:[
        maxSizeInByterPerFrameBefore notNil ifTrue:[
            WebSocketStream maxSizeInByterPerFrame:maxSizeInByterPerFrameBefore.
        ].
    ].

    "Created: / 20-01-2020 / 13:13:50 / Stefan Reise"
    "Modified (comment): / 22-01-2020 / 16:36:26 / Stefan Reise"
!

testMask
    self 
        maskAndUnmaskData:self allData
        doAssert:true.

    "Created: / 20-01-2020 / 15:08:27 / Stefan Reise"
    "Modified: / 22-01-2020 / 16:22:48 / Stefan Reise"
!

testMask100
    self 
        maskAndUnmaskData:self byteArray100
        doAssert:true.

    "Created: / 22-01-2020 / 15:41:29 / Stefan Reise"
!

testMask500
    self 
        maskAndUnmaskData:self byteArray500
        doAssert:true.

    "Created: / 22-01-2020 / 15:41:35 / Stefan Reise"
!

testPing
    "
        !! call the following method in case the sockets did get corrupted !!
        self resetServerAndClientWebsocket           

        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.             
        WebSocketStream verboseProtocol:false.   
    "

    |pingTimeDuration|

    pingTimeDuration := self clientWebSocket ping.
    Transcript showCR:pingTimeDuration printString.
    self assert:pingTimeDuration notNil.

    pingTimeDuration := self serverWebSocket ping.
    Transcript showCR:pingTimeDuration printString.
    self assert:pingTimeDuration notNil.

    "Created: / 17-01-2020 / 13:43:58 / Stefan Reise"
    "Modified (comment): / 22-01-2020 / 15:25:11 / Stefan Reise"
! !

!WebSocketTest methodsFor:'tests speed'!

testMask100Speed  
    self 
        assert:(self 
            maskAndUnmaskData:self byteArray100
            doAssert:false)
                < 10 seconds.

    "Created: / 22-01-2020 / 15:49:01 / Stefan Reise"
!

testMask500Speed  
    self 
        assert:(self 
            maskAndUnmaskData:self byteArray500
            doAssert:false)
                < 50 seconds.

    "Created: / 22-01-2020 / 15:48:52 / Stefan Reise"
! !

!WebSocketTest methodsFor:'zzz'!

testOnEchoServer
"/    |rply|   
"/
"/    rply := HTTPInterface get:'ws://echo.websocket.org'.
"/    rply isErrorResponse ifTrue:[
"/        self error:'failed to connect'.
"/    ]. 
"/
"/    rply webSocket

    "Created: / 15-01-2020 / 15:55:27 / Stefan Reise"
    "Modified: / 21-01-2020 / 16:11:15 / Stefan Reise"
! !

!WebSocketTest::DemoWebSocketService class methodsFor:'constants'!

defaultPort
    ^ 9095

    "Created: / 18-11-2019 / 13:19:29 / Stefan Reise"
!

linkName
    ^ '/websocket'

    "Created: / 13-11-2019 / 13:30:11 / Stefan Reise"
! !

!WebSocketTest::DemoWebSocketService class methodsFor:'documentation'!

documentation
"
    [start Server with:]
        HTTPServer startServerOnPort:8080

    [start with:]
        (self new)
            registerServiceOn:(HTTPServer runningServerOnPort:8080)

    class:
        <a short class summary here, describing what instances represent>

    responsibilities:    
        <describing what my main role is>

    collaborators:    
        <describing with whom and how I talk to>

    API:
        <public api and main messages>
        
    example:
        <a one-line examples on how to use - can also be in a separate example method>

    implementation:
        <implementation points>

    [author:]
        Stefan Reise

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!WebSocketTest::DemoWebSocketService class methodsFor:'examples'!

start
    "
        self start
    "

    |httpServer instance|

    httpServer := HTTPServer serverOnPort:self defaultPort.
    instance := self registerServiceOn:httpServer.
    httpServer start.

    ^ instance

    "Created: / 17-01-2020 / 13:19:08 / Stefan Reise"
! !

!WebSocketTest::DemoWebSocketService methodsFor:'accessing'!

webSocketCreationCallback:something
    webSocketCreationCallback := something.
! !

!WebSocketTest::DemoWebSocketService methodsFor:'processing'!

acceptsWebSocket:webSocket
    ^ true

    "Created: / 13-11-2019 / 13:57:03 / Stefan Reise"
!

startServingWebSocket:webSocket
    "to be redefined in subclasses (services) which do handle webSockets;
     close here, in case it was not redefined"

    webSocketCreationCallback value:webSocket.

    "Created: / 13-11-2019 / 14:42:43 / Stefan Reise"
    "Modified: / 17-01-2020 / 13:19:52 / Stefan Reise"
! !

!WebSocketTest::DemoWebSocketService methodsFor:'queries'!

allowWebSockets
    ^ true

    "Created: / 13-11-2019 / 13:29:48 / Stefan Reise"
! !

!WebSocketTest class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !