Stuck in the State Monad - haskell

I want to create a graph structure using an IntMap of nodes and unique keys. This topic has been covered well here and here. I understand how the state monad works by basically wrapping a function of state -> (val,state) in a newtype so we can create a monad instance for it. I have read about the topic quite a bit. I still cant seem to get my head around how I can get unique (or just incremental) values throughout the execution of my program. It's easy enough to get a run of successive IDs, but once I "runState" to get out of the monad it seems like I'm back where I started with having to keep track of the current ID. I feel like I'm stuck in the monad. The other option I considered was to keep the entire IntMap and current "next" ID as the state, but that seems very "imperative" and extreme. This question is very similar but did not get many answers(or maybe I'm just missing something obvious). What is the idiomatic way to utilize the state monad to get unique ID throughout a program execution? Thanks.

Let's imagine we were to IO-ify the State monad. What would that look like? Our pure State monad is just a newtype around:
s -> (a, s)
Well, the IO version might do a little bit of side effects before returning the final values, which would look like:
s -> IO (a, s)
That pattern is so common it has a name, specifically StateT:
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
The name has a T at the end because it is a monad Transformer. We call m the "base monad" and StateT s m the "transformed" monad.
StateT s m is only a Monad if m is a Monad:
instance (Monad m) => Monad (StateT s m) where {- great exercise -}
However, in addition to that, all monad transformers implement the MonadTrans class, defined as follows:
class MonadTrans t where
lift :: (Monad m) => m a -> t m a
instance MonadTrans (StateT s) where {- great exercise -}
If t is StateT s, then lift's type specializes to:
lift :: m a -> StateT s m a
In other words, it lets us "lift" an action in the base monad to become an action in the transformed monad.
So, for your specific problem, you want the StateT (IntMap k v) IO monad, which extends IO with additional State. Then you can write your entire program in this monad:
main = flip runStateT (initialState :: IntMap k v) $ do
m <- get -- retrieve the map
lift $ print m -- lift an IO action
(k, v) <- lift readLn
put (insert k v m)
Notice that I still use get and put. That's because the transformers package implements all the concepts I described and it generalizes the signatures of get and put to be:
get :: (Monad m) => StateT s m s
put :: (Monad m) => s -> StateT s m ()
That means they automatically work within StateT. transformers then just defines State as:
type State s = StateT s Identity
That means that you can use get and put for both State and StateT.
To learn more about monad transformers, I highly recommend Monad Transformers - Step by Step.

Related

Monad transformer Inner structural order

