Skip to content

Instantly share code, notes, and snippets.

@ianfun
Created August 1, 2022 13:36
Show Gist options
  • Save ianfun/c252ebbb9affa7071db13b98645e61c4 to your computer and use it in GitHub Desktop.
Save ianfun/c252ebbb9affa7071db13b98645e61c4 to your computer and use it in GitHub Desktop.
state Monad in Haskell
module Main where
import Control.Monad as M
import System.Random
newtype State s a = State {runState:: s -> (a, s)}
instance Functor (State s) where
fmap = M.liftM
instance Applicative (State s) where
pure = return
(<*>) = M.ap
instance Monad (State s) where
a >> b = State $ \s0 ->
let (_, s1) = runState a s0
in runState b s1
a >>= f = State $ \s0 ->
let (x, s1) = runState a s0
in runState (f x) s1
return a = State $ \s -> (a, s)
evalState :: State s a -> s -> a
evalState f s = fst (runState f s)
execState :: State s a -> s -> s
execState f s = snd (runState f s)
srandom :: (Random a, RandomGen g) => State g a
srandom = State $ System.Random.random
roll3Dice :: (Random a, RandomGen g) => State g [a]
roll3Dice = do
a <- srandom
b <- srandom
c <- srandom
return [a, b, c]
roll3DiceNoMonad :: (RandomGen g, Random a) => g -> [a]
roll3DiceNoMonad s0 =
let (a, s1) = random s0
(b, s2) = random s1
(c, _) = random s2
in [a, b, c]
roll3Dice' :: (Random a, RandomGen g) => State g [a]
roll3Dice' =
srandom >>= \a ->
srandom >>= \b ->
srandom >>= \c ->
return [a, b, c]
main = do
print $ ((evalState roll3Dice (mkStdGen 10))::[Int])
print $ ((evalState roll3Dice' (mkStdGen 10))::[Int])
print $ ((roll3DiceNoMonad (mkStdGen 10))::[Int])
-- expect output
-- [3575835729477015470,699411830304833045,7471923267167732691]
-- [3575835729477015470,699411830304833045,7471923267167732691]
-- [3575835729477015470,699411830304833045,7471923267167732691]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment