[Haskell-cafe] Quickcheck examples and Data.Word32
Joel Reymont
joelr1 at gmail.com
Thu Oct 27 11:17:45 EDT 2005
Would it cover the range between minBound :: Word32 and maxBound ::
Word32? I cannot figure out how to do this since maxBound :: Int32 is
less that that of Word32.
Also, I get the following error with ghci -fglasgow-exts
foo.hs:7:52: parse error on input `.'
--
module Foo where
import Data.Word
import Test.QuickCheck
instance Arbitrary Word32 where
arbitrary = arbitrary :: Gen Integer >>= return . fromIntegral
prop_Word32 :: Word32 -> Bool
prop_Word32 a = a == a
Thanks, Joel
On Oct 27, 2005, at 3:44 PM, Sebastian Sylvan wrote:
> Something like (untested!):
>
> instance Arbitrary Word32 where
> arbitrary = arbitrary :: Gen Integer >>= return . fromIntegral
--
http://wagerlabs.com/
More information about the Haskell-Cafe
mailing list