RegressionTests__WebSocketTest.st
author Claus Gittinger <cg@exept.de>
Tue, 25 Feb 2020 17:19:18 +0100
changeset 2581 e889c17eef8f
parent 2563 9e9b8eacd782
child 2587 7d31bbc2c162
permissions -rw-r--r--
s

"{ 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:'initialization'!

initialize
    |needsToReloadDemoWebSocketService|

    super initialize.

    needsToReloadDemoWebSocketService := (Smalltalk at:#HTTPService) isNil.

    Smalltalk loadPackage:'stx:goodies/communication'.
    Smalltalk loadPackage:'stx:goodies/webServer'.

    needsToReloadDemoWebSocketService ifFalse:[
        ^ self
    ].

    "file in again to get a working DemoWebSocketService"
    (self packageDirectory / 'RegressionTests__WebSocketTest.st') fileIn.

    "Created: / 05-02-2020 / 13:24:53 / 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"
!

data100
    ^ String new:100 * 1024 * 1024

    "Created: / 22-01-2020 / 15:40:35 / 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 maxBytesPerFrame.

    ^ Array
        with:string
        with:656112522

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

dataWithLengthMaxPerFramePlus1AndFrameHash
    |string|

    string := String new:WebSocketStream maxBytesPerFrame + 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'!

assertDataOrFilenameA:dataOrFilenameA
    equalsDataOrFilenameB:dataOrFilenameB

    |convertToDataBlock
     dataA dataB|

    "compare the whole content"
"/    compareSizeLimit := 20 * 1024 * 1024. "/ 20mb

    convertToDataBlock := 
        [:eachDataOrFilename |
            eachDataOrFilename isFilename ifTrue:[
                |fileContentForCompare|

                eachDataOrFilename readingFileDo:[:rs |    
                    fileContentForCompare := rs upToEnd.
"/                    fileContentForCompare := rs nextAvailable:compareSizeLimit.
                ].

                fileContentForCompare
            ] ifFalse:[
                eachDataOrFilename
"/                eachDataOrFilename to:(compareSizeLimit min:dataOrFilenameA size).
            ]
        ].

    dataA := convertToDataBlock value:dataOrFilenameA.
    dataB := convertToDataBlock value:dataOrFilenameB.

    self assert:dataA asByteArray = dataB asByteArray.

    "Created: / 27-01-2020 / 16:19:43 / Stefan Reise"
!

assertOnEchoServer:data
    |reply webSocket|   

    reply := HTTPInterface get:'ws://echo.websocket.org'.
    self assert:reply isErrorResponse not.

    webSocket := reply webSocket.
    webSocket nextPut:data.

    Delay waitForSeconds:5.

    self assert:webSocket next = data.
    webSocket close.

    "Created: / 04-02-2020 / 12:05:27 / Stefan Reise"
!

communicationWithData:dataArrayOrData
    doAssert:doAssert

    |nextData|

    ^ self 
        withData:dataArrayOrData
        do:[:eachDataOrFilename |
            self clientWebSocket nextPut:eachDataOrFilename.
            nextData := self serverWebSocket next.
            doAssert ifTrue:[
                self 
                    assertDataOrFilenameA:nextData
                    equalsDataOrFilenameB:eachDataOrFilename.
            ].

            self serverWebSocket nextPut:eachDataOrFilename.
            nextData := self clientWebSocket next.
            doAssert ifTrue:[
                self 
                    assertDataOrFilenameA:nextData
                    equalsDataOrFilenameB:eachDataOrFilename.  
            ].
        ]

    "Created: / 22-01-2020 / 16:19:34 / Stefan Reise"
    "Modified: / 27-01-2020 / 17:28:33 / 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|

    startTimestamp := Timestamp now.

    dataArray := dataArrayOrData.

    (dataArrayOrData 
        perform:#'firstIfEmpty:'
        with:nil 
        ifNotUnderstood:nil) isCollection ifFalse:[
            dataArray := Array with:dataArrayOrData.
        ].

    dataArray do:aBlock.

    ^ Timestamp now - startTimestamp

    "Created: / 22-01-2020 / 16:21:30 / Stefan Reise"
    "Modified: / 27-01-2020 / 17:49:37 / Stefan Reise"
! !

!WebSocketTest methodsFor:'initialization & release'!

setUp
    |response|   

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

    OperatingSystem isUNIXlike ifTrue:[
        "the first request, 
         gets error response,
         hmmm linux need some time..."
        Delay waitForSeconds:3.
    ].

    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: / 05-02-2020 / 13:54:35 / Stefan Reise"
!

tearDown
    |runningServer|

    super tearDown.

    ServerWebSocket notNil ifTrue:[
        ServerWebSocket close.
    ].

    ClientWebSocket notNil ifTrue:[
        ClientWebSocket close.
    ].

    runningServer := HTTPServer runningServerOnPort:DemoWebSocketService defaultPort.
    runningServer isNil ifTrue:[
        ^ self
    ].

    runningServer terminateServer.

    "Created: / 05-02-2020 / 13:34:55 / Stefan Reise"
! !

!WebSocketTest methodsFor:'queries'!

clientWebSocket
    ClientWebSocket isNil ifTrue:[
        self setUp.
    ].

    ^ ClientWebSocket

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

serverWebSocket
    ServerWebSocket isNil ifTrue:[
        self setUp.
    ].

    ^ ServerWebSocket

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

!WebSocketTest methodsFor:'tests'!

testCommunication
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame: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"
    "Modified (comment): / 23-01-2020 / 11:59:45 / Stefan Reise"
!

testCommunication100
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    self 
        communicationWithData:self data100
        doAssert:true.

    "Created: / 22-01-2020 / 16:39:15 / Stefan Reise"
    "Modified (comment): / 23-01-2020 / 11:59:47 / Stefan Reise"
!

testCommunication100Speed
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    self 
        communicationWithData:self data100
        doAssert:false.

    "Created: / 23-01-2020 / 11:32:34 / Stefan Reise"
!

testCommunication100WithPingsBetween
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |finishSema pingDuration|

    finishSema := Semaphore new.

    [
        self 
            communicationWithData:self data100
            doAssert:true.

        finishSema signal.
    ] forkAt:4.

    5 timesRepeat:[
        Delay waitForSeconds:1.
        pingDuration := self clientWebSocket ping. 
        Transcript showCR:'ping duration: ', pingDuration printString.
        self assert:(pingDuration notNil and:[pingDuration < 5 seconds]).

        Delay waitForSeconds:1.
        pingDuration := self serverWebSocket ping. 
        Transcript showCR:'ping duration: ', pingDuration printString.
        self assert:(pingDuration notNil and:[pingDuration < 5 seconds]).
    ].

    finishSema wait.

    "Created: / 07-02-2020 / 10:22:01 / Stefan Reise"
    "Modified: / 07-02-2020 / 13:50:44 / Stefan Reise"
!

testCommunicationByteArray100
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    self 
        communicationWithData:self byteArray100
        doAssert:true.

    "Created: / 22-01-2020 / 17:45:53 / Stefan Reise"
    "Modified (comment): / 23-01-2020 / 11:59:55 / Stefan Reise"
!

testCommunicationFilename
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |tempFile|

    tempFile := Filename newTemporary.
    tempFile contents:self data100.

    self 
        communicationWithData:tempFile
        doAssert:true.

    "Created: / 27-01-2020 / 15:07:37 / Stefan Reise"
    "Modified (format): / 04-02-2020 / 12:22:23 / Stefan Reise"
!

testCommunicationSmallFrameSize
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |maxSizeInByterPerFrameBefore|

    maxSizeInByterPerFrameBefore := WebSocketStream maxBytesPerFrame.
    WebSocketStream maxBytesPerFrame:1024. 

    self 
        communicationWithData:self allData
        doAssert:true.

    WebSocketStream maxBytesPerFrame:maxSizeInByterPerFrameBefore.

    "Created: / 22-01-2020 / 16:17:28 / Stefan Reise"
    "Modified (comment): / 23-01-2020 / 11:59:57 / Stefan Reise"
!

testCommunicationSmallFrameSizeData5
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |maxSizeInByterPerFrameBefore|

    maxSizeInByterPerFrameBefore := WebSocketStream maxBytesPerFrame.
    WebSocketStream maxBytesPerFrame:1024. 

    self 
        communicationWithData:(String new:5 * 1024 * 1024)
        doAssert:true.

    WebSocketStream maxBytesPerFrame:maxSizeInByterPerFrameBefore.

    "Created: / 06-02-2020 / 10:35:19 / Stefan Reise"
!

testCommunicationWithDelay
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame: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): / 23-01-2020 / 12:00:00 / Stefan Reise"
!

