I have a function with the following type signature
rndListIndex :: Double -> Double -> Double -> Double
rndListIndex maxIdx r1 r2 = …
the first input should be a value coming from a non-negative strictly positive integer
the second and third input are required to be within the closed interval [0.0,1.0] otherwise the function makes no sense
the function has the property of
prop_alwaysLessThanMaxIdx idx r1 r2 = (rndListIndex idx r1 r2 <= idx)
how do I generate random data for maxIdx and r1,r2 separately; I know of the function choosebut do not know how to use it with more than one input variable.
For now I have tested the Property with fixed idx, which is not the way it should be tested.
You have to use the forAll function from QuickCheck. It has the following type:
forAll :: (Show a, Testable prop)
=> Gen a -- ^ The generator to use for generating values
-> (a -> prop) -- ^ A function which returns a testable property
-> Property
forAll takes two arguments:
The generator describes how to generate values. Examples of generators are choose, arbitrary, oneof, ...
The function tests the property for the given input. It must return a value that is an instance of Testable, for example another Property, Bool or a function.
Example of a nested forAll with the choose and elements generators:
-- This generates a Property p for all x's in the closed interval [1,3]
-- The property p in turn generates a property q for all y ∈ [4,5]
-- The property q is True if x < y.
prop_choose = forAll (choose (1,3)) $ \x ->
forAll (elements [4,5]) $ \y -> x < y
For your test property, you can use forAll with choose for the second and third argument.
For the first argument, there is the Positive a type in QuickCheck which can be used to generate arbitrary positive values of type a (It has an Arbitrary instance when a is a Num):
prop_alwayLessThanMaxIdx :: Positive Integer -> Property
prop_alwaysLessThanMaxIdx (Positive idx) =
forAll (choose (0,1)) $ \r1 ->
forAll (choose (0,1)) $ \r2 ->
(rndListIndex idx r1 r2) < idx
I would suggest defining your own type that wraps Double and give it an Arbitrary instance that only generates numbers between 0 and 1. Something like:
import Test.QuickCheck
newtype UnitInterval = Unit Double deriving Show
instance Arbitrary UnitInterval where
arbitrary = fmap Unit (choose (0, 1))
shrink (Unit x) = [ Unit y | y <- shrink x, 0 <= y && y <= 1 ]
For generating idx, you can use QuickCheck's Positive modifier, as #bennoffs suggested (you will have to import Test.QuickCheck.Modifiers). This is similar to the UnitInterval type I defined above, but generates positive numbers instead of numbers between 0 and 1. Your property will then look like:
prop_alwaysLessThanMaxIdx (Positive idx) (Unit r1) (Unit r2) =
rndListIndex idx r1 r2 <= idx
Related
I want use quickcheck in a function that tests if a Maclaurin series is equal to 1/x, for x>1 and x<2. However, for small values of n, quickcheck returns false tests. Additionally, if I put n>100 restriction, for example, quickcheck returns:
"Gave up! Passed only 0 tests.".
Here's my code:
prop_inv :: Float -> Int -> Property
prop_inv x n = (x>1 && x<2) && n>100 ==> inv x n == 1/x
(inv x n is the function that calculates the Maclaurin series.)
The usual way is to make a small newtype that only generates values in the desired range. For example:
newtype BetweenOneAndTwo = BOAT Float deriving Show
instance Arbitrary BetweenOneAndTwo where
arbitrary = BOAT <$> Test.QuickCheck.choose (1, 2)
prop_inv (BOAT x) (NonNegative n) = inv x (n+100) == 1/x
The following data structure can be tested with the Tasty-SmallCheck related code that follows. There is a relation that has to hold with the constructor ShB: the second and the third positive integers should be at most as large as the first one.
data Shape = ShA Int Int Bool
| ShB Int Int Int Bool Bool
deriving (Show,Read,Eq)
The constructor ShA should have positive Int's but otherwise there is no relation between the parameters.
auxShA :: (Positive Int, Positive Int, Bool) -> Shape
auxShA (i,j,b) = ShA (fromIntegral i) (fromIntegral j) b
auxShB :: (Positive Int, Positive Int, Positive Int) -> Bool -> Bool -> Shape
auxShB (a1,a2,a3) = ShB i u d
where
(i,u,d) = auxTriplet (a1,a2,a3)
auxTriplet :: (Positive Int, Positive Int, Positive Int) -> (Int,Int,Int)
auxTriplet (a,b,c)
| a >= b && a >= c = (fromIntegral a, fromIntegral b, fromIntegral c)
| b >= a && b >= c = (fromIntegral b, fromIntegral a, fromIntegral c)
| otherwise = (fromIntegral c, fromIntegral a, fromIntegral b)
consB :: (Serial m a1, Serial m a2, Serial m a3, Serial m b, Serial m c) =>
((a1,a2,a3) -> b -> c -> e) -> Series m e
consB f = decDepth $
f <$> series
<~> series
<~> series
instance Monad m => Serial m Shape where
series = cons1 auxShA \/ consB auxShB
The generated cases are otherwise ok but there are duplicates that can be seen e.g. with
list 4 series :: [Shape]
The question is, how to generate the test cases with SmallCheck (tasty) when the following holds?
there are properties that has to hold, e.g. the first parameter has to Positive
what if the first parameter should be larger than 10::Int?
And continuing, what if the second parameter should between the first - 5 and the first, and the third should be between the second - 5 and the second?
Or, how to generate test cases that dynamically can depend on the previous generated values?
First thought was to write constructors to Shape that check that inputs are valid (e.g. the bullet points above), but the problem of duplicate test case generation would remain with that approach.
The above code uses similar solution as in
SmallCheck invariant -answer.
I have the following Haskell functions:
expM :: Integer -> Integer -> Integer -> Integer
expM x y = rem (x^y)
And
exMME :: Integer -> Integer -> Integer -> Integer
exMME b 0 m = 1
exMME b e m = exMME' b e m 1 0 where
exMME' b e m c e'
| e' < e = exMME' b e m ((b * c) `mod` m) (e'+1)
| otherwise = c
What I want to do is use quickCheck to compare these two functions so i can see that they produce the same answer and which one is the fastest.
To test if they have the same answers I want to let QuickCheck create random positive integers with the exception of 0. So I created a Gen:
positives :: Gen Integer
positives =
do -- Pick an arbitrary integer:
x <- arbitrary
if (x == 0)
then return 1
else if (x < 0)
then return (-x)
else
return x
This works from the command line (ghci) but I have a prop:
prop_CompareAnswerExMFM :: Integer -> Integer -> Integer -> Bool
prop_CompareAnswerExMFM b e m =exMFM b e m == exM b e m
And each time i call this with QuickCheck prop_CompareAnswerExMFM it doesn't us my gen. After reading some stuff i toughed that i needed to define a instance:
instance Arbitrary Integer where
arbitrary = positives
This doesn't work because a arbitrary instance of Integer already exist. Again after some googling I say that the standard way to solve this is to use a wrapper:
newtype Positives = Positives Integer
deriving (Eq, Ord, Show)
instance Arbitrary Positives where
arbitrary = positives
positives :: Gen Positives
positives =
do -- Pick an arbitrary integer:
x <- arbitrary
if (x == 0)
then return 1
else if (x < 0)
then return (-x)
else
return x
But after playing around i keep getting errors like can't resolve this, No instance for (Num Positives) arising from the literal '0' or Can't make a derived instance of 'Num Positives'.
I think i'm making it way to complex for what i want but I just can't figure it out. I hope someone can help me or send me in the right direction.
Thanks
The problem with your code is that in positives the variable x has type Integer, so your return statements need to include the Positives constructor:
positives :: Gen Positives
positives =
do -- Pick an arbitrary integer:
x <- arbitrary
if (x == 0)
then return $ Positives 1
else if (x < 0)
then return $ Positives (-x)
else
return $ Positives x
If it helps, here is another way to write (a similarly working) positives function:
positives' :: Gen Positives
positives' = fmap (\x -> Positives (1 + abs x)) arbitrary
Here the arbitrary call is a Gen Integer, so the function argument to fmap has type Integer -> Positives.
To use your Positives newtype with QuickCheck you would use the Positives (de-)constructor to get at the Integer values:
prop_addition :: Positives -> Positives -> Bool
prop_addition (Positives a) (Positives b) = a + b >= 2
ghci> quickCheck prop_addtion
As #Carsten mentions in the comments, QuickCheck as a Positive a type which has an arbitrary instance for numeric and ordered types a.
Here's a quick way that doesn't require much understanding of QuickCheck but is a bit of a hack:
prop_CompareAnswerExMFM :: Integer -> Integer -> Integer -> Bool
prop_CompareAnswerExMFM b e m =
exMFM absB absE absM == exM absB absE absM
where -- following guarantees args are positive integers > 0
absB = 1 + abs b
absE = 1 + abs e
absM = 1 + abs m
and then you can just use
quickCheck prop_factored
Here's a simple function. It takes an input Int and returns a (possibly empty) list of (Int, Int) pairs, where the input Int is the sum of the cubed elements of any of the pairs.
cubeDecomposition :: Int -> [(Int, Int)]
cubeDecomposition n = [(x, y) | x <- [1..m], y <- [x..m], x^3 + y^3 == n]
where m = truncate $ fromIntegral n ** (1/3)
-- cubeDecomposition 1729
-- [(1,12),(9,10)]
I want to test the property that the above is true; if I cube each element and sum any of the return tuples, then I get my input back:
import Control.Arrow
cubedElementsSumToN :: Int -> Bool
cubedElementsSumToN n = all (== n) d
where d = map (uncurry (+) . ((^3) *** (^3))) (cubeDecomposition n)
For runtime considerations, I'd like to limit the input Ints to a certain size when testing this with QuickCheck. I can define an appropriate type and Arbitrary instance:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Test.QuickCheck
newtype SmallInt = SmallInt Int
deriving (Show, Eq, Enum, Ord, Num, Real, Integral)
instance Arbitrary SmallInt where
arbitrary = fmap SmallInt (choose (-10000000, 10000000))
And then I guess I have to define versions of the function and property that use SmallInt rather than Int:
cubeDecompositionQC :: SmallInt -> [(SmallInt, SmallInt)]
cubeDecompositionQC n = [(x, y) | x <- [1..m], y <- [x..m], x^3 + y^3 == n]
where m = truncate $ fromIntegral n ** (1/3)
cubedElementsSumToN' :: SmallInt -> Bool
cubedElementsSumToN' n = all (== n) d
where d = map (uncurry (+) . ((^3) *** (^3))) (cubeDecompositionQC n)
-- cubeDecompositionQC 1729
-- [(SmallInt 1,SmallInt 12),(SmallInt 9,SmallInt 10)]
This works fine, and the standard 100 tests pass as expected. But it seems unnecessary to define a new type, instance, and function when all I really need is a custom generator. So I tried this:
smallInts :: Gen Int
smallInts = choose (-10000000, 10000000)
cubedElementsSumToN'' :: Int -> Property
cubedElementsSumToN'' n = forAll smallInts $ \m -> all (== n) (d m)
where d = map (uncurry (+) . ((^3) *** (^3)))
. cubeDecomposition
Now, the first few times I ran this, everything worked fine, and all tests pass. But on subsequent runs I observed failures. Bumping up the test size reliably finds one:
*** Failed! Falsifiable (after 674 tests and 1 shrink):
0
8205379
I'm a bit confused here due to the presence of two shrunken inputs - 0 and 8205379 - returned from QuickCheck, where I would intuitively expect one. Also, those inputs work as predicted (on my show-able property, at least):
*Main> cubedElementsSumToN 0
True
*Main> cubedElementsSumToN 8205379
True
So it seems like obviously there's a problem in the property that uses the custom Gen I defined.
What have I done wrong?
I quickly realized that the property as I've written it is obviously incorrect. Here's the proper way to do it, using the original cubedElementsSumToN property:
quickCheck (forAll smallInts cubedElementsSumToN)
which reads quite naturally.
So I'm writing a program which returns a procedure for some given arithmetic problem, so I wanted to instance a couple of functions to Show so that I can print the same expression I evaluate when I test. The trouble is that the given code matches (-) to the first line when it should fall to the second.
{-# OPTIONS_GHC -XFlexibleInstances #-}
instance Show (t -> t-> t) where
show (+) = "plus"
show (-) = "minus"
main = print [(+),(-)]
returns
[plus,plus]
Am I just committing a mortal sin printing functions in the first place or is there some way I can get it to match properly?
edit:I realise I am getting the following warning:
Warning: Pattern match(es) are overlapped
In the definition of `show': show - = ...
I still don't know why it overlaps, or how to stop it.
As sepp2k and MtnViewMark said, you can't pattern match on the value of identifiers, only on constructors and, in some cases, implicit equality checks. So, your instance is binding any argument to the identifier, in the process shadowing the external definition of (+). Unfortunately, this means that what you're trying to do won't and can't ever work.
A typical solution to what you want to accomplish is to define an "arithmetic expression" algebraic data type, with an appropriate show instance. Note that you can make your expression type itself an instance of Num, with numeric literals wrapped in a "Literal" constructor, and operations like (+) returning their arguments combined with a constructor for the operation. Here's a quick, incomplete example:
data Expression a = Literal a
| Sum (Expression a) (Expression a)
| Product (Expression a) (Expression a)
deriving (Eq, Ord, Show)
instance (Num a) => Num (Expression a) where
x + y = Sum x y
x * y = Product x y
fromInteger x = Literal (fromInteger x)
evaluate (Literal x) = x
evaluate (Sum x y) = evaluate x + evaluate y
evaluate (Product x y) = evaluate x * evaluate y
integer :: Integer
integer = (1 + 2) * 3 + 4
expr :: Expression Integer
expr = (1 + 2) * 3 + 4
Trying it out in GHCi:
> integer
13
> evaluate expr
13
> expr
Sum (Product (Sum (Literal 1) (Literal 2)) (Literal 3)) (Literal 4)
Here's a way to think about this. Consider:
answer = 42
magic = 3
specialName :: Int -> String
specialName answer = "the answer to the ultimate question"
specialName magic = "the magic number"
specialName x = "just plain ol' " ++ show x
Can you see why this won't work? answer in the pattern match is a variable, distinct from answer at the outer scope. So instead, you'd have to write this like:
answer = 42
magic = 3
specialName :: Int -> String
specialName x | x == answer = "the answer to the ultimate question"
specialName x | x == magic = "the magic number"
specialName x = "just plain ol' " ++ show x
In fact, this is just what is going on when you write constants in a pattern. That is:
digitName :: Bool -> String
digitName 0 = "zero"
digitName 1 = "one"
digitName _ = "math is hard"
gets converted by the compiler to something equivalent to:
digitName :: Bool -> String
digitName x | x == 0 = "zero"
digitName x | x == 1 = "one"
digitName _ = "math is hard"
Since you want to match against the function bound to (+) rather than just bind anything to the symbol (+), you'd need to write your code as:
instance Show (t -> t-> t) where
show f | f == (+) = "plus"
show f | f == (-) = "minus"
But, this would require that functions were comparable for equality. And that is an undecidable problem in general.
You might counter that you are just asking the run-time system to compare function pointers, but at the language level, the Haskell programmer doesn't have access to pointers. In other words, you can't manipulate references to values in Haskell(*), only values themselves. This is the purity of Haskell, and gains referential transparency.
(*) MVars and other such objects in the IO monad are another matter, but their existence doesn't invalidate the point.
It overlaps because it treats (+) simply as a variable, meaning on the RHS the identifier + will be bound to the function you called show on.
There is no way to pattern match on functions the way you want.
Solved it myself with a mega hack.
instance (Num t) => Show (t -> t-> t) where
show op =
case (op 6 2) of
8 -> "plus"
4 -> "minus"
12 -> "times"
3 -> "divided"