{-# LANGUAGE CPP #-}
module Test.SmallCheck.Series.ByteString
(
replicateA
, replicate0
, replicateW8
, enumW8s
, enumAlphabet
, enumList
, jack
) where
import Data.Word (Word8)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L (toStrict)
import Test.SmallCheck.Series
import qualified Test.SmallCheck.Series.ByteString.Lazy as L.Series
replicateA :: Series m ByteString
replicateA :: Series m ByteString
replicateA = ByteString -> ByteString
L.toStrict (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m ByteString
forall (m :: * -> *). Series m ByteString
L.Series.replicateA
replicate0 :: Series m ByteString
replicate0 :: Series m ByteString
replicate0 = ByteString -> ByteString
L.toStrict (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m ByteString
forall (m :: * -> *). Series m ByteString
L.Series.replicate0
replicateW8 :: Word8 -> Series m ByteString
replicateW8 :: Word8 -> Series m ByteString
replicateW8 = (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
L.toStrict (Series m ByteString -> Series m ByteString)
-> (Word8 -> Series m ByteString) -> Word8 -> Series m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Series m ByteString
forall (m :: * -> *). Word8 -> Series m ByteString
L.Series.replicateW8
enumW8s :: Series m ByteString
enumW8s :: Series m ByteString
enumW8s = ByteString -> ByteString
L.toStrict (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m ByteString
forall (m :: * -> *). Series m ByteString
L.Series.enumW8s
enumAlphabet :: Series m ByteString
enumAlphabet :: Series m ByteString
enumAlphabet = ByteString -> ByteString
L.toStrict (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m ByteString
forall (m :: * -> *). Series m ByteString
L.Series.enumAlphabet
enumList :: [Word8] -> Series m ByteString
enumList :: [Word8] -> Series m ByteString
enumList = (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
L.toStrict (Series m ByteString -> Series m ByteString)
-> ([Word8] -> Series m ByteString)
-> [Word8]
-> Series m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> Series m ByteString
forall (m :: * -> *). [Word8] -> Series m ByteString
L.Series.enumList
jack :: Series m ByteString
jack :: Series m ByteString
jack = ByteString -> ByteString
L.toStrict (ByteString -> ByteString)
-> Series m ByteString -> Series m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m ByteString
forall (m :: * -> *). Series m ByteString
L.Series.jack