testEncoding
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |serverWebSocket clientWebSocket 
     decodeBlock
     maxBytesPerFrameBefore|

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

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

    [        
        "inside #allDataWithFrameHash is #dataWithLengthMaxPerFrameAndFrameHash,
         which hash do depent on the #maxBytesPerFrame,
         so set the value, which was used when the hash has been recorded"
        maxBytesPerFrameBefore := WebSocketStream maxBytesPerFrame.
        WebSocketStream maxBytesPerFrame: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:[
        maxBytesPerFrameBefore notNil ifTrue:[
            WebSocketStream maxBytesPerFrame:maxBytesPerFrameBefore.
        ].
    ].

    "Created: / 20-01-2020 / 13:13:50 / Stefan Reise"
    "Modified (format): / 24-01-2020 / 16:03:42 / 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"
!

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

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

testOnEchoServer
    "/ empty (1) and big data (>5) is not supported by echo server
    (self allData from:2 to:5) do:[:eachData |
        self assertOnEchoServer:eachData.
    ].

    "Created: / 15-01-2020 / 15:55:27 / Stefan Reise"
    "Modified: / 04-02-2020 / 12:09:52 / Stefan Reise"
!

testParallelSocketWrite
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    ^ self 
        withData:self data100
        do:[:eachData |
            self clientWebSocket nextPut:eachData.
            self serverWebSocket nextPut:eachData.

            Delay waitForSeconds:20.

            self clientWebSocket next.
            self serverWebSocket next.
        ].

    "Created: / 23-01-2020 / 11:47:47 / Stefan Reise"
    "Modified: / 04-02-2020 / 12:26:59 / Stefan Reise"
!

testPing
    "
        WebSocketStream verbose:true.
        WebSocketStream verboseProtocol:true.

        WebSocketStream verbose:false.
        WebSocketStream verboseProtocol:false.

        WebSocketStream maxBytesPerFrame:1024. 
        WebSocketStream maxBytesPerFrame:nil.      
    "

    |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 manual'!

manualTestWithFirefox
    "
        self new manualTestWithFirefox

        opens firefox with a javascript websocket testpage.
        the testpage logs everything with javascript console.log().
        open the console window in firefox to see whats going on.

        you need a running websocket service, may start as followed:
        ATTENTION the Callback / Inspector opens after the connect from the test page (not directly after starting the service)
        use: self nextPut:'Hello World' 
        inside the inspector of the webSocket to send something to the javascript websocket client

            DemoWebSocketService start
                webSocketCreationCallback:[:webSocket |
                    webSocket 
                        closedByPeerCallback:[
                            Transcript showCR:'socket close by peer'.
                            self halt.
                        ];
                        closedByErrorCallback:[
                            Transcript showCR:'socket close by error'.
                            self halt.
                        ];
                        inspect. 
                ].


        enter the url in the connect box of the test page in firefox: (doit)

            'ws://localhost:%1%2'
                bindWith:DemoWebSocketService defaultPort
                with:DemoWebSocketService linkName   

            ws://localhost:9096/websocket
    "

    |firefox regEntry testHtml|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        regEntry := OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\WOW6432Node\Microsoft\Windows\CurrentVersion\App Paths\firefox.exe'.
        regEntry isNil ifTrue:[
            self error:'no firefox (at least in registry)'.
        ].

        firefox := '"', regEntry defaultValue, '"'.
    ] ifFalse:[
        firefox := 'firefox'.
    ].

    testHtml := Filename tempDirectory / (UUID genRandomUUID printString, '.html').
    testHtml contents:
