
Folks, Does anyone have QuickCheck examples they could send me? Also, how can I check Word32, Word64, etc. properties? It looks like the built-in random generator only works with Int values and for the life of me I cannot figure out how to extend it. Last but not least, I'm trying to figure out how I can use QuickCheck with tests against a network server. I would want to make sure that a certain packet sequence always produces a particular packet sequence in response. Is this a good area to apply QC? Thanks, Joel -- http://wagerlabs.com/

On 10/27/05, Joel Reymont
Folks,
Does anyone have QuickCheck examples they could send me?
Also, how can I check Word32, Word64, etc. properties? It looks like the built-in random generator only works with Int values and for the life of me I cannot figure out how to extend it.
Something like (untested!): instance Arbitrary Word32 where arbitrary = arbitrary :: Gen Integer >>= return . fromIntegral -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

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

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

On 10/27/05, Sebastian Sylvan
On 10/27/05, Joel Reymont
wrote: 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)
Sorry, indentation got screwed up there... 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)

Is there a way to squeeze this boilerplate code? class Arbitrary instance Arbitrary Word16 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word16) mn = fromIntegral (minBound :: Word16) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented" 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) coarbitrary a = error "Not implemented" instance Arbitrary Word64 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word64) mn = fromIntegral (minBound :: Word64) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented" On Oct 27, 2005, at 5:35 PM, Sebastian Sylvan wrote:
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)

I came up with this but can it be done better? I'm wishing for "default class methods" :-). instance Arbitrary Word16 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented" instance Arbitrary Word32 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented" instance Arbitrary Word64 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented" arbitraryBound :: forall a.(Integral a, Bounded a) => Gen a arbitraryBound = do let mx,mn :: Integer mx = fromIntegral (maxBound :: a) mn = fromIntegral (minBound :: a) c <- choose (mx, mn) return (fromIntegral c) On Oct 27, 2005, at 6:13 PM, Joel Reymont wrote:
Is there a way to squeeze this boilerplate code?
class Arbitrary instance Arbitrary Word16 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word16) mn = fromIntegral (minBound :: Word16) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented"
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) coarbitrary a = error "Not implemented"
instance Arbitrary Word64 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word64) mn = fromIntegral (minBound :: Word64) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented"

How about this? class ArbitraryDefault a where {} instance (Integral a, Bounded a, ArbitraryDefault a) => Arbitrary a where arbitrary = arbitraryBound coarbitrary a = error "Not implemented" instance ArbitraryDefault Word16 instance ArbitraryDefault Word32 instance ArbitraryDefault Word64 arbitraryBound :: forall a.(Integral a, Bounded a) => Gen a arbitraryBound = do let mx,mn :: Integer mx = fromIntegral (maxBound :: a) mn = fromIntegral (minBound :: a) c <- choose (mx, mn) return (fromIntegral c) Joel Reymont wrote:
I came up with this but can it be done better? I'm wishing for "default class methods" :-).
instance Arbitrary Word16 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented"
instance Arbitrary Word32 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented"
instance Arbitrary Word64 where arbitrary = arbitraryBound coarbitrary a = error "Not implemented"
arbitraryBound :: forall a.(Integral a, Bounded a) => Gen a arbitraryBound = do let mx,mn :: Integer mx = fromIntegral (maxBound :: a) mn = fromIntegral (minBound :: a) c <- choose (mx, mn) return (fromIntegral c)
On Oct 27, 2005, at 6:13 PM, Joel Reymont wrote:
Is there a way to squeeze this boilerplate code?
class Arbitrary instance Arbitrary Word16 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word16) mn = fromIntegral (minBound :: Word16) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented"
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) coarbitrary a = error "Not implemented"
instance Arbitrary Word64 where arbitrary = do let mx,mn :: Integer mx = fromIntegral (maxBound :: Word64) mn = fromIntegral (minBound :: Word64) c <- choose (mx, mn) return (fromIntegral c) coarbitrary a = error "Not implemented"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This requires {-# OPTIONS_GHC -fallow-undecidable-instances #-} but since I'm using -fglasgow-exts in a lot of places I'm wondering if adding undecidable instances would be a bad habit. I guess not... not until I shoot myself in the foot :-). Any explanation of undecidable instances, the good and the bad? Joel On Oct 27, 2005, at 6:49 PM, Bryn Keller wrote:
How about this?
class ArbitraryDefault a where {}
instance (Integral a, Bounded a, ArbitraryDefault a) => Arbitrary a where arbitrary = arbitraryBound coarbitrary a = error "Not implemented"
instance ArbitraryDefault Word16 instance ArbitraryDefault Word32 instance ArbitraryDefault Word64

I've not had any problems with them, though of course your mileage may vary. Have a look at section 7.4.4.3 in http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html... for an explanation. Basically, if you have a cyclic class dependency graph, the type checker won't terminate. Well, it will, but only because there's a limit on the recursion depth. The trivial example is instance C a => C a where ... In practice, I'm not sure that this is really a big issue, and it does come in handy. Perhaps someone who's actually been bitten by a problem with undecidable instances can comment? Bryn Joel Reymont wrote:
This requires
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
but since I'm using -fglasgow-exts in a lot of places I'm wondering if adding undecidable instances would be a bad habit. I guess not... not until I shoot myself in the foot :-).
Any explanation of undecidable instances, the good and the bad?
Joel
On Oct 27, 2005, at 6:49 PM, Bryn Keller wrote:
How about this?
class ArbitraryDefault a where {}
instance (Integral a, Bounded a, ArbitraryDefault a) => Arbitrary a where arbitrary = arbitraryBound coarbitrary a = error "Not implemented"
instance ArbitraryDefault Word16 instance ArbitraryDefault Word32 instance ArbitraryDefault Word64

On Thu, Oct 27, 2005 at 07:06:12PM +0100, Joel Reymont wrote:
This requires
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
but since I'm using -fglasgow-exts in a lot of places I'm wondering if adding undecidable instances would be a bad habit. I guess not... not until I shoot myself in the foot :-).
I would avoid them if at all possible. especially if you are still learning haskell, I have found they often hide real errors in ones design of a class hierarchy by making something compile that shouldn't. I had a particularly nasty bug in my regex library when I only had one operator (=~) that was not being caught because of undecidable instances being allowed, when I turned them off, I thought about the problem again and realized that separate monadic (=~~) and non monadic (=~) versions not only solved the issue but was actually a much nicer design with much clearer semantics. John -- John Meacham - ⑆repetae.net⑆john⑈

On Oct 27, 2005, at 5:34 PM, Sebastian Sylvan wrote:
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)
Awesome! This actually works!
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).
It wraps around, apparently *Foo> maxBound :: Word32 4294967295 *Foo> let x :: Integer = 4294967295 + 1 *Foo> x 4294967296 *Foo> fromIntegral x :: Word32 0 *Foo> let x :: Integer = 4294967295 + 10 *Foo> x 4294967305 *Foo> fromIntegral x :: Word32 9 *Foo> let x :: Integer = 4294967295 * 2 *Foo> x 8589934590 *Foo> fromIntegral x :: Word32 4294967294 Thanks, Joel -- http://wagerlabs.com/

On Thu, 27 Oct 2005, Sebastian Sylvan
instance Arbitrary Word32 where arbitrary = do c <- arbitrary :: Gen Integer return (fromIntegral c)
This definition will usually only generate very small or very large Word32 values. The reason is the wrapping mentioned elsewhere and the arbitrary definition for Integer: arbitrary = sized $ \n -> choose (-fromIntegral n,fromIntegral n) You would need to manually ask for larger sizes (using Test.QuickCheck.check with a suitable Config). If a uniform distribution of Word32s is really needed then I would go with the other definition. -- /NAD

Just one more question... data Prop = forall a b. (Eq a, Eq b, Show a, Packet b, Convertible a b) => Attr a b := a deriving (Typeable) data Attr a b = Attr String (a -> Dynamic, Dynamic -> Maybe a) (a -> b, b -> a) makeAttr :: (Typeable a, Convertible a b) => String -> Attr a b makeAttr name = Attr name (toDyn, fromDynamic) (convert_AB, convert_BA) I can do this for Attr instance (Typeable a, Arbitrary a, Typeable b, Arbitrary b, Convertible a b) => Arbitrary (Attr a b) where arbitrary = makeAttr `fmap` arbitrary coarbitrary a = error "Not implemented" How do I define an arbitrary prop, though? Following does not work: arbitraryProp :: forall a b.(Arbitrary a, Arbitrary b) => Attr a b -> Gen Prop arbitraryProp = arbitrary := arbitrary Thanks, Joel -- http://wagerlabs.com/

This compiles: instance (Typeable a, Arbitrary a, Typeable b, Arbitrary b, Convertible a b) => Arbitrary (Attr a b) where arbitrary = makeAttr `fmap` arbitrary coarbitrary a = error "Not implemented" arbitraryProp :: forall a b.(Eq a, Packet b, Show a, Convertible a b, Arbitrary a, Arbitrary b) => Gen (Attr a b) -> Gen Prop arbitraryProp attr = liftM2 (:=) attr arbitrary Joel On Oct 28, 2005, at 12:13 AM, Joel Reymont wrote:
Just one more question...
data Prop = forall a b. (Eq a, Eq b, Show a, Packet b, Convertible a b) => Attr a b := a deriving (Typeable)
data Attr a b = Attr String (a -> Dynamic, Dynamic -> Maybe a) (a -> b, b -> a)
makeAttr :: (Typeable a, Convertible a b) => String -> Attr a b makeAttr name = Attr name (toDyn, fromDynamic) (convert_AB, convert_BA)
I can do this for Attr
instance (Typeable a, Arbitrary a, Typeable b, Arbitrary b, Convertible a b) => Arbitrary (Attr a b) where arbitrary = makeAttr `fmap` arbitrary coarbitrary a = error "Not implemented"
How do I define an arbitrary prop, though? Following does not work:
arbitraryProp :: forall a b.(Arbitrary a, Arbitrary b) => Attr a b -
Gen Prop arbitraryProp = arbitrary := arbitrary

Joel Reymont
Does anyone have QuickCheck examples they could send me?
There's a minimal introduction to QuickCheck and HUnit in the most recent issue of The Monad.Reader: http://www.haskell.org/tmrwiki/IssueFive
Also, how can I check Word32, Word64, etc. properties? It looks like the built-in random generator only works with Int values and for the life of me I cannot figure out how to extend it.
You can build your own data generators easily. I was planning to cover that in the next TMR issue. In the meantime, these examples may help: http://www.scannedinavian.org/~shae/src/haskell/TestCore.hs http://www.scannedinavian.org/~shae/src/haskell/Tests.hs http://www.scannedinavian.org/~shae/combinatorrent/Bittorrent/BEncode.hs
Last but not least, I'm trying to figure out how I can use QuickCheck with tests against a network server. I would want to make sure that a certain packet sequence always produces a particular packet sequence in response. Is this a good area to apply QC?
You can do that with the model based checking from the QuickCheckST paper. You could either generate actions and results and test separately, or you can use unsafePerformIO to run IO tests from inside QuickCheckM. I would very much like to see QuickCheckM extended to handle IO directly. I've wanted to use QuickCheck to test TCP/IP stacks for unhandled cases. Think of the entertainment value :-) I hope that QuickCheck2 or a preview version is released soon. I'd like to do more with QC. -- Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said: You could switch out the unicycles for badgers, and the game would be the same.

Is this gonna be in the next version of QuickCheck? Or can it be implemented now? On Oct 27, 2005, at 3:47 PM, Shae Matijs Erisson wrote:
You can do that with the model based checking from the QuickCheckST paper. You could either generate actions and results and test separately, or you can use unsafePerformIO to run IO tests from inside QuickCheckM.
I would very much like to see QuickCheckM extended to handle IO directly. I've wanted to use QuickCheck to test TCP/IP stacks for unhandled cases. Think of the entertainment value :-)

Joel Reymont
I would very much like to see QuickCheckM extended to handle IO directly. I've wanted to use QuickCheck to test TCP/IP stacks for unhandled cases. Think of the entertainment value :-)
Is this gonna be in the next version of QuickCheck? Or can it be implemented now?
You'd have to monadify the internals of QuickCheck. QC depends on each monad having a 'run' function :: (m a -> a), which works for ST, but not IO. Thomas Jäger described the necessary changes to me on irc some months ago, Search for QuickCheckM in http://tunes.org/~nef/logs/haskell/05.03.21 I haven't gotten around to trying to implement them yet. If you do implement these changes, I'd definitely jump in and help. -- Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said: You could switch out the unicycles for badgers, and the game would be the same.

How is this supposed to work? Does anyone have a simple explanation? I could not understand how to define this for arbitraries of my choosing and Shae seems to have defined coarbitrary = error "Not implemented" :-). Thanks, Joel -- http://wagerlabs.com/

Joel Reymont
How is this supposed to work? Does anyone have a simple explanation?
Here's a demonstration of an arbitrary instance for a datatype. <code> module ProtoArbitrary where import Test.QuickCheck import Control.Monad data Tree a = Nil | Node (Tree a) a (Tree a) deriving (Eq,Ord,Show) instance (Arbitrary a) => Arbitrary (Tree a) where arbitrary = oneof [return Nil, liftM3 Node arbitrary arbitrary arbitrary] coarbitrary = error "not implemented" prop_TreeI :: Tree Int -> Bool prop_TreeI x = True prop_TreeF :: Tree Float -> Bool prop_TreeF x = True </code>
I could not understand how to define this for arbitraries of my choosing and Shae seems to have defined coarbitrary = error "Not implemented" :-).
Coarbitrary is for generator transformers, see section 3.3 on page 5 of the original paper http://www.md.chalmers.se/~koen/Papers/quick.ps -- Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said: You could switch out the unicycles for badgers, and the game would be the same.

On Thu, 27 Oct 2005, Shae Matijs Erisson
Joel Reymont
writes: I could not understand how to define this for arbitraries of my choosing and Shae seems to have defined coarbitrary = error "Not implemented" :-).
Coarbitrary is for generator transformers, see section 3.3 on page 5 of the original paper http://www.md.chalmers.se/~koen/Papers/quick.ps
You need coarbitrary for Word32 if you want to generate arbitrary functions of type Word32 -> <something>. As you will see in the QuickCheck paper Coarbitrary instances can (often) be defined mechanically. I think QuickCheck 2 includes default coarbitrary methods implemented using generic classes (http://haskell.org/ghc/docs/latest/html/users_guide/generic-classes.html). -- /NAD
participants (6)
-
Bryn Keller
-
Joel Reymont
-
John Meacham
-
Nils Anders Danielsson
-
Sebastian Sylvan
-
Shae Matijs Erisson