{-# language Rank2Types #-}
{-# language ScopedTypeVariables #-}
module EasyTest.Generators
(
random
, random'
, bool
, word8
, char
, int
, double
, word
, int'
, char'
, double'
, word'
, word8'
, pick
, listOf
, listsOf
, pair
, mapOf
, mapsOf
) where
import Control.Applicative
import Control.Concurrent.STM
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Reader
import Data.Map (Map)
import Data.Maybe ( fromJust )
import Data.Word
import System.Random (Random)
import qualified Data.Map as Map
import qualified System.Random as Random
import EasyTest.Internal
random :: forall a. Random a => Test a
random = do
rng <- asks envRng
liftIO . atomically $ do
rng0 <- readTVar rng
let (a :: a, rng1) = Random.random rng0
writeTVar rng rng1
pure a
random' :: Random a => a -> a -> Test a
random' lower upper = do
rng <- asks envRng
liftIO . atomically $ do
rng0 <- readTVar rng
let (a, rng1) = Random.randomR (lower,upper) rng0
writeTVar rng rng1
pure a
bool :: Test Bool
bool = random
word8 :: Test Word8
word8 = random
char :: Test Char
char = random
int :: Test Int
int = random
double :: Test Double
double = random
word :: Test Word
word = random
int' :: Int -> Int -> Test Int
int' = random'
char' :: Char -> Char -> Test Char
char' = random'
double' :: Double -> Double -> Test Double
double' = random'
word' :: Word -> Word -> Test Word
word' = random'
word8' :: Word8 -> Word8 -> Test Word8
word8' = random'
pick :: [a] -> Test a
pick as = let n = length as; ind = picker n as in do
i <- int' 0 (n - 1)
a <- pure (ind i)
pure (fromJust a)
picker :: Int -> [a] -> (Int -> Maybe a)
picker _ [] = const Nothing
picker _ [a] = \i -> if i == 0 then Just a else Nothing
picker size as = go where
lsize = size `div` 2
rsize = size - lsize
(l,r) = splitAt lsize as
lpicker = picker lsize l
rpicker = picker rsize r
go i = if i < lsize then lpicker i else rpicker (i - lsize)
listOf :: Int -> Test a -> Test [a]
listOf = replicateM
listsOf :: [Int] -> Test a -> Test [[a]]
listsOf sizes gen = sizes `forM` \n -> listOf n gen
pair :: Test a -> Test b -> Test (a,b)
pair = liftA2 (,)
mapOf :: Ord k => Int -> Test k -> Test v -> Test (Map k v)
mapOf n k v = Map.fromList <$> listOf n (pair k v)
mapsOf :: Ord k => [Int] -> Test k -> Test v -> Test [Map k v]
mapsOf sizes k v = sizes `forM` \n -> mapOf n k v