module Test.LeanCheck.Function.Listable.FunListable (FunListable (..)) where
import Test.LeanCheck
import Test.LeanCheck.Tiers
import Test.LeanCheck.Utils (Nat(..), Nat2(..), Nat3(..))
import Data.Maybe (fromMaybe)
sndArgTypeOf :: b -> (a -> b -> c) -> b
x `sndArgTypeOf` _ = x
instance (FunListable a, Listable b) => Listable (a -> b) where
tiers = concatMapT mkfss funtiers
where
mkfss (n, mkf) = mapT mkf (products (replicate n tiers)
`suchThat` validResults (undefined `sndArgTypeOf` mkf))
(\+:/) :: [[a]] -> [[a]] -> [[a]]
xss \+:/ yss = xss \/ ([]:yss)
infixr 9 \+:/
class FunListable a where
validResults :: a -> [b] -> Bool
validResults x = not . invalidResults x
invalidResults :: a -> [b] -> Bool
invalidResults x = not . validResults x
funtiers :: [[ (Int, [b] -> (a -> b)) ]]
instance FunListable () where
validResults _ _ = True
funtiers = [[ (1, \[r] () -> r) ]]
instance FunListable Bool where
validResults _ _ = True
funtiers = [[ (2, \[r1,r2] b -> if b then r1 else r2) ]]
instance FunListable a => FunListable (Maybe a) where
validResults _ _ = True
funtiers = mapT (\(n, mkf) -> (n+1, \(r:rs) m -> case m of
Nothing -> r
Just x -> mkf rs x)) funtiers
instance (FunListable a, FunListable b) => FunListable (Either a b) where
validResults _ _ = True
funtiers = productWith
(\(nf, mf) (ng, mg) -> (nf + ng, \rs e -> case e of
Left x -> mf (take nf rs) x
Right y -> mg (drop nf rs) y))
funtiers
funtiers
instance (FunListable a) => FunListable [a] where
validResults _ [r1,r2] = False
validResults x (r:rs) = validResults x rs
validResults _ _ = True
funtiers = [[ (1, \[r] xs -> r) ]]
\+:/ mapT (\(n, f) -> (1 + n, \(r:rs) xs -> case xs of
[] -> r
(x:xs) -> f rs (x,xs))) funtiers
instance (FunListable a, FunListable b) => FunListable (a,b) where
validResults _ _ = True
funtiers = productWith (\(n, f) (m, g)
-> (n*m, \rs (x,y) -> toMatrix m rs
!! f [0..(n-1)] x
!! g [0..(m-1)] y))
funtiers
funtiers
toMatrix :: Int -> [a] -> [[a]]
toMatrix n [] = []
toMatrix n xs = take n xs
: toMatrix n (drop n xs)
instance FunListable Int where
funtiers = [[]]
instance FunListable Nat where
funtiers = [[]]
instance FunListable Nat2 where
funtiers = [[]]
instance FunListable Nat3 where
funtiers = [[]]