[Haskell-cafe] reply to vincent foley's question about poker

Thomas Hartman tphyahoo at gmail.com
Sat Mar 8 22:21:21 EST 2008


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/8298c4d838c95505/bef67f52f0f28bc5#bef67f52f0f28bc5

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


More information about the Haskell-Cafe mailing list