module Test.SmallCheck.Series (
cons0, cons1, cons2, cons3, cons4, newtypeCons,
alts0, alts1, alts2, alts3, alts4, newtypeAlts,
Depth, Series, Serial(..), CoSerial(..),
Positive(..), NonNegative(..), NonEmpty(..),
(\/), (><), (<~>), (>>-),
localDepth,
decDepth,
getDepth,
generate,
list,
listM,
fixDepth,
decDepthChecked,
constM
) where
import Control.Monad.Logic
import Control.Monad.Reader
import Control.Applicative
import Control.Monad.Identity
import Data.List
import Data.Ratio
import Test.SmallCheck.SeriesMonad
import GHC.Generics
--{{{
class Monad m => Serial m a where
series :: Series m a
default series :: (Generic a, GSerial m (Rep a)) => Series m a
series = to <$> gSeries
class Monad m => CoSerial m a where
coseries :: Series m b -> Series m (a->b)
default coseries :: (Generic a, GCoSerial m (Rep a)) => Series m b -> Series m (a->b)
coseries rs = (. from) <$> gCoseries rs
generate :: (Depth -> [a]) -> Series m a
generate f = do
d <- getDepth
msum $ map return $ f d
suchThat :: Series m a -> (a -> Bool) -> Series m a
suchThat s p = s >>= \x -> if p x then pure x else empty
list :: Depth -> Series Identity a -> [a]
list d s = runIdentity $ observeAllT $ runSeries d s
listM :: Monad m => Depth -> Series m a -> m [a]
listM d s = observeAllT $ runSeries d s
infixr 7 \/
(\/) :: Monad m => Series m a -> Series m a -> Series m a
(\/) = interleave
infixr 8 ><
(><) :: Monad m => Series m a -> Series m b -> Series m (a,b)
a >< b = (,) <$> a <~> b
infixl 4 <~>
(<~>) :: Monad m => Series m (a -> b) -> Series m a -> Series m b
a <~> b = a >>- (<$> b)
uncurry3 :: (a->b->c->d) -> ((a,b,c)->d)
uncurry3 f (x,y,z) = f x y z
uncurry4 :: (a->b->c->d->e) -> ((a,b,c,d)->e)
uncurry4 f (w,x,y,z) = f w x y z
getDepth :: Series m Depth
getDepth = Series ask
localDepth :: (Depth -> Depth) -> Series m a -> Series m a
localDepth f (Series a) = Series $ local f a
decDepth :: Series m a -> Series m a
decDepth a = do
checkDepth
localDepth (subtract 1) a
checkDepth :: Series m ()
checkDepth = do
d <- getDepth
guard $ d > 0
constM :: Monad m => m b -> m (a -> b)
constM = liftM const
fixDepth :: Series m a -> Series m (Series m a)
fixDepth s = getDepth >>= \d -> return $ localDepth (const d) s
decDepthChecked :: Series m a -> Series m a -> Series m a
decDepthChecked b r = do
d <- getDepth
if d <= 0
then b
else decDepth r
unwind :: MonadLogic m => m a -> m [a]
unwind a =
msplit a >>=
maybe (return []) (\(x,a') -> (x:) `liftM` unwind a')
cons0 :: a -> Series m a
cons0 x = decDepth $ pure x
cons1 :: Serial m a => (a->b) -> Series m b
cons1 f = decDepth $ f <$> series
newtypeCons :: Serial m a => (a->b) -> Series m b
newtypeCons f = f <$> series
cons2 :: (Serial m a, Serial m b) => (a->b->c) -> Series m c
cons2 f = decDepth $ f <$> series <~> series
cons3 :: (Serial m a, Serial m b, Serial m c) =>
(a->b->c->d) -> Series m d
cons3 f = decDepth $
f <$> series
<~> series
<~> series
cons4 :: (Serial m a, Serial m b, Serial m c, Serial m d) =>
(a->b->c->d->e) -> Series m e
cons4 f = decDepth $
f <$> series
<~> series
<~> series
<~> series
alts0 :: Series m a -> Series m a
alts0 s = s
alts1 :: CoSerial m a => Series m b -> Series m (a->b)
alts1 rs = do
rs <- fixDepth rs
decDepthChecked (constM rs) (coseries rs)
alts2
:: (CoSerial m a, CoSerial m b)
=> Series m c -> Series m (a->b->c)
alts2 rs = do
rs <- fixDepth rs
decDepthChecked
(constM $ constM rs)
(coseries $ coseries rs)
alts3 :: (CoSerial m a, CoSerial m b, CoSerial m c) =>
Series m d -> Series m (a->b->c->d)
alts3 rs = do
rs <- fixDepth rs
decDepthChecked
(constM $ constM $ constM rs)
(coseries $ coseries $ coseries rs)
alts4 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) =>
Series m e -> Series m (a->b->c->d->e)
alts4 rs = do
rs <- fixDepth rs
decDepthChecked
(constM $ constM $ constM $ constM rs)
(coseries $ coseries $ coseries $ coseries rs)
newtypeAlts :: CoSerial m a => Series m b -> Series m (a->b)
newtypeAlts = coseries
class GSerial m f where
gSeries :: Series m (f a)
class GCoSerial m f where
gCoseries :: Series m b -> Series m (f a -> b)
instance GSerial m f => GSerial m (M1 i c f) where
gSeries = M1 <$> gSeries
instance GCoSerial m f => GCoSerial m (M1 i c f) where
gCoseries rs = (. unM1) <$> gCoseries rs
instance Serial m c => GSerial m (K1 i c) where
gSeries = K1 <$> series
instance CoSerial m c => GCoSerial m (K1 i c) where
gCoseries rs = (. unK1) <$> coseries rs
instance GSerial m U1 where
gSeries = pure U1
instance GCoSerial m U1 where
gCoseries rs = constM rs
instance (Monad m, GSerial m a, GSerial m b) => GSerial m (a :*: b) where
gSeries = (:*:) <$> gSeries <~> gSeries
instance (Monad m, GCoSerial m a, GCoSerial m b) => GCoSerial m (a :*: b) where
gCoseries rs = uncur <$> gCoseries (gCoseries rs)
where
uncur f (x :*: y) = f x y
instance (Monad m, GSerial m a, GSerial m b) => GSerial m (a :+: b) where
gSeries = (L1 <$> gSeries) `interleave` (R1 <$> gSeries)
instance (Monad m, GCoSerial m a, GCoSerial m b) => GCoSerial m (a :+: b) where
gCoseries rs =
gCoseries rs >>- \f ->
gCoseries rs >>- \g ->
return $
\e -> case e of
L1 x -> f x
R1 y -> g y
instance GSerial m f => GSerial m (C1 c f) where
gSeries = M1 <$> decDepth gSeries
instance Monad m => Serial m () where
series = return ()
instance Monad m => CoSerial m () where
coseries rs = constM rs
instance Monad m => Serial m Int where
series =
generate (\d -> if d >= 0 then pure 0 else empty) <|>
nats `interleave` (fmap negate nats)
where
nats = generate $ \d -> [1..d]
instance Monad m => CoSerial m Int where
coseries rs =
alts0 rs >>- \z ->
alts1 rs >>- \f ->
alts1 rs >>- \g ->
return $ \i -> case () of { _
| i > 0 -> f (N (i 1))
| i < 0 -> g (N (abs i 1))
| otherwise -> z
}
instance Monad m => Serial m Integer where
series = (toInteger :: Int -> Integer) <$> series
instance Monad m => CoSerial m Integer where
coseries rs = (. (fromInteger :: Integer->Int)) <$> coseries rs
newtype N a = N a deriving (Eq, Ord, Real, Enum, Num, Integral)
instance (Integral a, Serial m a) => Serial m (N a) where
series = generate $ \d -> map (N . fromIntegral) [0..d]
instance (Integral a, Monad m) => CoSerial m (N a) where
coseries rs =
alts0 rs >>- \z ->
alts1 rs >>- \f ->
return $ \(N i) ->
if i > 0
then f (N $ i1)
else z
instance Monad m => Serial m Float where
series =
series >>- \(sig, exp) ->
guard (odd sig || sig==0 && exp==0) >>
return (encodeFloat sig exp)
instance Monad m => CoSerial m Float where
coseries rs =
coseries rs >>- \f ->
return $ f . decodeFloat
instance Monad m => Serial m Double where
series = (realToFrac :: Float -> Double) <$> series
instance Monad m => CoSerial m Double where
coseries rs =
(. (realToFrac :: Double -> Float)) <$> coseries rs
instance (Integral i, Serial m i) => Serial m (Ratio i) where
series = pairToRatio <$> series
where
pairToRatio (n, Positive d) = n % d
instance (Integral i, CoSerial m i) => CoSerial m (Ratio i) where
coseries rs = (. ratioToPair) <$> coseries rs
where
ratioToPair r = (numerator r, denominator r)
instance Monad m => Serial m Char where
series = generate $ \d -> take (d+1) ['a'..'z']
instance Monad m => CoSerial m Char where
coseries rs =
coseries rs >>- \f ->
return $ \c -> f (N (fromEnum c fromEnum 'a'))
instance (Serial m a, Serial m b) => Serial m (a,b) where
series = cons2 (,)
instance (CoSerial m a, CoSerial m b) => CoSerial m (a,b) where
coseries rs = uncurry <$> alts2 rs
instance (Serial m a, Serial m b, Serial m c) => Serial m (a,b,c) where
series = cons3 (,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c) => CoSerial m (a,b,c) where
coseries rs = uncurry3 <$> alts3 rs
instance (Serial m a, Serial m b, Serial m c, Serial m d) => Serial m (a,b,c,d) where
series = cons4 (,,,)
instance (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) => CoSerial m (a,b,c,d) where
coseries rs = uncurry4 <$> alts4 rs
instance Monad m => Serial m Bool where
series = cons0 True \/ cons0 False
instance Monad m => CoSerial m Bool where
coseries rs =
rs >>- \r1 ->
rs >>- \r2 ->
return $ \x -> if x then r1 else r2
instance (Serial m a) => Serial m (Maybe a) where
series = cons0 Nothing \/ cons1 Just
instance (CoSerial m a) => CoSerial m (Maybe a) where
coseries rs =
maybe <$> alts0 rs <~> alts1 rs
instance (Serial m a, Serial m b) => Serial m (Either a b) where
series = cons1 Left \/ cons1 Right
instance (CoSerial m a, CoSerial m b) => CoSerial m (Either a b) where
coseries rs =
either <$> alts1 rs <~> alts1 rs
instance Serial m a => Serial m [a] where
series = cons0 [] \/ cons2 (:)
instance CoSerial m a => CoSerial m [a] where
coseries rs =
alts0 rs >>- \y ->
alts2 rs >>- \f ->
return $ \xs -> case xs of [] -> y; x:xs' -> f x xs'
instance (CoSerial m a, Serial m b) => Serial m (a->b) where
series = coseries series
instance (Serial m a, CoSerial m a, Serial m b, CoSerial m b) => CoSerial m (a->b) where
coseries r = do
args <- unwind series
g <- nest r args
return $ \f -> g $ map f args
where
nest :: forall a b m c . (Serial m b, CoSerial m b) => Series m c -> [a] -> Series m ([b] -> c)
nest rs args = do
case args of
[] -> const `liftM` rs
_:rest -> do
let sf = coseries $ nest rs rest
f <- sf
return $ \(b:bs) -> f b bs
instance (Serial Identity a, Show a, Show b) => Show (a->b) where
show f =
if maxarheight == 1
&& sumarwidth + length ars * length "->;" < widthLimit then
"{"++(
concat $ intersperse ";" $ [a++"->"++r | (a,r) <- ars]
)++"}"
else
concat $ [a++"->\n"++indent r | (a,r) <- ars]
where
ars = take lengthLimit [ (show x, show (f x))
| x <- list depthLimit series ]
maxarheight = maximum [ max (height a) (height r)
| (a,r) <- ars ]
sumarwidth = sum [ length a + length r
| (a,r) <- ars]
indent = unlines . map (" "++) . lines
height = length . lines
(widthLimit,lengthLimit,depthLimit) = (80,20,3)::(Int,Int,Depth)
newtype Positive a = Positive { getPositive :: a }
deriving (Eq, Ord, Num, Integral, Real, Enum)
instance (Num a, Ord a, Serial m a) => Serial m (Positive a) where
series = Positive <$> series `suchThat` (> 0)
instance Show a => Show (Positive a) where
showsPrec n (Positive x) = showsPrec n x
newtype NonNegative a = NonNegative { getNonNegative :: a }
deriving (Eq, Ord, Num, Integral, Real, Enum)
instance (Num a, Ord a, Serial m a) => Serial m (NonNegative a) where
series = NonNegative <$> series `suchThat` (>= 0)
instance Show a => Show (NonNegative a) where
showsPrec n (NonNegative x) = showsPrec n x
newtype NonEmpty a = NonEmpty { getNonEmpty :: [a] }
instance (Serial m a) => Serial m (NonEmpty a) where
series = NonEmpty <$> cons2 (:)
instance Show a => Show (NonEmpty a) where
showsPrec n (NonEmpty x) = showsPrec n x