File: ConduitSpec.hs

package info (click to toggle)
haskell-warp 3.0.0.5-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 300 kB
  • ctags: 2
  • sloc: haskell: 2,890; makefile: 8
file content (67 lines) | stat: -rw-r--r-- 1,942 bytes parent folder | download | duplicates (5)
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
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
{-# LANGUAGE OverloadedStrings #-}
module ConduitSpec (main, spec) where

import Network.Wai.Handler.Warp.Conduit
import Network.Wai.Handler.Warp.Types
import Control.Monad (replicateM)
import Test.Hspec
import Data.IORef as I
import qualified Data.ByteString as S

main :: IO ()
main = hspec spec

spec :: Spec
spec = describe "conduit" $ do
    it "IsolatedBSSource" $ do
        ref <- newIORef $ map S.singleton [1..50]
        src <- mkSource $ do
            x <- readIORef ref
            case x of
                [] -> return S.empty
                y:z -> do
                    writeIORef ref z
                    return y
        isrc <- mkISource src 40
        x <- replicateM 20 $ readISource isrc
        S.concat x `shouldBe` S.pack [1..20]

        y <- replicateM 40 $ readISource isrc
        S.concat y `shouldBe` S.pack [21..40]

        z <- replicateM 40 $ readSource src
        S.concat z `shouldBe` S.pack [41..50]
    it "chunkedSource" $ do
        ref <- newIORef $ "5\r\n12345\r\n3\r\n678\r\n0\r\n\r\nBLAH"
        src <- mkSource $ do
            x <- readIORef ref
            writeIORef ref S.empty
            return x
        csrc <- mkCSource src

        x <- replicateM 15 $ readCSource csrc
        S.concat x `shouldBe` "12345678"

        y <- replicateM 15 $ readSource src
        S.concat y `shouldBe` "BLAH"
    it "chunk boundaries" $ do
        ref <- newIORef
            [ "5\r\n"
            , "12345\r\n3\r"
            , "\n678\r\n0\r\n"
            , "\r\nBLAH"
            ]
        src <- mkSource $ do
            x <- readIORef ref
            case x of
                [] -> return S.empty
                y:z -> do
                    writeIORef ref z
                    return y
        csrc <- mkCSource src

        x <- replicateM 15 $ readCSource csrc
        S.concat x `shouldBe` "12345678"

        y <- replicateM 15 $ readSource src
        S.concat y `shouldBe` "BLAH"