summaryrefslogtreecommitdiff
path: root/test.hs
blob: a8780ff460c1ab0756c49d247ead89b4af724c65 (plain)
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
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import qualified Data.ByteString.Char8 as B
import Data.FastQ
import Data.Function
import qualified Streamly.Data.Fold as F
import qualified Streamly.Data.Stream as S
import qualified Streamly.Data.Unfold as U
import Test.QuickCheck
import Test.QuickCheck.Arbitrary
import Test.QuickCheck.Monadic
import Prelude hiding (Read)

instance Arbitrary Read where
  arbitrary = Read <$> genStr <*> genStr <*> genStr
    where
      genBS = fmap B.pack . listOf . elements
      genStr = genBS $ [' ' .. '*'] ++ [',' .. '?'] ++ ['A' .. '~']

main :: IO ()
main = quickCheckWith stdArgs {maxSuccess = 10000} $ \rp -> monadicIO $ do
  rp' <- run $ do
    S.unfold U.fromList rp & unparse "a" "b"
    cnt <- B.readFile "a"
    B.writeFile "a" $ cnt <> cnt
    cnt <- B.readFile "b"
    B.writeFile "b" $ cnt <> cnt
    parse "a" "b" & S.fold F.toList
  assert $ rp <> rp == rp'