File: HuffmanSpec.hs

package info (click to toggle)
haskell-http2 5.0.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 55,180 kB
  • sloc: haskell: 8,657; makefile: 5
file content (71 lines) | stat: -rw-r--r-- 2,264 bytes parent folder | download
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
68
69
70
71
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

module HPACK.HuffmanSpec where

#if __GLASGOW_HASKELL__ < 709
import Control.Applicative ((<$>))
#endif
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Char8 as BS
import Data.Char (toLower)
import Network.HPACK
import Network.HPACK.Internal
import Test.Hspec
import Test.Hspec.QuickCheck

testData :: [(ByteString, ByteString)]
testData =
    [ ("", "")
    , ("www.example.com", "f1e3c2e5f23a6ba0ab90f4ff")
    , ("no-cache", "a8eb10649cbf")
    , ("custom-key", "25a849e95ba97d7f")
    , ("custom-value", "25a849e95bb8e8b4bf")
    , ("private", "aec3771a4b")
    ,
        ( "Mon, 21 Oct 2013 20:13:21 GMT"
        , "d07abe941054d444a8200595040b8166e082a62d1bff"
        )
    , ("https://www.example.com", "9d29ad171863c78f0b97c8e9ae82ae43d3")
    ,
        ( "Mon, 21 Oct 2013 20:13:22 GMT"
        , "d07abe941054d444a8200595040b8166e084a62d1bff"
        )
    , ("gzip", "9bd9ab")
    ,
        ( "foo=ASDJKHQKBZXOQWEOPIUAXQWEOIU; max-age=3600; version=1"
        , "94e7821dd7f2e6c7b335dfdfcd5b3960d5af27087f3672c1ab270fb5291f9587316065c003ed4ee5b1063d5007"
        )
    ]

shouldBeEncoded :: ByteString -> ByteString -> Expectation
shouldBeEncoded inp out = do
    out' <- BS.map toLower . B16.encode <$> encodeHuffman inp
    out' `shouldBe` out

shouldBeDecoded :: ByteString -> ByteString -> Expectation
shouldBeDecoded inp out = do
    out' <- decodeHuffman $ B16.decodeLenient inp
    out' `shouldBe` out

tryDecode :: ByteString -> IO ByteString
tryDecode inp = decodeHuffman $ B16.decodeLenient inp

spec :: Spec
spec = do
    describe "encode and decode" $ do
        prop "duality" $ \cs -> do
            let bs = BS.pack cs
            es <- encodeHuffman bs
            ds <- decodeHuffman es
            ds `shouldBe` bs
    describe "encode" $ do
        it "encodes" $ do
            mapM_ (\(x, y) -> x `shouldBeEncoded` y) testData
    describe "decode" $ do
        it "decodes" $ do
            tryDecode "ff" `shouldThrow` (== TooLongEos)
            tryDecode "ffffeaff" `shouldThrow` (== TooLongEos)
            "ffffea" `shouldBeDecoded` "\9"
            mapM_ (\(x, y) -> y `shouldBeDecoded` x) testData