module Faker.Combinators where
import Control.Monad
import Data.Foldable
import Data.List (sort)
import Faker
import System.Random
fromRange :: Random a => (a, a) -> Fake a
fromRange rng =
Fake
(\r ->
let (x, _) = randomR rng (getRandomGen r)
in pure x)
pickAny :: Random a => Fake a
pickAny =
Fake
(\settings ->
let (x, _) = random (getRandomGen settings)
in pure x)
suchThatMaybe :: Fake a -> (a -> Bool) -> Fake (Maybe a)
gen `suchThatMaybe` p = do
x <- gen
return $
if p x
then Just x
else Nothing
suchThat :: Fake a -> (a -> Bool) -> Fake a
gen `suchThat` p = do
mx <- gen `suchThatMaybe` p
case mx of
Just x -> return x
Nothing -> gen `suchThat` p
oneof :: Foldable t => t (Fake a) -> Fake a
oneof xs = helper
where
items = toList xs
helper =
case items of
[] -> error "Faker.Combinators.oneof should be non-empty"
xs' -> fromRange (0, length xs' - 1) >>= (items !!)
elements :: Foldable t => t a -> Fake a
elements xs =
case items of
[] -> error "Faker.Combinators.element used with empty list"
ys -> (ys !!) `fmap` fromRange (0, length xs - 1)
where
items = toList xs
listOf :: Int -> Fake a -> Fake [a]
listOf = replicateM
orderedList :: (Ord a) => Int -> Fake a -> Fake [a]
orderedList n gen = sort <$> listOf n gen
frequency :: [(Int, Fake a)] -> Fake a
frequency [] = error "Faker.Combinators.frequency used with empty list"
frequency xs0 = fromRange (1, tot) >>= (`pick` xs0)
where
tot = sum (map fst xs0)
pick n ((k, x):xs)
| n <= k = x
| otherwise = pick (n - k) xs
pick _ _ = error "Fake.pick used with empty list"
fakeEnumFromTo :: Enum a => a -> a -> Fake a
fakeEnumFromTo from to = toEnum <$> fromRange (fromEnum from, fromEnum to)
fakeBoundedEnum :: (Enum a, Bounded a) => Fake a
fakeBoundedEnum = fakeEnumFromTo minBound maxBound