reply to vincent foley's question about poker

Weirdly, I came across a question Vincent Foley asked in FA Haskell when I read it in the googlegroups interface, http://groups.google.com/group/fa.haskell/browse_thread/thread/8298c4d838c95... but I don't seem to have his question in my inbox where I get haskell cafe. Maybe it got filtered somehow? I notice nobody else from Haskell Cafe seems to have answered, and this is usually a pretty helpful place so I am thinking maybe it really did get filtered. Oh well, I will answer it anyway now.. The question had to do with writing Arbitrary instances for datatypes useful for playing poker, and using quickCheck with them. I like my solution because I get Arbitrary instances for basically every datatype that's involved, from a single definition that gives you Arbitrary for any type a that is both Enum and Bounded. instance (Enum a, Bounded a) => Arbitrary a where arbitrary = do n <- choose (fromEnum (minBound :: a), fromEnum (maxBound :: a) ) return $ toEnum n Here's the code. (Note: For the code to compile you need the EnumInstances .hs module. I posted this a few minutes ago on haskell cafe.) {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} module Cards where import Test.QuickCheck import Control.Arrow import Debug.Trace import EnumInstances -- Types data Suit = Clubs | Diamond | Heart | Spade deriving (Show, Eq, Bounded, Enum, Ord) data Rank = Ace | Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | Jack | Queen | King deriving (Show, Eq, Bounded, Enum,Ord) --instance Arbitrary Rank where -- arbitrary = return $ choose data Card = Card (Rank, Suit) deriving (Eq,Show,Bounded, Ord) instance Enum Card where fromEnum (Card (r,s)) = fromEnum (r,s) toEnum i = Card (toEnum i) -- to check a new instance with quickCheck -- quickCheck (pEnum :: SomeType -> Bool) pEnum x = x == (toEnum . fromEnum) x -- type Hand = [Card] -- a hand is five cards data Hand = Hand Card Card Card Card Card deriving (Eq,Show, Bounded) instance Enum Hand where fromEnum (Hand a b c d e) = fromEnum (a,b,c,d,e) toEnum i = Hand a b c d e where (a,b,c,d,e) = toEnum i instance (Enum a, Bounded a) => Arbitrary a where arbitrary = do n <- choose (fromEnum (minBound :: a), fromEnum (maxBound :: a) ) return $ toEnum n -- not a very useful property, and certainly fails -- but it proves we have a working Arbitrary instance for Hand. pHandIsAlwaysAceOfClubs h = h == (Hand c c c c c) where c = Card (Ace, Clubs) t1 = do quickCheck (pEnum :: Rank -> Bool) quickCheck (pEnum :: Suit -> Bool) quickCheck (pEnum :: Card -> Bool) quickCheck (pEnum :: Hand -> Bool) quickCheck pHandIsAlwaysAceOfClubs -- of course this fails traceIt x = trace (show x) x

On Sun, Mar 9, 2008 at 3:21 AM, Thomas Hartman
instance (Enum a, Bounded a) => Arbitrary a where arbitrary = do n <- choose (fromEnum (minBound :: a), fromEnum (maxBound :: a) ) return $ toEnum n
I really think it's a bad idea to allow undecidable instances. While it may seem to work for small problems, when you start using undecidable instances in larger pieces of software, you will get elusive typecheker errors (stack overflows / infinite loops) which magically appear and disappear with small changes to the code. You probably already know this, but the evil of undecidable instances makes itself pretty apparent once you understand how the typeclass algorithm works. Here's how it goes, anthropomorphically: * I see a call to arbitrary; I will call its return value "a". The call to arbitrary comes with the constraint "Arbitrary a". ... in the future, when generalizing the type ... * I see that "a" has be unified to "[b]" (for some b). I need an instance for "Arbitrary [b]". Ah, here's one (seeing the instance above). Now I have "Arbitrary [b]", and I thus have to add the constraints "Enum [b]" and "Bounded [b]" ... continue solving... The thing to note is that we did not *check* that we had "Enum [b]" and "Bounded [b]" before using the instance "Arbitrary [b]"; rather it worked the other way round: We found an instance "Arbitrary [b]" and that induced some new constraints for us. That means that if you have, say, these two instances: instance (Arbitrary a) => Aribtrary [a] instance (Enum a, Bounded a) => Aribtrary a If you have a list type that you need to be an instance of Aribtrary, if you're unlucky it will pick the second one and you'll end up with Enum [a] and Bounded [a], which won't be satisfiable. There is no backtracking, you just get a type error where there (according to you) should not be one. I believe GHC has some rules to minimize the occurences of such "unluckiness", but they're just heuristic and don't provide any guarantee (and thus only propagate the illusion that instances like this are actually okay). This is an example where undecidable instances will lead to indeterminate behavior, but there are other trickier cases where you get an infinite loop, which is fixable only by knowing how the algorithm works and placing a type annotation in the most obscure corner of some function. Okay, now that that rant is done, what is the safe way to accomplish what you want? Wrap it in a newtype: newtype EnumArbitrary a = EnumArbitrary { fromEnumArbitrary :: a } instance (Enum a, Bounded a) => Arbitrary (EnumArbitrary a) where ... This is a perfectly fine, well behaved H98 instance. You mark when you want to use this instance by appearances of the constructor EnumArbitrary, so you don't run into cases like the above. However, many times for usability purposes I run into situations where I want a generic instance like the one you used. Props to anyone who can come up with a typeclass system which allows such things and has decidable and predictable inference. Luke
participants (2)
-
Luke Palmer
-
Thomas Hartman