On Haskell, what is the linguistic way to represent a card effect for a card game? - haskell

I have a simple one-player Card Game:
data Player = Player {
_hand :: [Card],
_deck :: [Card],
_board :: [Card]}
$(makeLenses ''Player)
Some cards have an effect. For example, "Erk" is a card with the following effect:
Flip a coin. If heads, shuffle your deck.
I've implemented it as such:
shuffleDeck :: (MonadRandom m, Functor m) => Player -> m Player
shuffleDeck = deck shuffleM
randomCoin :: (MonadRandom m) => m Coin
randomCoin = getRandom
flipCoin :: (MonadRandom m) => m a -> m a -> m a
flipCoin head tail = randomCoin >>= branch where
branch Head = head
branch Tail = tail
-- Flip a coin. If heads, shuffle your deck.
erk :: (MonadRandom m, Functor m) => Player -> m Player
erk player = flipCoin (deck shuffleM player) (return player)
While this certainly does the job, I find an issue on the forced coupling to the Random library. What if I later on have a card that depends on another monad? Then I'd have to rewrite the definition of every card defined so far (so they have the same type). I'd prefer a way to describe the logic of my game entirely independent from the Random (and any other). Something like that:
erk :: CardAction
erk = do
coin <- flipCoin
case coin of
Head -> shuffleDeck
Tail -> doNothing
I could, later on, have a runGame function that does the connection.
runGame :: (RandomGen g) => g -> CardAction -> Player -> Player
I'm not sure that would help. What is the correct, linguistic way to deal with this pattern?

This is one of the engineering problems the mtl library was designed to solve. It looks like you're already using it, but don't realize its full potential.
The idea is to make monad transformer stacks easier to work with using typeclasses. A problem with normal monad transformer stacks is that you have to know all of the transformers you're using when you write a function, and changing the stack of transformers changes how lifts work. mtl solves this by defining a typeclass for each transformer it has. This lets you write functions that have a class constraint for each transformer it requires but can work on any stack of transformers that includes at least those.
This means that you can freely write functions with different sets of constraints and then use them with your game monad, as long as you game monad has at least those capabilities.
For example, you could have
erk :: MonadRandom m => ...
incr :: MonadState GameState m => ...
err :: MonadError GameError m => ...
lots :: (MonadRandom m, MonadState GameState m) => ...
and define your Game a type to support all of those:
type Game a = forall g. RandT g (StateT GameState (ErrorT GameError IO)) a
You'd be able to use all of these interchangeably within Game, because Game belongs to all of those typeclasses. Moreover, you wouldn't have to change anything except the definition of Game if you wanted to add more capabilities.
There's one important limitation to keep in mind: you can only access one instance of each transformer. This means that you can only have one StateT and one ErrorT in your whole stack. This is why StateT uses a custom GameState type: you can just put all of the different things you may want to store throughout your game into that one type so that you only need one StateT. (GameError does the same for ErrorT.)
For code like this, you can get away with just using the Game type directly when you define your functions:
flipCoin :: Game a -> Game a -> Game a
flipCoin a b = ...
Since getRandom has a type polymorphic over m itself, it will work with whatever Game happens to be as long as it has at least a RandT (or something equivalent) inside.
So, to answer you question, you can just rely on the existing mtl typeclasses to take care of this. All of the primitive operations like getRandom are polymorphic over their monad, so they will work with whatever stack you end up with in the end. Just wrap all your transformers into a type of your own (Game), and you're all set.

