
On 10/27/05, Joel Reymont
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 `.'
Okay, try this then: import Data.Word import Test.QuickCheck instance Arbitrary Word32 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word32) mn = fromIntegral (minBound :: Word32) c <- choose (mx, mn) return (fromIntegral c) That really should work. However the following will work too instance Arbitrary Word32 where arbitrary = do c <- arbitrary :: Gen Integer return (fromIntegral c) Though I'm not sure of the range and distribution of the generated Word32's (since it would depend on how fromIntegral behaves transforming an Integer to a Word32 when the Integer is larger than maxBound::Word32). /S
-- 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
-- Sebastian Sylvan +46(0)736-818655 UIN: 44640862