I have been wondering why Monad Transformers has for example m(Maybe(m(Maybe a)) structural order and why not Maybe(m(Maybe( m a))). I have tried to implement the second one but I'm unable to complete it possibly BCS of my inadequate Haskell knowledge.
In all monad transformers, do we always have a structure like this?
if yes then why?
if not then when to choose one from another?
newtype MaybeOT m a = MaybeOT {runMaybeOT :: Maybe (m a) }
instance (Monad m) => Monad (MaybeOT m) where
return = pure
(MaybeOT mma) >>= f = MaybeOT $
case mma of
Nothing -> Nothing
(Just ma) -> inner ma where
inner ma = do
a <- ma
undefined
You've essentially discovered why monad transformers are inwards instead of outwards (nit: I'm pretty sure I'm not using correct terminology here, but you get what I mean - feel free to correct me here). It's much easier (easy == less constraints) to have the monad you know about be in the data position (inside), rather than the container position (outside). Intuitively, you can see why - after all, the monadic nature demands the container to be the same. You can do whatever you want with the data, but you must not change the type of the container during binding.
Of course, it's easier to realize all this by actually trying to implement the absurd. Which is what this is about. The final step you'll be stuck on while implementing >>=/bind for MaybeOT is this-
m a >>= ??? . runMaybeOT . f
Where, m is a Monad, m a :: m a, f :: a -> MaybeOT m a, and runMaybeOT :: MaybeOT m a -> Maybe (m a) (and also ??? :: ???, hehe)
Now, you must obtain a monad with the container type m to successfully bind on m a. But alas, you cannot get the m a out of Maybe (m a)! What happens when it's Nothing? Your primary tool in implementing monad transformers is knowledge about the specific monad you're implementing the transformer for. And your knowledge is telling you that this is absurd.
In contrast, the final step in implementing >>= for MaybeT goes well smoothly. For completeness, here's MaybeT-
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
Here, you'll be binding on the type m (Maybe a). During binding, you must return the type m b, for whatever b. You're given a function, f, of type a -> MaybeT m b, you can easily get m (Maybe b) from MaybeT m b.
Aha! Now you can see the solution. The function you're given returns the same outer monad as the one you're binding on. That is precisely what you need. In the case of MaybeOT, you were stuck with binding on the monad m, with a function that doesn't return a value with outer monad m!
And that is the crucial realization - the function you're given must be able to give you a value with the same outer monad. This is why MaybeT (and other transformers too) keeps the unknown monad outwards - because when you implement >>= for MaybeT, you know the binding function will be required to construct that outer monad.
It is helpful, at least intuitively, to note that the problem you get stuck on here - is the very same problem you'll face when implementing monadic composition. That is, >>= for nested monads. Monads don't compose! That's why you need monad transformers!
If you break this problem down, you'll notice that if you just had a function that could swap monads, to get Maybe (m a) from m (Maybe a) and vice versa - all would be well. Monads would compose, monad transformers could look like however you please, and in fact, monad transformers would essentially serve no purpose. This detail is noticed in the answer linked above. All you need is-
swap :: (Monad m, Monad n) => m (n a) -> n (m a)
This exists. They're called traversable monads, and indeed if you merely add the Traversable constraint to your Monad implementation for MaybeOT, you strike gold-
instance (Traversable m, Monad m) => Monad (MaybeOT m) where
return = pure
MaybeOT Nothing >>= _ = MaybeOT Nothing
MaybeOT (Just ma) >>= f = MaybeOT $ sequence $ ma >>= sequence . runMaybeOT . f
I assume it's law-conforming, though I'd have to check.
In another note, it is totally possible to make MaybeOT a law conforming applicative. After all, the problem you face while implementing Monad is simply non existent here. Applicatives do compose.
instance Applicative f => Applicative (MaybeT f) where
pure = MaybeT . pure . Just
MaybeT f <*> MaybeT a = MaybeT $ liftA2 (<*>) f a
(Or, perhaps more simply)
instance Applicative f => Applicative (MaybeT f) where
pure = MaybeT . pure . Just
MaybeT f <*> MaybeT a = MaybeT $ (<*>) <$> f <*> a
Which should be law conforming, as far as I can tell.

Is every repeatedly nested monads useful?

By the title, I mean types like Monad m => m (m a).
When the structure of a monad is simple, I can easily think of a usage of such type:
[[a]], which is a multidimensional list
Maybe (Maybe a), which is a type adjoined by two error states
Either e (Either e a), which is like above, but with messages
Monoid m => (m,(m,a)), which is a writer monad with two things to write over
r -> r -> a, which is a reader monad with two things to read from
Identity (Identity a), which is still the identity monad
Complex (Complex a), which is a 2-by-2 matrix
But it goes haywire in my mind if I think about the following types:
ReadP (ReadP a)? Why would it be useful when ReadP isn't an instance of Read?
ReadPrec (ReadPrec a)? Like above?
Monad m => Kleisli m a (Kleisli m a b)?
IO (IO a)!? This must be useful. It just is too hard to think about it.
forall s. ST s (ST s a)!? This should be like the above.
Is there a practical use for such types? Especially for the IO one?
On the second thought, I might need to randomly pick an IO action. That's an example of IO (IO a) which focuses on inputs. What about one focusing on outputs?
In some sense, a monad can be thought of as a functor in which layers can be collapsed.
If the Monad class were defined more like the category-theory definition, it would look like
class Applicative m => Monad m where
return :: a -> m a
join :: m (m a) -> m a
Using fmap with a function of type a -> m b results in a function of type m a -> m (m b). join is used to eliminate one layer of monad from the result. Since that's a common thing to do, one might define a function that does it.
foo :: Monad m => (a -> m b) -> m a -> m b
foo f ma = join (fmap f ma)
If you look carefully, you'll recognize foo as >>= with its arguments flipped.
foo = flip (>>=)
Since >>= is used more than join would be, the typeclass definition is
class Applicative m => Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
and join is defined as a separate function
join :: Monad m => m (m a) -> m a
join mma = mma >>= id
Does not matter.
Monads are monads precisely because for every Monad ( Monad a ) we can always get Monad a. Such operation is called "join" and it's alternative operation to "bind" that could form definition of Monad. Haskell uses "bind" because its much more useful for composing monadic code :)
(join can be implemented with bind, and bind with join - they are equivalent)
Does not matter
Is actually small lie, since ability to form Monad ( Monad a ) is also de facto part of what makes Monads monads. With Monad (Monad a) being transitional representation in some operations.
Full answer is: Yes, because that enables Monads. Though Monad ( Monad a ) can have extra "domain" meaning as you list for some of the Monads ;)

