
For some reason the generate function is not in QC2.
Here's a quick fix:
\begin{code}
import Test.QuickCheck.Gen
import System.Random
generate :: Int -> StdGen -> Gen a -> a
generate n rnd (MkGen m) = m rnd' size
where
(size, rnd') = randomR (0, n) rnd
\end{code}
Perhaps it would be better to ask the QC maintainers to re-include
this function in the library...
/Jonas
On 3 July 2010 01:09, Antoine Latter
Including the café.
On Jul 2, 2010 8:49 AM, "Mark Wright"
wrote: Hi,
I'm trying to upgrade Hackage show to QuickCheck 2, after applying the diffs below (which may not be correct, since I am a beginner), I am left which this error message:
runghc ./Setup.hs build Preprocessing library show-0.3.4... Building show-0.3.4... [4 of 4] Compiling ShowQ ( ShowQ.hs, dist/build/ShowQ.o )
ShowQ.hs:104:20: Not in scope: `generate'
Compilation exited abnormally with code 1 at Fri Jul 2 23:07:17
The error occurs in this method:
tests :: Gen Result -> StdGen -> Int -> Int -> [[String]] -> IO String tests gen rnd0 ntest nfail stamps | ntest == 500 = done "OK, passed" ntest stamps | nfail == 1000 = done "Arguments exhausted after" ntest stamps | otherwise = case ok result of Nothing -> tests gen rnd1 ntest (nfail+1) stamps Just True -> tests gen rnd1 (ntest+1) nfail (stamp result:stamps) Just False -> return $ "Falsifiable, after " ++ show ntest ++ " tests:\n" ++ reason result where result = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen (rnd1,rnd2) = split rnd0
The QuickCheck 1 generate method is near the bottom this page:
http://hackage.haskell.org/packages/archive/QuickCheck/1.2.0.0/doc/html/Test...
but I can not find generate in QuickCheck 2. I am wondering if you have any ideas on how to fix it?
I'm trying to package lambdabot on Solaris. I have already packaged the Haskell Platform and about 90 packages, they are in:
http://pkgbuild.sourceforge.net/spec-files-extra/
Thanks very much, Mark
here are the diffs:
goanna% diff -wc show-0.3.4-orig/ShowQ.hs show-0.3.4/ShowQ.hs *** show-0.3.4-orig/ShowQ.hs Wed Jan 20 11:24:11 2010 --- show-0.3.4/ShowQ.hs Fri Jul 2 23:07:13 2010 *************** *** 12,22 **** --- 12,25 ----
import qualified Test.SmallCheck (smallCheck, Testable) import Test.QuickCheck + import Test.QuickCheck.Arbitrary import Data.Char import Data.List import Data.Word import Data.Int import System.Random + import Control.Exception (evaluate) + import Test.QuickCheck.Property (ok, stamp)
type T = [Int] type I = Int *************** *** 23,36 **** --- 26,45 ----
instance Arbitrary Char where arbitrary = choose (minBound, maxBound) + + instance CoArbitrary Char where coarbitrary c = variant (ord c `rem` 4)
instance Arbitrary Word8 where arbitrary = choose (minBound, maxBound) + + instance CoArbitrary Word8 where coarbitrary c = variant (fromIntegral ((fromIntegral c) `rem` 4))
instance Arbitrary Ordering where arbitrary = elements [LT,EQ,GT] + + instance CoArbitrary Ordering where coarbitrary LT = variant 1 coarbitrary EQ = variant 2 coarbitrary GT = variant 0 *************** *** 37,42 **** --- 46,53 ----
instance Arbitrary Int64 where arbitrary = sized $ \n -> choose (-fromIntegral n,fromIntegral n) + + instance CoArbitrary Int64 where coarbitrary n = variant (fromIntegral (if n >= 0 then 2*n else 2*(-n) + 1))
instance (Integral a, Arbitrary a) => Arbitrary (Ratio a) where *************** *** 48,53 **** --- 59,65 ---- else (b % a) else (a % b)
+ instance (Integral a, CoArbitrary a) => CoArbitrary (Ratio a) where coarbitrary m = variant (fromIntegral $ if n >= 0 then 2*n else 2*(-n) + 1) where n = numerator m
*************** *** 87,93 **** Just False -> return $ "Falsifiable, after " ++ show ntest ++ " tests:\n" ! ++ unlines (arguments result) where result = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen (rnd1,rnd2) = split rnd0 --- 99,105 ---- Just False -> return $ "Falsifiable, after " ++ show ntest ++ " tests:\n" ! ++ reason result where result = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen (rnd1,rnd2) = split rnd0 goanna%
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners