File: NetworkSpec.hs

package info (click to toggle)
haskell-streaming-commons 0.2.2.6-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 284 kB
  • sloc: haskell: 2,547; ansic: 297; makefile: 7
file content (38 lines) | stat: -rw-r--r-- 1,673 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
{-# LANGUAGE OverloadedStrings #-}
module Data.Streaming.NetworkSpec where

import           Control.Concurrent.Async (withAsync)
import           Control.Exception        (bracket)
import           Control.Monad            (forever, replicateM_)
import           Data.Array.Unboxed       (elems)
import qualified Data.ByteString.Char8    as S8
import           Data.Char                (toUpper)
import           Data.Streaming.Network
import           Network.Socket           (close)
import           Test.Hspec
import           Test.Hspec.QuickCheck

spec :: Spec
spec = do
    describe "getDefaultReadBufferSize" $ do
        it "sanity" $ do
            getReadBufferSize (clientSettingsTCP 8080 "localhost") >= 4096 `shouldBe` True

    describe "getUnassignedPort" $ do
        it "sanity" $ replicateM_ 100000 $ do
            port <- getUnassignedPort
            (port `elem` elems unassignedPorts) `shouldBe` True
    describe "bindRandomPortTCP" $ do
        modifyMaxSuccess (const 5) $ prop "sanity" $ \content -> bracket
            (bindRandomPortTCP "*4")
            (close . snd)
            $ \(port, socket) -> do
                let server ad = forever $ appRead ad >>= appWrite ad . S8.map toUpper
                    client ad = do
                        appWrite ad bs
                        appRead ad >>= (`shouldBe` S8.map toUpper bs)
                    bs
                        | null content = "hello"
                        | otherwise = S8.pack $ take 1000 content
                withAsync (runTCPServer (serverSettingsTCPSocket socket) server) $ \_ -> do
                    runTCPClient (clientSettingsTCP port "localhost") client