This sounds like a good use-case for the operational package. It lets you define a monad as a set of operations and their return types using a GADT and you can then easily build an interpreter function like the runGame function you suggested. For example:
{-# LANGUAGE GADTs #-}
import Control.Monad.Operational
import System.Random
data Player = Player {
_hand :: [Card],
_deck :: [Card],
_board :: [Card]}
data Coin = Head | Tail
data CardOp a where
FlipCoin :: CardOp Coin
ShuffleDeck :: CardOp ()
type CardAction = Program CardOp
flipCoin :: CardAction Coin
flipCoin = singleton FlipCoin
shuffleDeck :: CardAction ()
shuffleDeck = singleton ShuffleDeck
erk :: CardAction ()
erk = do
coin <- flipCoin
case coin of
Head -> shuffleDeck
Tail -> return ()
runGame :: RandomGen g => g -> CardAction a -> Player -> Player
runGame = step where
step g action player = case view action of
Return _ -> player
FlipCoin :>>= continue ->
let (heads, g') = random g
coin = if heads then Head else Tail
in step g' (continue coin) player
...etc...
However, you might also want to consider just describing all your card actions as a simple ADT without do-syntax. I.e.
data CardAction
= CoinFlip CardAction CardAction
| ShuffleDeck
| DoNothing
erk :: CardAction
erk = CoinFlip ShuffleDeck DoNothing
You can easily write an interpreter for the ADT and as a bonus you can also e.g. generate the card's rule text automatically.

Related

How do I add lists or ListT to this monad transformer?

I have a game record that represents the current state of a game.
data Game = Game { score :: Int, turn :: Int }
I want to be able to create a bunch of functions to change the game state, and also use a random number generator as well as keep a log of what happened to get from one state to another. So I created a GameState record that contains the additional information.
type History = [String]
data GameState = GameState Game StdGen History
Now I want to create a data type for the functions that are going to be acting on this GameState. They'll be modeled imperatively as updates to the game as well as rolling dice and logging what's happening. So I created a monad transformer of all the effects I want.
type Effect = WriterT History (RandT StdGen (State Game))
Writing the function to run an Effect on a given GameState is pretty simple.
runEffect :: GameState -> Effect () -> GameState
runEffect (GameState game stdGen history) effect =
let ((((), newHist), newGen), newGame) =
runState (runRandT (runWriterT effect) stdGen) game
in GameState newGame newGen newHist
Perfect. Now I want to model one additional thing. Some Effects can have multiple different resulting GameStates. So my runEffect should actually return a [GameState]. I need to add ListT to this monad transformer, probably. And then all of my Effects will have the option of producing more than one result if need be. But also if they are just a one-to-one mapping then then can act like that too.
I tried to make the following changes:
type Effect2 = ListT (WriterT [String] (RandT StdGen (State Game)))
runEffect2 :: GameState -> Effect2 a -> [GameState]
runEffect2 (GameState game stdGen history) effect =
let l = runListT effect
result = map (\e->runState (runRandT (runWriterT e) stdGen) game) l
in map (\((((), newHist), newGen), newGame)->
GameState newGame newGen newHist)
result
What I'm trying to do is add ListT to the transformer, outside of the Writer and Random and State because I want for the different branches of the computation to have different histories and independent states and random generators. But this doesn't work. I get the following type error.
Prelude λ: :reload [1 of 1] Compiling Main ( redux.hs, interpreted )
redux.hs:31:73: error:
• Couldn't match expected type ‘[WriterT
w
(RandT StdGen (StateT Game Data.Functor.Identity.Identity))
a1]’
with actual type ‘WriterT [String] (RandT StdGen (State Game)) [a]’
• In the second argument of ‘map’, namely ‘l’
In the expression:
map (\ e -> runState (runRandT (runWriterT e) stdGen) game) l
In an equation for ‘result’:
result
= map (\ e -> runState (runRandT (runWriterT e) stdGen) game) l
• Relevant bindings include
result :: [(((a1, w), StdGen), Game)] (bound at redux.hs:31:7)
l :: WriterT [String] (RandT StdGen (State Game)) [a]
(bound at redux.hs:30:7)
effect :: Effect2 a (bound at redux.hs:29:44)
runEffect2 :: GameState -> Effect2 a -> [GameState]
(bound at redux.hs:29:1)
Failed, modules loaded: none.
Does anyone know what I'm doing wrong? I effectively want to be able to expand one GameState into multiple GameStates. Each with an independent StdGen and History for that branch. I have done this by putting everything into the Game record and just using non-monadic functions for the effects. This works and it's pretty straight forward. However, composition of these functions is really annoying because they're acting like state and I need to need to handle it myself. This is what monads are great at so I figured reusing that here would be wise. Sadly the list aspect of it has me really confused.
Firstly, the immediate cause of the error is that the type of runListT is...
GHCi> :t runListT
runListT :: ListT m a -> m [a]
... but you are using it as if it produced a [m a], rather than a m [a]. In other words, the map in the definition of result shouldn't be there.
Secondly, in a monadic stack the inner monads rule over the outer ones. Wrapping, for instance, StateT with ListT results in a garden-variety stateful computation that happens to produce multiple results. We can see that by specialising the type of runListT:
GHCi> :set -XTypeApplications
GHCi> :t runListT #(StateT _ _)
runListT #(StateT _ _) :: ListT (StateT t t1) a -> StateT t t1 [a]
Wrapping ListT with StateT, on the other hand, gives us a computation that produces multiple states as well as results:
GHCi> :t runStateT #_ #(ListT _)
runStateT #_ #(ListT _)
:: StateT t (ListT t1) a -> t -> ListT t1 (a, t)
That being so, you want to swap the transformers in your stack. If you want to have multiple effects for everything, as you describe, and you don't need IO as your base monad, you don't need ListT at all -- simply put [] at the bottom of the stack.
Thirdly, on a tangential note, avoid the ListT from transformers. It is known to be unlawful, and it has been deprecated in the latest version of transformers. A simple replacement for it is provided by the list-t package. (If, at some point further down the road, you get to make use of the pipes streaming library, you might also find its own version of ListT useful.)

Composing State and State transformer actions

I have several State monad actions. Some of the actions make decisions based on the current state and other input optionally generating result. The two types of actions invoke each other.
I have modeled these two action types with State and StateT Maybe. The following (contrived) example shows my current approach.
{-# LANGUAGE MultiWayIf #-}
import Control.Monad (guard)
import Control.Monad.Identity (runIdentity)
import Control.Monad.Trans.State
type Producer = Int -> State [Int] Int
type MaybeProducer = Int -> StateT [Int] Maybe Int
produce :: Producer
produce n
| n <= 0 = return 0
| otherwise = do accum <- get
let mRes = runStateT (maybeProduce n) accum
if | Just res <- mRes -> StateT $ const (return res)
| otherwise -> do res <- produce (n - 1)
return $ res + n
maybeProduce :: MaybeProducer
maybeProduce n = do guard $ odd n
modify (n:)
mapStateT (return . runIdentity) $
do res <- produce (n - 1)
return $ res + n
I have factored out separating the checks from the actions (thus transforming them into simple State actions) because the check itself is very involved (80% of the work) and provides the bindings needed in the action. I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.
Is there a better or more elegan way that I'm missing? In particular I don't like the mapStateT/runStateT duo, but it seems necessary.
PS: I know the example is actually a Writer, but I used State to better reflect the real case
I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.
What do you mean by "promote"? I can't tell which of these you mean:
Rewrite the definitions of the State actions so that their type is now StateT Maybe, even though they don't rely on Maybe at all;
Use an adapter function that transforms State s a into StateT s Maybe a.
I agree with rejecting (1), but to me that mean either:
Go for (2). One useful tool for this is to use the mmorph library (blog entry).
Rewrite the actions from State s a to use Monad m => StateT s m a.
In the second case, the type is compatible with any Monad m but does not allow the code to assume any specific base monad, so you get the same purity as State s a.
I'd give mmorph a shot. Note that:
State s a = StateT s Identity a;
hoist generalize :: (MFunctor t, Monad m) => t Identity a -> t m a;
And that specializes to hoist generalize :: State s a -> StateT s Maybe a.
EDIT: It's worth nothing that there is an isomorphism between the State s a and forall m. StateT s m a types, given by these inverse functions:
{-# LANGUAGE RankNTypes #-}
import Control.Monad.Morph
import Control.Monad.Trans
import Control.Monad.Trans.State
import Control.Monad.Identity
fwd :: (MFunctor t, Monad m) => t Identity a -> t m a
fwd = hoist generalize
-- The `forall` in the signature forbids callers from demanding any
-- specific choice of type for `m`, which allows *us* to choose
-- `Identity` for `m` here.
bck :: MFunctor t => (forall m. t m a) -> t Identity a
bck = hoist generalize
So the Monad m => StateT s m a and mmorph solutions are, effectively, the same. I prefer using mmorph here, though.

Making Read-Only functions for a State in Haskell

I often end up in a situation where it's very convenient to be using the State monad, due to having a lot of related functions that need to operate on the same piece of data in a semi-imperative way.
Some of the functions need to read the data in the State monad, but will never need to change it. Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
Is there some type-level thing that I can do to ensure that these functions can only read from the State, and never write to it?
Current situation:
iWriteData :: Int -> State MyState ()
iWriteData n = do
state <- get
put (doSomething n state)
-- Ideally this type would show that the state can't change.
iReadData :: State MyState Int
iReadData = do
state <- get
return (getPieceOf state)
bigFunction :: State MyState ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData -- How do we know that the state wasn't modified?
iWRiteData num
Ideally iReadData would probably have the type Reader MyState Int, but then it doesn't play nicely with the State. Having iReadData be a regular function seems to be the best bet, but then I have to go through the gymnastics of explicitly extracting and passing it the state every time it's used. What are my options?
It's not hard to inject the Reader monad into State:
read :: Reader s a -> State s a
read a = gets (runReader a)
then you could say
iReadData :: Reader MyState Int
iReadData = do
state <- ask
return (getPieceOf state)
and call it as
x <- read $ iReadData
this would allow you to build up Readers into larger read-only sub-programs and inject them into State only where you need to combine them with mutators.
It's not hard to extend this to a ReaderT and StateT at the top of your monad transformer stack (in fact, the definition above works exactly for this case, just change the type). Extending it to a ReaderT and StateT in the middle of the stack is harder. You basically need a function
lift1 :: (forall a. m0 a -> m1 a) -> t m0 a -> t m1 a
for every monad transformer t in the stack above the ReaderT/StateT, which isn't part of the standard library.
I would recommend wrapping up the State monad in a newtype and defining a MonadReader instance for it:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Applicative
import Control.Monad.State
import Control.Monad.Reader
data MyState = MyState Int deriving Show
newtype App a = App
{ runApp' :: State MyState a
} deriving
( Functor
, Applicative
, Monad
, MonadState MyState
)
runApp :: App a -> MyState -> (a, MyState)
runApp app = runState $ runApp' app
instance MonadReader MyState App where
ask = get
local f m = App $ fmap (fst . runApp m . f) $ get
iWriteData :: MonadState MyState m => Int -> m ()
iWriteData n = do
MyState s <- get
put $ MyState $ s + n
iReadData :: MonadReader MyState m => m Int
iReadData = do
MyState s <- ask
return $ s * 2
bigFunction :: App ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData
iWriteData num
This is certainly more code that #jcast's solution, but it follows the the tradition of implementing your transformer stack as a newtype wrapper, and by sticking with constraints instead of solidified types you can make strong guarantees about the use of your code while providing maximum flexibility for re-use. Anyone using your code would be able to extend your App with transformers of their own while still using iReadData and iWriteData as intended. You also don't have to wrap every call to a Reader monad with a read function, the MonadReader MyState functions are seamlessly integrated with functions in the App monad.
Excellent answers by jcast and bhelkir, with exactly the first idea I thought of—embedding Reader inside State.
I think it's worthwhile to address this semi-side point of your question:
Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
That's a potential red flag, indeed. I've always found that State works best for code with "small" states that can be contained within the lifetime of a single, brief application of runState. My go-to example is numbering the elements of a Traversable data structure:
import Control.Monad.State
import Data.Traversable (Traversable, traverse)
tag :: (Traversable t, Enum s) => s -> t a -> t (s, a)
tag i ta = evalState (traverse step ta) init
where step a = do s <- postIncrement
return (s, a)
postIncrement :: Enum s => State s s
postIncrement = do result <- get
put (succ result)
return result
You don't directly say so, but you make it sound you may have a big state value, with many different fields being used in many different ways within a long-lived runState call. And perhaps it does need to be that way for your program at this point. But one technique for coping with this might be to write your smaller State actions so that they only use narrower state types than the "big" one and then embed these into the larger State type with a function like this:
-- | Extract a piece of the current state and run an action that reads
-- and modifies only that piece.
substate :: (s -> s') -> (s' -> s -> s) -> State s' a -> State s a
substate extract replace action =
do s <- get
let (s', a) = runState action (extract s)
put (replace s' s)
return a
Schematic example
example :: State (A, B) Whatever
example = do foo <- substate fst (,b) action1
bar <- substate snd (a,) action2
return $ makeWhatever foo bar
-- Can only touch the `A` component of the state
action1 :: State A Foo
action1 = ...
-- Can only touch the `B` component of the state
action2 :: State B Bar
action2 = ...
Note that the extract and replace functions constitute a lens, and there are libraries for that, which may even already include a function like this.

Combining multiple states in StateT

I am writing a program that runs as a daemon.
To create the daemon, the user supplies a set of
implementations for each of the required classes (one of them is a database)
All of these classes have functions have
type signatures of the form StateT s IO a,
but s is different for each class.
Suppose each of the classes follows this pattern:
import Control.Monad (liftM)
import Control.Monad.State (StateT(..), get)
class Hammer h where
driveNail :: StateT h IO ()
data ClawHammer = MkClawHammer Int -- the real implementation is more complex
instance Hammer ClawHammer where
driveNail = return () -- the real implementation is more complex
-- Plus additional classes for wrenches, screwdrivers, etc.
Now I can define a record that represents the implementation chosen by
the user for each "slot".
data MultiTool h = MultiTool {
hammer :: h
-- Plus additional fields for wrenches, screwdrivers, etc.
}
And the daemon does most of its work in the StateT (MultiTool h ...) IO ()
monad.
Now, since the multitool contains a hammer, I can use it in any situation
where a hammer is needed. In other words, the MultiTool type
can implement any of the classes it contains, if I write code like this:
stateMap :: Monad m => (s -> t) -> (t -> s) -> StateT s m a -> StateT t m a
stateMap f g (StateT h) = StateT $ liftM (fmap f) . h . g
withHammer :: StateT h IO () -> StateT (MultiTool h) IO ()
withHammer runProgram = do
t <- get
stateMap (\h -> t {hammer=h}) hammer runProgram
instance Hammer h => Hammer (MultiTool h) where
driveNail = withHammer driveNail
But the implementations of withHammer, withWrench, withScrewdriver, etc.
are basically identical. It would be nice to be able to write something
like this...
--withMember accessor runProgram = do
-- u <- get
-- stateMap (\h -> u {accessor=h}) accessor runProgram
-- instance Hammer h => Hammer (MultiTool h) where
-- driveNail = withMember hammer driveNail
But of course that won't compile.
I suspect my solution is too object-oriented.
Is there a better way?
Monad transformers, maybe?
Thank you in advance for any suggestions.
If you want to go with a large global state like in your case, then what you want to use is lenses, as suggested by Ben. I too recommend Edward Kmett's lens library. However, there is another, perhaps nicer way.
Servers have the property that the program runs continuously and performs the same operation over a state space. The trouble starts when you want to modularize your server, in which case you want more than just some global state. You want modules to have their own state.
Let's think of a module as something that transforms a Request to a Response:
Module :: (Request -> m Response) -> Module m
Now if it has some state, then this state becomes noticable in that the module might give a different answer the next time. There are a number of ways to do this, for example the following:
Module :: s -> ((Request, s) -> m (Response s)) -> Module m
But a much nicer and equivalent way to express this is the following constructor (we will build a type around it soon):
Module :: (Request -> m (Response, Module m)) -> Module m
This module maps a request to a response, but along the way also returns a new version of itself. Let's go further and make requests and responses polymorphic:
Module :: (a -> m (b, Module m a b)) -> Module m a b
Now if the output type of a module matches another module's input type, then you can compose them like regular functions. This composition is associative and has a polymorphic identity. This sounds a lot like a category, and in fact it is! It is a category, an applicative functor and an arrow.
newtype Module m a b =
Module (a -> m (b, Module m a b))
instance (Monad m) => Applicative (Module m a)
instance (Monad m) => Arrow (Module m)
instance (Monad m) => Category (Module m)
instance (Monad m) => Functor (Module m a)
We can now compose two modules that have their own individual local state without even knowing about it! But that's not sufficient. We want more. How about modules that can be switched among? Let's extend our little module system such that modules can actually choose not to give an answer:
newtype Module m a b =
Module (a -> m (Maybe b, Module m a b))
This allows another form of composition that is orthogonal to (.): Now our type is also a family of Alternative functors:
instance (Monad m) => Alternative (Module m a)
Now a module can choose whether to respond to a request, and if not, the next module will be tried. Simple. You have just reinvented the wire category. =)
Of course you don't need to reinvent this. The Netwire library implements this design pattern and comes with a large library of predefined "modules" (called wires). See the Control.Wire module for a tutorial.
Here's a concrete example of how to use lens like everybody else is talking about. In the following code example, Type1 is the local state (i.e. your hammer), and Type2 is the global state (i.e. your multitool). lens provides the zoom function which lets you run a localized state computation that zooms in on any field defined by a lens:
import Control.Lens
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State
data Type1 = Type1 {
_field1 :: Int ,
_field2 :: Double}
field1 :: SimpleLens Type1 Int
field1 = lens _field1 (\x a -> x { _field1 = a})
field2 :: SimpleLens Type1 Double
field2 = lens _field2 (\x a -> x { _field2 = a})
data Type2 = Type2 {
_type1 :: Type1 ,
_field3 :: String}
type1 :: SimpleLens Type2 Type1
type1 = lens _type1 (\x a -> x { _type1 = a})
field3 :: SimpleLens Type2 String
field3 = lens _field3 (\x a -> x { _field3 = a})
localCode :: StateT Type1 IO ()
localCode = do
field1 += 3
field2 .= 5.0
lift $ putStrLn "Done!"
globalCode :: StateT Type2 IO ()
globalCode = do
f1 <- zoom type1 $ do
localCode
use field1
field3 %= (++ show f1)
f3 <- use field3
lift $ putStrLn f3
main = runStateT globalCode (Type2 (Type1 9 4.0) "Hello: ")
zoom is not limited to immediate sub-fields of a type. Since lenses are composable, you can zoom as deep as you want in a single operation just by doing something like:
zoom (field1a . field2c . field3b . field4j) $ do ...
This sounds very much like an application of lenses.
Lenses are a specification of a sub-field of some data. The idea is you have some value toolLens and functions view and set so that view toolLens :: MultiTool h -> h fetches the tool and set toolLens :: MultiTool h -> h -> MultiTool h replaces it with a new value. Then you can easily define your withMember as a function just accepting a lens.
Lens technology has advanced a great deal recently, and they are now incredibly capable. The most powerful library around at the time of writing is Edward Kmett's lens library, which is a bit much to swallow, but pretty simple once you find the features you want. You can also search for more questions about lenses here on SO, e.g. Functional lenses which links to lenses, fclabels, data-accessor - which library for structure access and mutation is better, or the lenses tag.
I created a lensed extensible record library called data-diverse-lens which allows combining multiple ReaderT (or StateT) like this gist:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Lens
import Control.Monad.Reader
import Control.Monad.State
import Data.Diverse.Lens
import Data.Semigroup
foo :: (MonadReader r m, HasItem' Int r, HasItem' String r) => m (Int, String)
foo = do
i <- view (item' #Int) -- explicitly specify type
s <- view item' -- type can also be inferred
pure (i + 10, s <> "bar")
bar :: (MonadState s m, HasItem' Int s, HasItem' String s) => m ()
bar = do
(item' #Int) %= (+10) -- explicitly specify type
item' %= (<> "bar") -- type can also be inferred
pure ()
main :: IO ()
main = do
-- example of running ReaderT with multiple items
(i, s) <- runReaderT foo ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show i <> s -- prints out "12foobar"
-- example of running StateT with multiple items
is <- execStateT bar ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show (view (item #Int) is) <> (view (item #String) is) -- prints out "12foobar"
Data.Has is a simpler library that does the same with tuples. Example from the library front page:
{-# LANGUAGE FlexibleContexts #-}
-- in some library code
...
logInAnyReaderHasLogger :: (Has Logger r, MonadReader r m) => LogString -> m ()
logInAnyReaderHasLogger s = asks getter >>= logWithLogger s
queryInAnyReaderHasSQL :: (Has SqlBackEnd r, MonadReader r m) => Query -> m a
queryInAnyReaderHasSQL q = asks getter >>= queryWithSQL q
...
-- now you want to use these effects together
...
logger <- initLogger ...
sql <- initSqlBackEnd ...
(`runReader` (logger, sql)) $ do
...
logInAnyReaderHasLogger ...
...
x <- queryInAnyReaderHasSQL ...
...

choosing a monad at runtime

I'm trying to write a two-player game in Haskell, such as checkers. I envision having types GameState, Move, and a function result :: GameState -> Move -> GameState that defines the game rules. I want to have both human and automated players, and I figured I'd do this by having a typeclass:
class Player p m | p -> m where
selectMove :: p -> GameState -> m Move
where the idea would be that m could be Identity for a basic AI player, IO for a human, State for an AI that maintains state across moves, etc. The question is how to go from these to the overall game loop. I figure I could define something like:
Player p1 m1, Player p2 m2 => moveList :: p1 -> p2 -> GameState -> m1 m2 [Move]
a monadic function that takes in the players and initial state, and returns the lazy list of moves. But then on top of this let's say I want a text-based interface that, say, allows first selecting each player from a list of possibilities, then causes the game to be played. So I'd need:
playGame :: IO ()
I can't see how to define playGame given moveList in a generic way. Or is my overall approach not right?
EDIT: thinking further about it, I don't even see how to define moveList above. E.g., if player 1 was a human, so IO, and player 2 was a stateful AI, so State, the first move of player 1 would have type IO Move. Then player 2 would have to take the resulting state of type IO GameState and produce a move of type State IO Move, and player 1's next move would be of type IO State IO Move? That doesn't look right.
There are two parts to this question:
How to mix a monad-independent chess-playing framework with incremental monad-specific input
How to specify the monad-specific part at run time
You solve the former problem using a generator, which is a special case of a free monad transformer:
import Control.Monad.Trans.Free -- from the "free" package
type GeneratorT a m r = FreeT ((,) a) m r
-- or: type Generator a = FreeT ((,) a)
yield :: (Monad m) => a -> GeneratorT a m ()
yield a = liftF (a, ())
GeneratorT a is a monad transformer (because FreeT f is a monad transformer, for free, when f is a Functor). This means we can mix yield (which is polymorphic in the base monad), with monad-specific calls by using lift to invoke the base monad.
I'll define some fake chess moves just for this example:
data ChessMove = EnPassant | Check | CheckMate deriving (Read, Show)
Now, I'll define an IO based generator of chess moves:
import Control.Monad
import Control.Monad.Trans.Class
ioPlayer :: GeneratorT ChessMove IO r
ioPlayer = forever $ do
lift $ putStrLn "Enter a move:"
move <- lift readLn
yield move
That was easy! We can unwrap the result one move at a time using runFreeT, which will only demand the player input a move when you bind the the result:
runIOPlayer :: GeneratorT ChessMove IO r -> IO r
runIOPlayer p = do
x <- runFreeT p -- This is when it requests input from the player
case x of
Pure r -> return r
Free (move, p') -> do
putStrLn "Player entered:"
print move
runIOPlayer p'
Let's test it:
>>> runIOPlayer ioPlayer
Enter a move:
EnPassant
Player entered:
EnPassant
Enter a move:
Check
Player entered:
Check
...
We can do the same thing using the Identity monad as the base monad:
import Data.Functor.Identity
type Free f r = FreeT f Identity r
runFree :: (Functor f) => Free f r -> FreeF f r (Free f r)
runFree = runIdentity . runFreeT
NoteThe transformers-free packages defines these already (Disclaimer: I wrote it and Edward merged its functionality was merged into the free package. I only keep it for teaching purposes and you should use free if possible).
With those in hand, we can define pure chess move generators:
type Generator a r = Free ((,) a) r
-- or type Generator a = Free ((,) a)
purePlayer :: Generator ChessMove ()
purePlayer = do
yield Check
yield CheckMate
purePlayerToList :: Generator ChessMove r -> [ChessMove]
purePlayerToList p = case (runFree p) of
Pure _ -> []
Free (move, p') -> move:purePlayerToList p'
purePlayerToIO :: Generator ChessMove r -> IO r
purePlayerToIO p = case (runFree p) of
Pure r -> return r
Free (move, p') -> do
putStrLn "Player entered: "
print move
purePlayerToIO p'
Let's test it:
>>> purePlayerToList purePlayer
[Check, CheckMate]
Now, to answer your next question, which is how to choose the base monad at run time. This is easy:
main = do
putStrLn "Pick a monad!"
whichMonad <- getLine
case whichMonad of
"IO" -> runIOPlayer ioPlayer
"Pure" -> purePlayerToIO purePlayer
"Purer!" -> print $ purePlayerToList purePlayer
Now, here is where things get tricky. You actually want two players, and you want to specify the base monad for both of them independently. To do this, you need a way to retrieve one move from each player as an action in the IO monad and save the rest of the player's move list for later:
step
:: GeneratorT ChessMove m r
-> IO (Either r (ChessMove, GeneratorT ChessMove m r))
The Either r part is in case the player runs out of moves (i.e. reaches the end of their monad), in which case the r is the block's return value.
This function is specific to each monad m, so we can type class it:
class Step m where
step :: GeneratorT ChessMove m r
-> IO (Either r (ChessMove, GeneratorT ChessMove m r))
Let's define some instances:
instance Step IO where
step p = do
x <- runFreeT p
case x of
Pure r -> return $ Left r
Free (move, p') -> return $ Right (move, p')
instance Step Identity where
step p = case (runFree p) of
Pure r -> return $ Left r
Free (move, p') -> return $ Right (move, p')
Now, we can write our game loop to look like:
gameLoop
:: (Step m1, Step m2)
=> GeneratorT ChessMove m1 a
-> GeneratorT ChessMove m2 b
-> IO ()
gameLoop p1 p2 = do
e1 <- step p1
e2 <- step p2
case (e1, e2) of
(Left r1, _) -> <handle running out of moves>
(_, Left r2) -> <handle running out of moves>
(Right (move1, p2'), Right (move2, p2')) -> do
<do something with move1 and move2>
gameLoop p1' p2'
And our main function just selects which players to use:
main = do
p1 <- getStrLn
p2 <- getStrLn
case (p1, p2) of
("IO", "Pure") -> gameLoop ioPlayer purePlayer
("IO", "IO" ) -> gameLoop ioPlayer ioPlayer
...
I hope that helps. That was probably a bit over kill (and you can probably use something simpler than generators), but I wanted to give a general tour of cool Haskell idioms that you can sample from when designing your game. I type-checked all but the last few code blocks, since I couldn't come up with a sensible game logic to test on the fly.
You can learn more about free monads and free monad transformers if those examples didn't suffice.
My advice has two main parts:
Skip defining a new type class.
Program to the interfaces defined by existing type classes.
For the first part, what I mean is you should consider creating a data type like
data Player m = Player { selectMove :: m Move }
-- or even
type Player m = m Move
What the second part means is to use classes like MonadIO and MonadState to keep your Player values polymorphic, and choose an appropriate monad instance only at the end after combining all the players. For example, you might have
computerPlayer :: MonadReader GameState m => Player m
randomPlayer :: MonadRandom m => Player m
humanPlayer :: (MonadIO m, MonadReader GameState m) => Player m
Perhaps you will find there are other players you want, too. Anyway, the point of this is that once you've created all these players, if they are typeclass polymorphic as above, you may choose a particular monad that implements all the required classes and you are done. For example, for these three, you might choose ReaderT GameState IO.
Good luck!

Resources