File: Properties.hs

package info (click to toggle)
haskell-zstd 0.1.3.0-2
  • links: PTS, VCS
  • area: main
  • in suites: sid, trixie
  • size: 1,992 kB
  • sloc: ansic: 26,812; haskell: 1,085; makefile: 7
file content (69 lines) | stat: -rw-r--r-- 2,431 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
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in
-- the LICENSE file in the root directory of this source tree. An
-- additional grant of patent rights can be found in the PATENTS file
-- in the same directory.

{-# LANGUAGE OverloadedStrings #-}

module Properties
    (
      tests
    ) where

import Codec.Compression.Zstd
import qualified Codec.Compression.Zstd.Lazy as L
import qualified Codec.Compression.Zstd.Streaming as S
import Codec.Compression.Zstd.Streaming (Result(..))
import Data.ByteString (ByteString, pack, unpack)
import System.IO.Unsafe (unsafePerformIO)
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck
import qualified Control.Exception as E
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as L
import QuickCheckUtils

dict = unsafePerformIO $ do
  training0 <- B8.lines <$> B.readFile "tests/Properties.hs"
  let training = concat (replicate 20 training0)
  case trainFromSamples 1000 training of
    Left e -> do
        print e
        error e
    Right d -> return d

t_rechunk cs bs = L.toStrict (rechunk cs bs) == bs

t_roundtrip (CLevel n) (NE s) = decompress (compress n s) == Decompress s

t_dict_roundtrip (CLevel n) (NE s) =
  decompressUsingDict dict (compressUsingDict dict n s) == Decompress s

t_lazy_roundtrip (CLevel n) cs s =
  L.decompress (L.compress n (rechunk cs s)) == L.fromStrict s

-- Two lazy representations of an input compress to the same result.
t_lazy_compress_equiv (CLevel n) = unsquare $ \cs ds s ->
  L.compress n (rechunk cs s) == L.compress n (rechunk ds s)

t_stream_lazy_compress (CLevel n) = unsquare $ \cs ds s ->
  L.fromChunks (stream (S.compress n) cs s) == L.compress n (rechunk ds s)

t_stream_roundtrip (CLevel n) cs s =
  (B.concat . stream S.decompress cs . L.toStrict . L.compress n . L.fromStrict) s == s

tests :: Test
tests = testGroup "properties" [
    testProperty "rechunk" t_rechunk
  , testProperty "roundtrip" t_roundtrip
  , testProperty "dict_roundtrip" t_dict_roundtrip
  , testProperty "lazy_roundtrip" t_lazy_roundtrip
  , testProperty "lazy_compress_equiv" t_lazy_compress_equiv
  , testProperty "stream_lazy_compress" t_stream_lazy_compress
  , testProperty "stream_roundtrip" t_stream_roundtrip
  ]