{-# OPTIONS_GHC -Wall #-} -- Properties.hs is modified from Brent Yorgey's file of the same name -- for his package Data.List.Split module Properties where import Data.Complex.Cyclotomic import Test.QuickCheck import Test.SmallCheck import Control.Monad import Text.Printf import Examples main :: IO () main = do results <- mapM (\(s,t) -> printf "%-40s" s >> t) tests when (not . all isSuccess $ results) $ fail "Not all tests passed!" where isSuccess (Success{}) = True isSuccess _ = False qc si su x = quickCheckWithResult (stdArgs { maxSize = si, maxSuccess = su }) x tests = [ ("square of sqrtRat", qc 15 15 prop_square_sqrtRat) , ("dftInv . dft", qc 30 15 prop_dftInv_dft) , ("dft . dftInv", qc 30 15 prop_dft_dftInv) ] two :: Integer two = 2 prop_square_sqrtRat :: Int -> Bool prop_square_sqrtRat n = sqrtRat (fromIntegral n) ^ two == fromIntegral n prop_dftInv_dft :: [Rational] -> Bool prop_dftInv_dft rs = dftInv (dft cs) == cs where cs = map fromRational rs prop_dft_dftInv :: [Rational] -> Bool prop_dft_dftInv rs = dft (dftInv cs) == cs where cs = map fromRational rs smallCheckTests :: IO () smallCheckTests = smallCheck 10 prop_square_sqrtRat -- smallCheck 10 prop_dftInv_dft >> -- smallCheck 10 prop_dft_dftInv