{-# LANGUAGE BangPatterns     #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Test.QuickCheck.Instances.ByteString () where

import Prelude ()
import Test.QuickCheck.Instances.CustomPrelude

import Data.Word              (Word8)
import Test.QuickCheck
import Test.QuickCheck.Gen
import Test.QuickCheck.Random (QCGen (..))

import qualified System.Random.SplitMix as SM

import qualified Data.ByteString       as BS
import qualified Data.ByteString.Lazy  as LBS
import qualified Data.ByteString.Short as SBS

-------------------------------------------------------------------------------
-- bytestring
-------------------------------------------------------------------------------

instance Arbitrary BS.ByteString where
    arbitrary :: Gen ByteString
arbitrary = (QCGen -> Int -> ByteString) -> Gen ByteString
forall a. (QCGen -> Int -> a) -> Gen a
MkGen ((QCGen -> Int -> ByteString) -> Gen ByteString)
-> (QCGen -> Int -> ByteString) -> Gen ByteString
forall a b. (a -> b) -> a -> b
$ \(QCGen SMGen
g0) Int
size ->
        if Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
        then ByteString
BS.empty
        else
            let (Int
i, SMGen
g1) = SMGen -> (Int, SMGen)
SM.nextInt SMGen
g0
                size' :: Int
size' = Int
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
size
            in (ByteString, Maybe SMGen) -> ByteString
forall a b. (a, b) -> a
fst (Int
-> (SMGen -> Maybe (Word8, SMGen))
-> SMGen
-> (ByteString, Maybe SMGen)
forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
BS.unfoldrN Int
size' SMGen -> Maybe (Word8, SMGen)
gen SMGen
g1)
      where
        gen :: SM.SMGen -> Maybe (Word8, SM.SMGen)
        gen :: SMGen -> Maybe (Word8, SMGen)
gen !SMGen
g = (Word8, SMGen) -> Maybe (Word8, SMGen)
forall a. a -> Maybe a
Just (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w64, SMGen
g')
          where
            ~(Word64
w64, SMGen
g') = SMGen -> (Word64, SMGen)
SM.nextWord64 SMGen
g

    shrink :: ByteString -> [ByteString]
shrink ByteString
xs = [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word8] -> [[Word8]]
forall a. Arbitrary a => a -> [a]
shrink (ByteString -> [Word8]
BS.unpack ByteString
xs)

instance CoArbitrary BS.ByteString where
    coarbitrary :: ByteString -> Gen b -> Gen b
coarbitrary = [Word8] -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary ([Word8] -> Gen b -> Gen b)
-> (ByteString -> [Word8]) -> ByteString -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BS.unpack

instance Function BS.ByteString where
    function :: (ByteString -> b) -> ByteString :-> b
function = (ByteString -> [Word8])
-> ([Word8] -> ByteString) -> (ByteString -> b) -> ByteString :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ByteString -> [Word8]
BS.unpack [Word8] -> ByteString
BS.pack


instance Arbitrary LBS.ByteString where
    arbitrary :: Gen ByteString
arbitrary = (QCGen -> Int -> ByteString) -> Gen ByteString
forall a. (QCGen -> Int -> a) -> Gen a
MkGen ((QCGen -> Int -> ByteString) -> Gen ByteString)
-> (QCGen -> Int -> ByteString) -> Gen ByteString
forall a b. (a -> b) -> a -> b
$ \(QCGen SMGen
g0) Int
size ->
        if Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
        then ByteString
LBS.empty
        else
            let (Int
i, SMGen
g1) = SMGen -> (Int, SMGen)
SM.nextInt SMGen
g0
                size' :: Int
size' = Int
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
size
            in ((Int, SMGen) -> Maybe (Word8, (Int, SMGen)))
-> (Int, SMGen) -> ByteString
forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
LBS.unfoldr (Int, SMGen) -> Maybe (Word8, (Int, SMGen))
gen (Int
size', SMGen
g1)
      where
        gen :: (Int, SM.SMGen) -> Maybe (Word8, (Int, SM.SMGen))
        gen :: (Int, SMGen) -> Maybe (Word8, (Int, SMGen))
gen (!Int
i, !SMGen
g)
            | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = Maybe (Word8, (Int, SMGen))
forall a. Maybe a
Nothing
            | Bool
otherwise = (Word8, (Int, SMGen)) -> Maybe (Word8, (Int, SMGen))
forall a. a -> Maybe a
Just (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w64, (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, SMGen
g'))
          where
            ~(Word64
w64, SMGen
g') = SMGen -> (Word64, SMGen)
SM.nextWord64 SMGen
g

    shrink :: ByteString -> [ByteString]
shrink ByteString
xs = [Word8] -> ByteString
LBS.pack ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word8] -> [[Word8]]
forall a. Arbitrary a => a -> [a]
shrink (ByteString -> [Word8]
LBS.unpack ByteString
xs)

instance CoArbitrary LBS.ByteString where
    coarbitrary :: ByteString -> Gen b -> Gen b
coarbitrary = [Word8] -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary ([Word8] -> Gen b -> Gen b)
-> (ByteString -> [Word8]) -> ByteString -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
LBS.unpack

instance Function LBS.ByteString where
    function :: (ByteString -> b) -> ByteString :-> b
function = (ByteString -> [Word8])
-> ([Word8] -> ByteString) -> (ByteString -> b) -> ByteString :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ByteString -> [Word8]
LBS.unpack [Word8] -> ByteString
LBS.pack


instance Arbitrary SBS.ShortByteString where
    arbitrary :: Gen ShortByteString
arbitrary = [Word8] -> ShortByteString
SBS.pack ([Word8] -> ShortByteString) -> Gen [Word8] -> Gen ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [Word8]
forall a. Arbitrary a => Gen a
arbitrary
    shrink :: ShortByteString -> [ShortByteString]
shrink ShortByteString
xs = [Word8] -> ShortByteString
SBS.pack ([Word8] -> ShortByteString) -> [[Word8]] -> [ShortByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word8] -> [[Word8]]
forall a. Arbitrary a => a -> [a]
shrink (ShortByteString -> [Word8]
SBS.unpack ShortByteString
xs)

instance CoArbitrary SBS.ShortByteString where
    coarbitrary :: ShortByteString -> Gen b -> Gen b
coarbitrary = [Word8] -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary ([Word8] -> Gen b -> Gen b)
-> (ShortByteString -> [Word8])
-> ShortByteString
-> Gen b
-> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
SBS.unpack

instance Function SBS.ShortByteString where
    function :: (ShortByteString -> b) -> ShortByteString :-> b
function = (ShortByteString -> [Word8])
-> ([Word8] -> ShortByteString)
-> (ShortByteString -> b)
-> ShortByteString :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ShortByteString -> [Word8]
SBS.unpack [Word8] -> ShortByteString
SBS.pack