Skip to content

Instantly share code, notes, and snippets.

@tuttlem
Created October 10, 2012 12:55
Show Gist options
  • Save tuttlem/3865449 to your computer and use it in GitHub Desktop.
Save tuttlem/3865449 to your computer and use it in GitHub Desktop.
Uno cards and shuffling
module Cards where
import System.Random
import Data.Maybe
import Data.List
import Data.Function
import Test.HUnit
import Test.QuickCheck
-- | Card values for uno cards
data CardValue = Naught | One | Two | Three
| Four | Five | Six | Seven | Eight | Nine
| Skip | Reverse | DrawTwo | Wild | WildDrawFour
deriving (Show, Eq, Enum)
-- | Possible card colours
data CardColour = Red | Blue | Green | Yellow
deriving (Show, Eq, Enum)
-- | Defines the attributes of a card
data Card = Card CardValue (Maybe CardColour)
deriving (Show)
-- | Seeds a list of cards with a random value
seedCards :: StdGen -> [Card] -> [(Card, Int)]
seedCards g [] = []
seedCards g (c:cs) = x:seedCards ng cs
where (seed, ng) = randomR(1, 10000) g :: (Int, StdGen)
x = (c, seed)
-- | Makes a randomly shuffled deck of cards
makeShuffledDeck :: StdGen -> [Card]
makeShuffledDeck g = [x | c <- sorted, let x = fst c]
where cards = seedCards g deck
sorted = sortBy (compare `on` snd) cards
deck = val ++ take 10 (cycle spec)
val = [Card v (Just c) | v <- [Naught .. DrawTwo], c <- [Red .. Yellow]]
spec = [Card v Nothing | v <- [Wild .. WildDrawFour]]
tests = TestList $ map TestCase
[assertEqual "add tests here" 1 1]
prop_empty c1 = (c1::Int) == c1
runTests = do
runTestTT tests
quickCheck prop_empty
-- | Main entry point
main :: IO ()
main = runTests
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment