{- 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@] Defines /QuickCheck/-properties for "Math.Power". -} module Factory.Test.QuickCheck.Power( -- * Functions quickChecks ) where import qualified Data.List import qualified Factory.Math.Power as Math.Power import qualified Test.QuickCheck import Test.QuickCheck((==>)) -- | Defines invariant properties. quickChecks :: IO () quickChecks = Test.QuickCheck.quickCheck `mapM_` [prop_maybeSquareNumber, prop_rewriteRule] >> Test.QuickCheck.quickCheckWith Test.QuickCheck.stdArgs {Test.QuickCheck.maxSuccess = 10000} prop_notSquare >> Test.QuickCheck.quickCheck `mapM` [prop_squaresFrom, prop_isPerfectPower] >> Test.QuickCheck.quickCheck prop_raiseModulo where prop_maybeSquareNumber, prop_notSquare, prop_rewriteRule :: Integer -> Test.QuickCheck.Property prop_maybeSquareNumber i = Test.QuickCheck.label "prop_maybeSquareNumber" $ Math.Power.maybeSquareNumber (Math.Power.square i) == Just (abs i) prop_notSquare i = abs i > 0 ==> Test.QuickCheck.label "prop_notSquare" $ Math.Power.maybeSquareNumber (i ^ (10 {-promote rounding-error using big number-} :: Int) + 1) == Nothing prop_rewriteRule i = Test.QuickCheck.label "prop_rewriteRule" $ Math.Power.isPerfectPower i' == Math.Power.isPerfectPower (fromIntegral i' :: Int) where i' = abs i prop_squaresFrom, prop_isPerfectPower :: Integer -> Integer -> Test.QuickCheck.Property prop_squaresFrom from l = Test.QuickCheck.label "prop_squaresFrom" . (\(x, y) -> y == Math.Power.square x) . Data.List.genericIndex (Math.Power.squaresFrom from) $ abs l prop_isPerfectPower b e = Test.QuickCheck.label "prop_isPerfectPower" . Math.Power.isPerfectPower $ b' ^ e' where b' = 2 + (b `mod` 10) e' = 2 + (e `mod` 8) prop_raiseModulo :: Integer -> Integer -> Integer -> Test.QuickCheck.Property prop_raiseModulo b e m = m /= 0 ==> Test.QuickCheck.label "prop_raiseModulo" $ Math.Power.raiseModulo b e' m == (b ^ e') `mod` m where e' :: Integer e' = abs e