{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- Copyright (C) 2011 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Implements 'Test.QuickCheck.Arbitrary' and defines /QuickCheck/-properties for "Math.Implementations.Primes". -} module Factory.Test.QuickCheck.Primes( -- * Functions quickChecks, -- isPrime, upperBound ) where import Control.Applicative((<$>)) import qualified Control.DeepSeq import qualified Data.Set import qualified Factory.Math.Implementations.Primality as Math.Implementations.Primality import qualified Factory.Math.Implementations.PrimeFactorisation as Math.Implementations.PrimeFactorisation import qualified Factory.Math.Implementations.Primes as Math.Implementations.Primes import qualified Factory.Math.Primality as Math.Primality import qualified Factory.Math.Primes as Math.Primes import qualified Test.QuickCheck import Test.QuickCheck((==>)) import qualified ToolShed.Defaultable as Defaultable instance Test.QuickCheck.Arbitrary Math.Implementations.Primes.Algorithm where arbitrary = Test.QuickCheck.oneof [ return Math.Implementations.Primes.TurnersSieve, Math.Implementations.Primes.TrialDivision . (`mod` 10) <$> Test.QuickCheck.arbitrary, Math.Implementations.Primes.SieveOfEratosthenes . (`mod` 10) <$> Test.QuickCheck.arbitrary ] #if !(MIN_VERSION_QuickCheck(2,1,0)) coarbitrary = undefined --CAVEAT: stops warnings from ghc. #endif isPrime :: (Control.DeepSeq.NFData i, Integral i) => i -> Bool isPrime = Math.Primality.isPrime primalityAlgorithm where primalityAlgorithm :: Math.Implementations.Primality.Algorithm Math.Implementations.PrimeFactorisation.Algorithm primalityAlgorithm = Defaultable.defaultValue upperBound :: Math.Implementations.Primes.Algorithm -> Int -> Int upperBound algorithm i = mod i $ if algorithm == Math.Implementations.Primes.TurnersSieve then 8192 else 65536 -- | Defines invariant properties. quickChecks :: IO () quickChecks = Test.QuickCheck.quickCheck `mapM_` [prop_isPrime, prop_isComposite] >> Test.QuickCheck.quickCheck prop_consistency where prop_isPrime, prop_isComposite :: Math.Implementations.Primes.Algorithm -> Int -> Test.QuickCheck.Property prop_isPrime algorithm i = Test.QuickCheck.label "prop_isPrime" . all isPrime . takeWhile (<= (upperBound algorithm i)) $ (Math.Primes.primes algorithm :: [Int]) prop_isComposite algorithm i = Test.QuickCheck.label "prop_isComposite" . not . any isPrime . Data.Set.toList . Data.Set.difference ( Data.Set.fromList [2 .. upperBound algorithm i] ) . Data.Set.fromList . takeWhile (<= (upperBound algorithm i)) $ Math.Primes.primes algorithm prop_consistency :: Math.Implementations.Primes.Algorithm -> Math.Implementations.Primes.Algorithm -> Int -> Test.QuickCheck.Property prop_consistency l r i = l /= r ==> Test.QuickCheck.label "prop_consistency" . and . take (i `mod` 4096) $ zipWith (==) (Math.Primes.primes l) (Math.Primes.primes r :: [Int])