Monad Transformer stacks with MaybeT and RandT - haskell

I'm trying to learn how Monad Transformers work by re-factoring something I wrote when I first learned Haskell. It has quite a few components that could be replaced with a (rather large) stack of Monad Transformers.
I started by writing a type alias for my stack:
type SolverT a = MaybeT
(WriterT Leaderboard
(ReaderT Problem
(StateT SolutionState
(Rand StdGen)))) a
A quick rundown:
Rand threads through a StdGen used in various random operations
StateT carries the state of the solution as it gets progressively evaluated
ReaderT has a fixed state Problem space being solved
WriterT has a leaderboard constantly updated by the solution with the best version(s) so far
MaybeT is needed because both the problem and solution state use lookup from Data.Map, and any error in how they are configured would lead to a Nothing
In the original version a Nothing "never" happened because I only used a Map for efficient lookups for known key/value pairs (I suppose I could refactor to use an array). In the original I got around the Maybe problem by making a liberal use of fromJust.
From what I understand having MaybeT at the top means that in the event of a Nothing in any SolverT a I don't lose any of the information in my other transformers, as they are unwrapped from outside-in.
Side question
[EDIT: This was a problem because I didn't use a sandbox, so I had old/conflicting versions of libraries causing an issue]
When I first wrote the stack I had RandT at the top. I decided to avoid using lift everywhere or writing my own instance declarations for all the other transformers for RandT. So I moved it to the bottom.
I did try writing an instance declaration for MonadReader and this was about as much as I could get to compile:
instance (MonadReader r m,RandomGen g) => MonadReader r (RandT g m) where
ask = undefined
local = undefined
reader = undefined
I just couldn't get any combination of lift, liftRand and liftRandT to work in the definition. It's not particularly important but I am curious about what a valid definition might be?
Problem 1
[EDIT: This was a problem because I didn't use a sandbox, so I had old/conflicting versions of libraries causing an issue]
Even though MonadRandom has instances of everything (except MaybeT) I still had to write my own instance declarations for each Transformer:
instance (MonadRandom m) => MonadRandom (MaybeT m) where
getRandom = lift getRandom
getRandomR = lift . getRandomR
getRandoms = lift getRandoms
getRandomRs = lift . getRandomRs
I did this for WriterT, ReaderT and StateT by copying the instances from the MonadRandom source code. Note: for StateT and WriterT they do use qualified imports but not for Reader. If I didn't write my own declarations I got errors like this:
No instance for (MonadRandom (ReaderT Problem (StateT SolutionState (Rand StdGen))))
arising from a use of `getRandomR'
I'm not quite sure why this is happening.
Problem 2
With the above in hand, I re-wrote one of my functions:
randomCity :: SolverT City
randomCity = do
cits <- asks getCities
x <- getRandomR (0,M.size cits -1)
--rc <- M.lookup x cits
return undefined --rc
The above compiles and I think is how transformers are suppose to be used. In-spite of the tedium of having to write repetitive transformer instances, this is pretty handy. You'll notice that in the above I've commented out two parts. If I remove the comments I get:
Couldn't match type `Maybe'
with `MaybeT
(WriterT
Leaderboard
(ReaderT Problem (StateT SolutionState (Rand StdGen))))'
Expected type: MaybeT
(WriterT
Leaderboard (ReaderT Problem (StateT SolutionState (Rand StdGen))))
City
Actual type: Maybe City
At first I thought the problem was about the types of Monads that they are. All of the other Monads in the stack have a constructor for (\s -> (a,s)) while Maybe has Just a | Nothing. But that shouldn't make a difference, the type for ask should return Reader r a, while lookup k m should give a type Maybe a.
I thought I would check my assumption, so I went into GHCI and checked these types:
> :t ask
ask :: MonadReader r m => m r
> :t (Just 5)
(Just 5) :: Num a => Maybe a
> :t MaybeT 5
MaybeT 5 :: Num (m (Maybe a)) => MaybeT m a
I can see that all of my other transformers define a type class that can be lifted through a transformer. MaybeT doesn't seem to have a MonadMaybe typeclass.
I know that with lift I can lift something from my transformer stack into MaybeT, so that I can end up with MaybeT m a. But if I end up with Maybe a I assumed that I could bind it in a do block with <-.
Problem 3
I actually have one more thing to add to my stack and I'm not sure where it should go. The Solver operates on a fixed number of cycles. I need to keep track of the current cycle vs the max cycle. I could add the cycle count to the solution state, but I'm wondering if there is an additional transformer I could add.
Further to that, how many transformers is too many? I know this is incredibly subjective but surely there is a performance cost on these transformers? I imagine some amount of fusion can optimise this at compile time so maybe the performance cost is minimal?

Problem 1
Can't reproduce. There are already these instances for RandT.
Problem 2
lookup returns Maybe, but you have a stack based on MaybeT. The reason why there is no MonadMaybe is that the corresponding type class is MonadPlus (or more general Alternative) - pure/return correspond to Just and empty/mzero correspond to Nothing. I'd suggest to create a helper
lookupA :: (Alternative f, Ord k) => k -> M.Map k v -> f v
lookupA k = maybe empty pure . M.lookup k
and then you can call lookupA wherever you need in your monad stack
As mentioned in the comments, I'd strongly suggest to use RWST, as it's exactly what fits your case, and it's much easier to work with than the stack of StateT/ReaderT/WriterT.
Also think about the difference between
type Solver a = RWST Problem Leaderboard SolutionState (MaybeT (Rand StdGen)) a
and
type Solver a = MaybeT (RWST Problem Leaderboard SolutionState (Rand StdGen)) a
The difference is what happens in the case of a failure. The former stack doesn't return anything, while the latter allows you to retrieve the state and the Leaderboard computed so far.
Problem 3
The easiest way is to add it into the state part. I'd just include it into SolutionState.
Sample code
import Control.Applicative
import Control.Monad.Random
import Control.Monad.Random.Class
import Control.Monad.Trans
import Control.Monad.Trans.Maybe
import Control.Monad.RWS
import qualified Data.Map as M
import Data.Monoid
import System.Random
-- Dummy data types to satisfy the compiler
data Problem = Problem
data Leaderboard = Leaderboard
data SolutionState = SolutionState
data City = City
instance Monoid Leaderboard where
mempty = Leaderboard
mappend _ _ = Leaderboard
-- dummy function
getCities :: Problem -> M.Map Int City
getCities _ = M.singleton 0 City
-- the actual sample code
type Solver a = RWST Problem Leaderboard SolutionState (MaybeT (Rand StdGen)) a
lookupA :: (Alternative f, Ord k) => k -> M.Map k v -> f v
lookupA k = maybe empty pure . M.lookup k
randomCity :: Solver City
randomCity = do
cits <- asks getCities
x <- getRandomR (0, M.size cits - 1)
lookupA x cits

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.

'ExceptT ResourceT' vs 'ResourceT ExceptT'

Real World Haskell states that "Transformer stacking order is important". However, I can't seem to figure out if there's a difference between ExceptT (ResourceT m) a and ResourceT (ExceptT m) a. Will they interfere with each other?
In this example, there is no real difference between both orders. The reason being: unlike many transformers including ExceptT, the resource transformer does not “inject” its own doings into the base monad you apply it to, but rather start off the entire action with passing in the release references.
If you write out the types (I'll refer to MaybeT instead of ExceptT for the sake of simplicity; they're obviously equivalent for the purpose of this question) then you have basically
type MaybeResourceT m a = MaybeT (IORef RelMap -> m a)
= IORef RelMap -> m (Maybe a)
type ResourceMaybeT m a = ResourceT (m (Maybe a))
= IORef RelMap -> m (Maybe a)
i.e. actually equivalent types. I suppose you could also show that for the operations.

State monad with Predicates

I'm attempting to create something that looks a lot like the State monad, but also carries a list of predicates and accompanying transition functions over the state. The basic steps for computation I'm envisioning are like follows:
Foo (state, [(pred, t)]) >>= f. Apply f to s, yielding s'. Then apply each predicate to s'. For each predicate that matches, apply the associated transition function to the state in sequence. E.g. suppose [(p1, t1), (p2, t2), (p3, t3)], f, and s. If after f s yields s', p1 s' and p3 s' both return True, you would perform t1 s' yielding s'' and then perform t3 s'' yielding s''', the result of the computation.
There's a lot of moving parts here, and I feel as if the correct approach would be to build this on top of the StateT transformer or the State monad, however I can't figure out where to start.
I feel as if this isn't terribly clear. Any clarifications that would make this clearer are much appreciated.
I don't think you can make the monad you're asking for. As I was mentioning in my discussion with jozefg, we have two monad laws that say
f >=> return = f
return >=> f = f
which means that nothing "interesting" can happen at a binding location. In particular, we can't run a state-transition function at each binding, because then f >=> return will run that transition function and f won't, and these laws will be broken.
However, that doesn't stop us from making a monadic action that runs the state transitions on our behalf. So I'll sketch the idea for how to design a monad that tracks such transitions and runs them on demand. You'll surely need to flesh out the API some if you want it to be useful. The basic idea is that instead of just an s as state, we'll store both an s and a transition table. First, some boilerplate.
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
import Control.Arrow
import Control.Applicative
import Control.Monad.State
For now, let's just work with s -> s transitions. You can implement them however you like -- including looking in a list of predicates and transitions and picking out the ones you want to run, if that's your cup of tea. But that's orthogonal to getting the rest of the idea right. We'll define our new type and give it a Monad instance that just dispatches to the underlying type.
newtype TStateT s m a = TStateT { unTStateT :: StateT (s, s -> s) m a }
deriving (Functor, Applicative, Monad)
The MonadState instance is a bit trickier than just using deriving, but still pretty straightforward. Presumably publically we want to pretend that only s is part of the state, so we need to focus our attention a bit. We'll also give the runStateT analog, and pick a sane initial transition function. (We'll give a way to modify this choice later.)
instance Monad m => MonadState s (TStateT s m) where
state f = TStateT (state (\(s, t) -> let (v, s') = f s in (v, (s', t))))
runTStateT :: Functor m => TStateT s m a -> s -> m (a, s)
runTStateT m s = second fst <$> runStateT (unTStateT m) (s, id)
Now comes the interesting bit. The superpower of TStateT is that it has some transitions it can run at any time. So let's provide a way to run them and a way to modify the transition table.
step :: Monad m => TStateT s m ()
step = TStateT (gets snd) >>= modify
modifyTransitions :: Monad m => ((s -> s) -> (s -> s)) -> TStateT s m ()
modifyTransitions = TStateT . modify . second
And that's pretty much everything!

Transformation under Transformers

I'm having a bit of difficulty with monad transformers at the moment. I'm defining a few different non-deterministic relations which make use of transformers. Unfortunately, I'm having trouble understanding how to translate cleanly from one effectful model to another.
Suppose these relations are "foo" and "bar". Suppose that "foo" relates As and Bs to Cs; suppose "bar" relates Bs and Cs to Ds. We will define "bar" in terms of "foo". To make matters more interesting, the computation of these relations will fail in different ways. (Since the bar relation depends on the foo relation, its failure cases are a superset.) I therefore give the following type definitions:
data FooFailure = FooFailure String
data BarFailure = BarSpecificFailure | BarFooFailure FooFailure
type FooM = ListT (EitherT FooFailure (Reader Context))
type BarM = ListT (EitherT BarFailure (Reader Context))
I would then expect to be able to write the relations with the following function signatures:
foo :: A -> B -> FooM C
bar :: B -> C -> BarM D
My problem is that, when writing the definition for "bar", I need to be able to receive errors from the "foo" relation and properly represent them in "bar" space. So I'd be fine with a function of the form
convert :: (e -> e') -> ListT (EitherT e (Reader Context) a
-> ListT (EitherT e' (Reader Context) a
I can even write that little beast by running the ListT, mapping on EitherT, and then reassembling the ListT (because it happens that m [a] can be converted to ListT m a). But this seems... messy.
There's a good reason I can't just run a transformer, do some stuff under it, and generically "put it back"; the transformer I ran might have effects and I can't magically undo them. But is there some way in which I can lift a function just far enough into a transformer stack to do some work for me so I don't have to write the convert function shown above?
I think convert is a good answer, and using Control.Monad.Morph and Control.Monad.Trans.Either it's (almost) really simple to write:
convert :: (Monad m, Functor m, MFunctor t)
=> (e -> e')
-> t (EitherT e m) b -> t (EitherT e' m) b
convert f = hoist (bimapEitherT f id)
the slight problem is that ListT isn't an instance of MFunctor. I think this is the author boycotting ListT because it doesn't follow the monad transformer laws though because it's easy to write a type-checking instance
instance MFunctor ListT where hoist nat (ListT mas) = ListT (nat mas)
Anyway, generally take a look at Control.Monad.Morph for dealing with natural transformations on (parts of) transformer stacks. I'd say that fits the definition of lifting a function "just enough" into a stack.

Resources