Confusion about StateT, State and MonadState

I'm utterly confused between
newtype StateT s m a = StateT {runStateT :: s -> m (a, s)}
and
type State s = StateT s Identity
and
class Monad m => MonadState s m | m -> s
Once upon a time, there was a State type:
-- Not the current definition.
newtype State s a = State {runState :: s -> (a, s)}
State s a values are, in essence, functions that take a state and produce a result and an updated state. Suitable Functor, Applicative and Monad instances make it possible to compose such functions in a more convenient manner, by making the tuple shuffling need to handle the (a, s) output implicit. With the help of a handful basic of operations that manipulate the state...
get = State $ \s -> (s, s)
put s = State $ \_ -> ((), s)
... it is possible to avoid any mention of the underlying s -> (a, s) type, and write code that feels stateful.
StateT s is a monad transformer patterned after State s:
newtype StateT s m a = StateT {runStateT :: s -> m (a, s)}
This transformer adds the state processing capabilities described above atop a base monad, m. It comes with Functor, Applicative and Monad instances, as well as versions of get and put.
If m, the base monad, in StateT s m is Identity, the dummy functor...
newtype Identity a = Identity {runIdentity :: a}
... we get something equivalent to plain old State s. That being so, transformers defines State as a synonym...
type State s = StateT s Identity
... rather than as a separate type.
As for MonadState, it caters to two different needs. Firstly, we can use the monad transformers machinery to have StateT s m as a base monad for some other transformer in a stack of transformers (arbitrary example: MaybeT (StateT Int IO)). In that case, though, lift from MonadTrans becomes necessary to use get and put. One way of using the operations directly in such cases is through MonadState: it provides them as methods...
-- Abridged class definition.
class Monad m => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
state :: (s -> (a, s)) -> m a
... so that we can have instances for any combination of transformers involving StateT that we are interested in.
instance Monad m => MonadState s (StateT s m) where -- etc.
instance MonadState s m => MonadState s (MaybeT m) where -- etc.
-- And so forth
Secondly, if we want to have a state monad with an implementation different than the one in transformers, we can make it an instance of MonadState, so that we keep the same basic operations and, as long as we write type signatures in terms of MonadState, have it easier to change implementations if need be.
State is for your normal state monad. This is the simplest of the three. (In some older tutorials, you may see use of the State constructor, but this has been replaced with the state function, because State s is now a type alias for StateT s Identity.)
StateT is the monad transformer for the State monad. It adds a layer of generality by allowing you to put an arbitrary monad inside the state. This is useful for simple parsers, which could use e.g. StateT [Token] Maybe Result to represent the parsing as a stateful operation that could fail.
MonadState generalizes the situation even farther. There is an instance Monad m => MonadState s (StateT s m), but there are also instances, like one that allows you to perform stateful operations on monad transformers of StateT. All basic state functions (get, set, modify, etc.) can be used with an instance of MonadState.

Is there a library or typeclass for getting the transformer version of a monad?