'<html>
    <head>
        <script language="javascript" type="text/javascript">
            var websocket;
        
            function onOpen(evt) {
                console.log("callback onopen");
            }

            function onClose(evt) {
                console.log("callback onClose");
            }

            function onMessage(evt) {
                console.log("callback onMessage: " + evt.data);
            }

            function onError(evt) {
                console.log("callback onError: " + evt.data);
            }

            function startWebSocket(wsUrl) {
                websocket = new WebSocket(wsUrl);
                websocket.onopen = function(evt) { onOpen(evt) };
                websocket.onclose = function(evt) { onClose(evt) };
                websocket.onmessage = function(evt) { onMessage(evt) };
                websocket.onerror = function(evt) { onError(evt) };
            }
          
            function closeWebSocket() {
                if (websocket) {
                    console.log("close");
                    websocket.close();
                } else {
                    console.log("var websocket not set");
                }
            }

            function doSend(message) {
                if (websocket) {
                    console.log("send: " + message);
                    websocket.send(message);
                } else {
                    console.log("var websocket not set");
                }
            }
        </script>
    </head>
    <body>
        <table><tr><td align="right">
            Websocket URL:
        </td><td>
            <input type="edit" id="wsUrl">
        </td><td>
            <input type="button" value="Connect" onClick="startWebSocket(document.getElementById(&quot;wsUrl&quot;).value);">
        </td></tr><tr><td align="right">
            Message:
        </td><td>
            <input type="edit" id="message">
        </td><td>
            <input type="button" value="Send" onClick="doSend(document.getElementById(&quot;message&quot;).value);">
        </td></tr><tr><td align="right"></td><td align="right"></td><td>
            <input type="button" value="Disconnect" onClick="closeWebSocket();">
        </td></tr></table>
    </body>
</html>'.

    OperatingSystem 
        executeCommand:('%1 "file://%2"'
            bindWith:firefox
            with:testHtml).

    "Created: / 04-02-2020 / 14:37:54 / Stefan Reise"
! !

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

defaultPort
    OperatingSystem isMSWINDOWSlike ifTrue:[
        ^ 8958
    ].

    ^ 9095

    "Created: / 18-11-2019 / 13:19:29 / Stefan Reise"
    "Modified: / 06-02-2020 / 11:19:25 / 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"

    |callback|

    callback := webSocketCreationCallback.
    callback notNil ifTrue:[
        callback 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$'
! !


WebSocketTest initialize!