I'm running into problems with generating an arbitrary function of type Double -> Double. Specifically, the following code:

{-# LANGUAGE PatternSignatures #-}
import Test.QuickCheck
import Text.Show.Functions

prop_ok (f :: Double -> Double) =
    f (-5.5) `seq` True

prop_bug (f :: Double -> Double) =
    f (-5.6) `seq` True

main = do
    putStr "prop_ok:\t"  >> quickCheck prop_ok
    putStr "prop_bug:\t" >> quickCheck prop_bug


On an Intel Core 2 Duo running Mac OS 10.5.4 with GHC 6.8.2 the output I get is

prop_ok:        OK, passed 100 tests.
prop_bug:       Test: Prelude.(!!): negative index

On Intel Xeon running RedHat with GHC 6.8.2 both tests hang.

Has anyone seen this before?  Is it fixed in QuickCheck2?

Thanks,


Patrick

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to