In my current project I've run into the need to turn various monads into their transformer counterparts e.g.
stateT :: Monad m => State s a -> StateT s m a
stateT stf = StateT $ return . runState stf
It's trivial to write these utility functions for the monads I need, but I was wondering if there already exists a library that contains this functionality for the standard monads and maybe a typeclass that abstracts this sort of transformation. Something like
class (Monad f, MonadTrans t) => LiftTrans f t | f -> t where
liftT :: Monad m => f a -> t m a
("lift" is probably the wrong term to use here, but I wasn't sure what else to call it.)
Check out function hoist from the mmorph package.
Its signature is
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b
Meaning that it can change the base monad underlying a transformer.
Now, in the trasformers package, many "basic" monads are implemented as transformers applied to the Identity monad, like this:
type State s = StateT s Identity
Therefore, we can define the following function (taken form the Generalizing base monads section of the mmorph documentation):
import Data.Functor.Identity
generalize :: (Monad m) => Identity a -> m a
generalize m = return (runIdentity m)
and combine it with hoist:
hoist generalize :: (Monad m, MFunctor t) => t Identity b -> t m b
This method won't work for simple monads which are not defined as transformers applied to Identity, like the Maybe and Either monads. You are stuck with hoistMaybe and hoistEither for these.
You are trying to go the wrong way. If something is a transformer, than the plain version of it is the transformer applied to the Identity monad. (They are not always implemented like that directly, but should be equivalent modulo bottom.) But, not all monads are transformers (They need to be universally left or universally right adjoint in order to transform. [citation needed])
hoist and friends are super helpful, too, but I think it best to invert your process.

Combining StateT and State monads

Lets say I have a function
f :: State [Int] Int
and a function:
g :: StateT [Int] IO Int
I want to use f in g and pass the state between them. Is there a library function for
StateT (return . runState f)? Or in general, given a monad transformer with a corresponding monad, is there a library function for it?
In even more general, what you're trying to do is apply a transformation to an inner layer of a transformer stack. For two arbitrary monads, the type signature might look something like this:
fmapMT :: (MonadTrans t, Monad m1, Monad m2) => (m1 a -> m2 a) -> t m1 a -> t m2 a
Basically a higher-level fmap. In fact, it would probably make even more sense to combine it with a map over the final parameter as well:
fmapMT :: (MonadTrans t, Monad m1, Monad m2) => (m1 a -> m2 b) -> t m1 a -> t m2 b
Clearly this isn't going to be possible in all cases, though when the "source" monad is Identity it's likely to be easier, but I can imagine defining another type class for the places it does work. I don't think there's anything like this in the typical monad transformer libraries; however, some browsing on hackage turns up something very similar in the Monatron package:
class MonadT t => FMonadT t where
tmap' :: FunctorD m -> FunctorD n -> (a -> b)
-> (forall x. m x -> n x) -> t m a -> t n b
tmap :: (FMonadT t, Functor m, Functor n) => (forall b. m b -> n b)
-> t m a -> t n a
tmap = tmap' functor functor id
In the signature for tmap', the FunctorD types are basically ad-hoc implementations of fmap instead of using Functor instances directly.
Also, for two Functor-like type constructors F and G, a function with a type like (forall a. F a -> G a) describes a natural transformation from F to G. There's quite possibly another implementation of the transformer map that you want somewhere in the category-extras package but I'm not sure what the category-theoretic version of a monad transformer would be so I don't know what it might be called.
Since tmap requires only a Functor instance (which any Monad must have) and a natural transformation, and any Monad has a natural transformation from the Identity monad provided by return, the function you want can be written generically for any instance of FMonadT as tmap (return . runIdentity)--assuming the "basic" monad is defined as a synonym for the transformer applied to Identity, at any rate, which is generally the case with transformer libraries.
Getting back to your specific example, note that Monatron does indeed have an instance of FMonadT for StateT.
What you are asking for is a mapping (known as a monad morphism) from a monad StateT m to StateT n. I'll be using the the mmorph library, which provides a very nice set of tools for working with monad morphisms.
To perform the State -> StateT m transform you are looking for, we'll start by defining a morphism to generalize the Identity monad embedded in State,
generalize :: Monad m => Identity a -> m a
generalize = return . runIdentity
Next we'll want to lift this morphism to act on the inner monad of your StateT. That is, we want a function which given a mapping from one monad to another (e.g. our generalize morphism), will give us a function acting on the base monad of a monad transformer, e.g. t Identity a -> t m a. You'll find this resembles the hoist function of mmorph's MFunctor class,
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b
Putting the pieces together,
myAction :: State s Int
myAction = return 2
myAction' :: Monad m => StateT s m Int
myAction' = hoist generalize myAction
Such a function is not definable for all monad transformers. The Cont r monad, for example, can't be lifted into ContT r IO because that would require turning a continuation in the IO monad (a -> IO r) into a pure continuation (a -> r).

Resources