module Test.SmallCheck.Series.ByteString.Lazy
  (
  
    replicateA
  , replicate0
  , replicateW8
  
  , enumW8s
  , enumAlphabet
  , enumList
  
  , jack
  ) where
import Data.Char (ord)
import Data.List (inits)
import Data.Word (Word8)
import Data.ByteString.Lazy (ByteString, pack)
import qualified Data.ByteString.Lazy.Char8 as L8 (pack)
import Test.SmallCheck.Series
replicateA :: Series m ByteString
replicateA :: Series m ByteString
replicateA = Word8 -> Series m ByteString
forall (m :: * -> *). Word8 -> Series m ByteString
replicateW8 Word8
97
replicate0 :: Series m ByteString
replicate0 :: Series m ByteString
replicate0 = Word8 -> Series m ByteString
forall (m :: * -> *). Word8 -> Series m ByteString
replicateW8 Word8
0
replicateW8 :: Word8 -> Series m ByteString
replicateW8 :: Word8 -> Series m ByteString
replicateW8 Word8
b =
    (Depth -> [ByteString]) -> Series m ByteString
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [ByteString]) -> Series m ByteString)
-> (Depth -> [ByteString]) -> Series m ByteString
forall a b. (a -> b) -> a -> b
$ \Depth
d -> ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteString
pack ([[Word8]] -> [ByteString])
-> ([Word8] -> [[Word8]]) -> [Word8] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> [[Word8]]
forall a. [a] -> [[a]]
inits ([Word8] -> [ByteString]) -> [Word8] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ (Depth -> Word8 -> [Word8]
forall a. Depth -> a -> [a]
replicate (Depth -> Word8 -> [Word8])
-> (Depth -> Depth) -> Depth -> Word8 -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Depth -> Depth
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Depth
d Word8
b
enumW8s :: Series m ByteString
enumW8s :: Series m ByteString
enumW8s = [Word8] -> Series m ByteString
forall (m :: * -> *). [Word8] -> Series m ByteString
enumList [Word8
0..Word8
255]
enumAlphabet :: Series m ByteString
enumAlphabet :: Series m ByteString
enumAlphabet = [Word8] -> Series m ByteString
forall (m :: * -> *). [Word8] -> Series m ByteString
enumList ([Word8] -> Series m ByteString) -> [Word8] -> Series m ByteString
forall a b. (a -> b) -> a -> b
$ (Char -> Word8) -> [Char] -> [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Depth -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Depth -> Word8) -> (Char -> Depth) -> Char -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Depth
ord) [Char
'a'..Char
'z']
enumList  :: [Word8] -> Series m ByteString
enumList :: [Word8] -> Series m ByteString
enumList [Word8]
cs = (Depth -> [ByteString]) -> Series m ByteString
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [ByteString]) -> Series m ByteString)
-> (Depth -> [ByteString]) -> Series m ByteString
forall a b. (a -> b) -> a -> b
$ \Depth
d -> ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteString
pack ([[Word8]] -> [ByteString])
-> ([Word8] -> [[Word8]]) -> [Word8] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> [[Word8]]
forall a. [a] -> [[a]]
inits ([Word8] -> [ByteString]) -> [Word8] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ Depth -> [Word8] -> [Word8]
forall a. Depth -> [a] -> [a]
take Depth
d [Word8]
cs
jack :: Series m ByteString
jack :: Series m ByteString
jack = (Depth -> [ByteString]) -> Series m ByteString
forall a (m :: * -> *). (Depth -> [a]) -> Series m a
generate ((Depth -> [ByteString]) -> Series m ByteString)
-> (Depth -> [ByteString]) -> Series m ByteString
forall a b. (a -> b) -> a -> b
$ \Depth
d ->
    ([[Char]] -> ByteString) -> [[[Char]]] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Char] -> ByteString
L8.pack ([Char] -> ByteString)
-> ([[Char]] -> [Char]) -> [[Char]] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [Char]
unwords) ([[[Char]]] -> [ByteString])
-> ([Char] -> [[[Char]]]) -> [Char] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[[Char]]]
forall a. [a] -> [[a]]
inits ([[Char]] -> [[[Char]]])
-> ([Char] -> [[Char]]) -> [Char] -> [[[Char]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Depth -> [[Char]] -> [[Char]]
forall a. Depth -> [a] -> [a]
take Depth
d ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
forall a. [a] -> [a]
cycle ([[Char]] -> [[Char]])
-> ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
words ([Char] -> [ByteString]) -> [Char] -> [ByteString]
forall a b. (a -> b) -> a -> b
$
        [Char]
"All work and no play makes Jack a dull boy."