
So I've finally got some code which shuffles a deck of cards and deals out an arbitrary number of hands. https://gist.github.com/19916435df2b116e0edc type DealerState = State [Card] [[Card]] deck :: [Card] deck = [ (s, r) | s <- suits, r <- ranks ] shuffleDeck :: Int -> RVar [Card] shuffleDeck n = shuffle $ concat $ replicate n deck deal :: Int -> ([[Card]] -> DealerState) deal n = \xs -> state $ \s -> (xs ++ [take n s], drop n s) -- |Deal a number of hands a number of cards each. dealHands :: Int -> Int -> ([[Card]] -> DealerState) dealHands hs cs = foldr1 (<=<) $ replicate hs (deal cs) First of all, I have no idea if this is any good. The way I end up calling dealHands and getting a "real" result is `runState (dealHands 3 7 []) deck`. And I see that I've got nested lambdas all in `deal`. But hey it took me forever to figure it out and it "works." I'm using `shuffle` from Data.Random.Extras, which results in an RVar, and thus the beginning of my perplexity. I'm happy to end up with RVar inside a State monad, but I'm not sure where to start. To be honest, I'm only barely understanding what I'm doing with the State monad as it is. :) Happy for any help whatsoever! - Matthew

hello matthew,
I commented your gist on github adding the missing pieces with minor fixes.
Anyway, I suggest giving up RVar's which are overkill for your task. You
could implement your shuffle as an exercise, or use random-shuffle package
as I do in the code below.
Also I'd avoid State monad for such a simple task of remembering the
remaining deck after each deal. You should switch to using a monad after
you are comfortable with pure code.
import Control.Arrow
import System.Random.Shuffle
import Control.Monad.Random.Class
-- |Cards.
data Suit = Hearts | Diamonds | Clubs | Spades deriving (Enum, Bounded,
Show)
data Rank = Ace | Two | Three | Four | Five | Six | Seven | Eight | Nine |
Ten | Jack | Queen | King deriving (Enum, Bounded, Show)
data Card = Flat Rank Suit | Jolly deriving Show
type Deck = [Card]
type Hand = [Card]
deck :: Deck
deck = [ Flat s r | s <- [minBound .. maxBound] , r <- [minBound ..
maxBound]]++ [Jolly,Jolly]
-- deal n cards m times from the given deck and return the rest along the
hands
dealHands :: Int -> Int -> Deck -> ([Hand],Deck)
dealHands n m = (map (take n) *** head) . splitAt m . iterate (drop n)
-- same as dealHands, but shuffle the deck before
randomDealHands :: (Functor m, MonadRandom m) => Int -> Int -> Deck -> m
([Hand],Deck)
randomDealHands n m xs = dealHands n m `fmap` shuffleM xs
test :: IO ([Hand],Deck)
test = randomDealHands 5 4 $ deck ++ deck
You can run randomDealHands in IO (ghci prompt) as IO is both a Functor and
a MonadRandom instance
regards
paolino
2012/8/25 Matthew
So I've finally got some code which shuffles a deck of cards and deals out an arbitrary number of hands.
https://gist.github.com/19916435df2b116e0edc
type DealerState = State [Card] [[Card]]
deck :: [Card] deck = [ (s, r) | s <- suits, r <- ranks ]
shuffleDeck :: Int -> RVar [Card] shuffleDeck n = shuffle $ concat $ replicate n deck
deal :: Int -> ([[Card]] -> DealerState) deal n = \xs -> state $ \s -> (xs ++ [take n s], drop n s)
-- |Deal a number of hands a number of cards each. dealHands :: Int -> Int -> ([[Card]] -> DealerState) dealHands hs cs = foldr1 (<=<) $ replicate hs (deal cs)
First of all, I have no idea if this is any good. The way I end up calling dealHands and getting a "real" result is `runState (dealHands 3 7 []) deck`. And I see that I've got nested lambdas all in `deal`. But hey it took me forever to figure it out and it "works."
I'm using `shuffle` from Data.Random.Extras, which results in an RVar, and thus the beginning of my perplexity. I'm happy to end up with RVar inside a State monad, but I'm not sure where to start. To be honest, I'm only barely understanding what I'm doing with the State monad as it is. :)
Happy for any help whatsoever!
- Matthew
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Matthew
-
Paolino