Skip to content

Instantly share code, notes, and snippets.

@yuanwang-wf
Created February 22, 2019 22:46
Show Gist options
  • Save yuanwang-wf/994c75345b651431236632d828dd1af9 to your computer and use it in GitHub Desktop.
Save yuanwang-wf/994c75345b651431236632d828dd1af9 to your computer and use it in GitHub Desktop.
State Monad examples
module Deck where
import Control.Applicative
import Control.Monad.Trans.State
import Data.List
import System.Random
data Rank = One | Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | Jack | Queue | King deriving (Bounded, Enum, Show, Eq, Ord)
data Suit = Diamonds | Clubs | Hearts | Spades deriving (Bounded, Enum, Show, Eq, Ord)
data Card = Card Suit Rank deriving (Show, Eq, Ord)
type Deck = [Card]
fullDeck :: Deck
fullDeck = [Card suit rank | suit <- enumFrom minBound,
rank <- enumFrom minBound]
removeCard :: Deck -> Int -> Deck
removeCard [] _ = []
removeCard deck index = deck' ++ deck''
where (deck', remain) = splitAt (index + 1) deck
deck'' = drop 1 remain
drawCard :: State (StdGen, Deck) Card
drawCard = do (generator, deck) <- get
let (index, generator') = randomR (0, length deck ) generator
put (generator', removeCard deck index)
return $ deck !! index
drawNCard :: Int -> State (StdGen, Deck) [Card]
drawNCard 0 = state (\s -> ([], s))
drawNCard count = liftA2 (:) drawCard (drawNCard $ count - 1)
module Dice where
import Control.Applicative
import Control.Monad.Trans.State
import System.Random
rollDiceIO :: IO (Int, Int)
rollDiceIO = liftA2 (,) (randomRIO (1, 6)) (randomRIO (1,6))
rollNDiceIO :: Int -> IO [Int]
rollNDiceIO 0 = pure []
rollNDiceIO count = liftA2 (:) (randomRIO (1, 6)) (rollNDiceIO (count - 1))
clumsyRollDice :: (Int, Int)
clumsyRollDice = (n, m)
where
(n, g) = randomR (1, 6) (mkStdGen 0)
(m, _) = randomR (1, 6) g
-- rollDice :: StdGen -> ((Int, Int), StdGen)
-- rollDice g = ((n, m), g'')
-- where
-- (n, g') = randomR (1, 6) g
-- (m, g'') = randomR (1, 6) g'
-- use state to construct
rollDie :: State StdGen Int
rollDie = state $ randomR (1, 6)
-- use State as Monad
rollDieM :: State StdGen Int
rollDieM = do generator <- get
let (value, generator') = randomR (1, 6) generator
put generator'
return value
rollDice :: State StdGen (Int, Int)
rollDice = liftA2 (,) rollDieM rollDieM
rollNDice :: Int -> State StdGen [Int]
rollNDice 0 = state (\s -> ([], s))
rollNDice count = liftA2 (:) rollDieM (rollNDice (count - 1))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment