Type Variable Location in Transformers - haskell

Consider the State type - or at least a simplified version:
newtype State s a = State { runState :: s -> (a, s) }
Now, let's say we want to derive the StateT monad transformer. transformers defines it as follows:
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
Here, the m has been placed on the right of the function arrow, but outside the tuple. However, if we didn't know the correct answer, we might instead put m somewhere else:
newtype StateT s m a = StateT { runStateT :: m (s -> ( a, s)) }
newtype StateT s m a = StateT { runStateT :: s -> (m a, s) }
Obviously the version in transformers is correct, but why? More generally, how does one know where to put the type variable for the 'inner' monad when defining a monad transformer? Generalising even more, is there a similar rule for comonad transformers?

I think the difference can be easily understood when m ~ IO:
s -> IO (a, s)
is the type of an action which can read the current state s, perform IO depending on that (e.g. printing the current state, reading a line from the user), and then produce both the new state s, and a return value a.
Instead:
IO (s -> (a, s))
is the type of an action which immediately performs IO, without knowing the current state. After all the IO is over, it returns a pure function mapping the old state into a new state and a return value.
This is similar to the previous type, since the new state and return value can depend both on the previous state and the IO. However, the IO can not depend on the current state: e.g., printing the current state is disallowed.
Instead,
s -> (IO a, s)
is the type of an action which reads the current state s, and then performs IO depending on that (e.g. printing the current state, reading a line from the user), and then produce a return value a. Depdnding on the current state, bot not on the IO, a new state is produced. This type is effectively isomorphic to a pair of functions (s -> IO a, s -> s).
Here, the IO can read a line from the user, and produce a return value a depending on that, but the new state can not depend on that line.
Since the first variant is more general, we want that as our state transformer.
I don't think there's a "general rule" for deciding where to put m: it depends on what we want to achieve.

Related

StateMonad instance for TeletypeIO

So, I have this datatype (it's from here: https://wiki.haskell.org/IO_Semantics):
data IO a = Done a
| PutChar Char (IO a)
| GetChar (Char -> IO a)
and I thought of writing a StateMonad instance for it. I have already written Monad and Applicative instances for it.
instance MonadState (IO s) where
get = GetChar (\c -> Done c)
put = PutChar c (Done ())
state f = Done (f s)
I don't think I fully understand what state (it was named 'modify' before) is supposed to do here.
state :: (s -> (a, s)) -> m a
I also have messed up with declarations. I don't really understand what is wrong, let alone how to fix it. Would appreciate your help.
Expecting one more argument to ‘MonadState (IO s)’
Expected a constraint,
but ‘MonadState (IO s)’ has kind ‘(* -> *) -> Constraint’
In the instance declaration for ‘MonadState (IO s)’
As I mentioned in the comments, your type doesn't really hold any state, so a StateMonad instance would be nonsensical for it.
However, since this is just an exercise (also based on the comments), I guess it's ok to implement the instance technically, even if it doesn't do what you'd expect it to do.
First, the compiler error you're getting tells you that the MonadState class actually takes two arguments - the type of the state and the type of the monad, where monad has to have kind * -> *, that is, have a type parameter, like Maybe, or list, or Identity.
In your case, the monad in question (not really a monad, but ok) is IO, and the type of your "state" is Char, since that's what you're getting and putting. So the declaration has to look like this:
instance MonadState Char IO where
Second, the state method doesn't have the signature (s -> s) -> m s as you claim, but rather (s -> (a, s)) -> m a. See its definition. What it's supposed to do is create a computation in monad m out of a function that takes a state and returns "result" plus new (updated) state.
Note also that this is the most general operation on the State monad, and both get and put can be expressed in terms of state:
get = state $ \s -> (s, s)
put s = state $ \_ -> ((), s)
This means that you do not have to implement get and put yourself. You only need to implement the state function, and get/put will come from default implementations.
Incidentally, this works the other way around as well: if you define get and put, the definition of state will come from the default:
state f = do
s <- get
let (a, s') = f s
put s'
return a
And now, let's see how this can actually be implemented.
The semantics of the state's parameter is this: it's a function that takes some state as input, then performs some computation based on that state, and this computation has some result a, and it also may modify the state in some way; so the function returns both the result and the new, modified state.
In your case, the way to "get" the state from your "monad" is via GetChar, and the way in which is "returns" the Char is by calling a function that you pass to it (such function is usually referred to as "continuation").
The way to "put" the state back into your "monad" is via PutChar, which takes the Char you want to "put" as a parameter, plus some IO a that represents the computation "result".
So, the way to implement state would be to (1) first "get" the Char, then (2) apply the function to it, then (3) "put" the resulting new Char, and then (3) return the "result" of the function. Putting it all together:
state f = GetChar $ \c -> let (a, c') = f c in PutChar c' (Done a)
As further exercise, I encourage you to see how get and put would unfold, starting from the definitions I gave above, and performing step-by-step substitution. Here, I'll give you a couple first steps:
get = state $ \s -> (s, s)
-- Substituting definition of `state`
= GetChar $ \c -> let (a, c') = (\s -> (s, s)) c in PutChar c' (Done a)
-- Substituting (\s -> (s, s)) c == (c, c)
= GetChar $ \c -> let (a, c') = (c, c) in PutChar c' (Done a)
= <and so on...>
MonadState takes two arguments, in this order:
the type of the state
the monad
In this case the monad is IO:
instance MonadState _ IO where
...
And you need to figure out what goes in place of the underscore

Can IO action in negative position give unexpected results?

There seems to be some undocumented knowledge about the difference between Monad IO and IO. Remarks here and here) hint that IO a can be used in negative position but may have unintended consequences:
Citing Snoyman 1:
However, we know that some control flows (such as exception handling)
are not being used, since they are not compatible with MonadIO.
(Reason: MonadIO requires that the IO be in positive, not negative,
position.) This lets us know, for example, that foo is safe to use in
a continuation-based monad like ContT or Conduit.
And Kmett 2:
I tend to export functions with a MonadIO constraint... whenever it
doesn't have to take an IO-like action in negative position (as an
argument).
When my code does have to take another monadic action as an argument,
then I usually have to stop and think about it.
Is there danger in such functions that programmers should know about?
Does it for example mean that running arbitrary continuation-based action may redefine control flow giving unexpected results in ways that Monad IO based interface are safe from?
Is there danger in such functions that programmers should know about?
There is not danger. Quite the opposite, the point Snoyman and Kmett are making is that Monad IO doesn't let you lift through things with IO in a negative positive.
Suppose you want to generalize putStrLn :: String -> IO (). You can, because the IO is in a positive position:
putStrLn' :: MonadIO m => String -> m ()
putStrLn' str = liftIO (putStrLn str)
Now, suppose you want to generalize handle :: Exception e => (e -> IO a) -> IO a -> IO a. You can't (at least not with just MonadIO):
handle' :: (MonadIO m, Exception e) => (e -> m a) -> m a -> m a
handle' handler act = liftIO (handle (handler . unliftIO) (unliftIO act))
unliftIO :: MonadIO m => m a -> IO a
unliftIO = error "MonadIO isn't powerful enough to make this implementable!"
You need something more. If you're curious about how you'd do that, take a look at the implementation of functions in lifted-base. For instance: handle :: (MonadBaseControl IO m, Exception e) => (e -> m a) -> m a -> m a.

How does `get` work in the CPS version of the State monad?

I am trying to understand continuation in general following this tutorial.
However, I am having difficulties to understand following example in section 2.10:
# let get () =
shift (fun k -> fun state -> k state state) ;;
get : unit => ’a = <fun>
state is of type int I suppose. What I don't get is the type of k. According to my understanding, k captures all computation comes subsequently after get (), and since we are talking about a state monad, k is reasonable to represent a computation that will be continued by taking an int, hence
k : int => 'a
but from the code, it doesn't seem to do that and it takes state for a second time, which actually implies:
k : int => int => 'a
but I don't get where the second one is coming from, and in which sense get is of type unit => 'a instead of unit => int => 'a?
Compared to the actual state monad implementation, the confusion adds more:
newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
i.e. state transition is represented as a function from state to a tuple of result and state, which matches my first understanding.
Can anyone give a lead?
Secondly, how am I supposed to implement get here using Haskell's Control.Monad.Trans.Cont? I am having problems comforting the type system.
UPDATE
It seems I got the second one:
Prelude Control.Monad.Trans.Cont> let get () = shift $ \k -> return $ \i -> k i i
But I still don't get why I need to apply the state twice to the continuation.
You apply k on state twice because the first one corresponds to the result of get () (we want get's effect to be retrieving the current state and returning it as the result) and the second one corresponds to passing the state after the get (which, because get doesn't change the state, is the same as the state before the get) to the next stateful computation.
In other words, since the state monad is State s a ~ s -> (a, s), its CPS version is State s r a ~ s -> (a -> s -> r) -> r, and so for get : State s s, because a ~ s, the continuation will be a function of type s -> s -> r.

'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.

Meaning of a newtype statement

I have this statement:
newtype State st a = State (st -> (st, a))
Hence the type of State is:
State :: (st -> (st, a)) -> State st a
I cannot understand the meaning:
Are st and a just placeholder of two data-type? Right?
Does the statement means that State is a function that take as argument a function?
Yes. Data constructors are functions in Haskell, with the additional feature that you can pattern match against them. So, for example, if you have list of type fs : [st -> (st, a)] you can do map State fs :: [State st a].
The way the state monad works conventionally is that State st a represents a state transformer: a thing that takes an initial state, performs some computation that may depend or alter that state, and produces a result of type a. Composing two state transformers means creating a composite one that executes the first one with the initial state, and then executes the second one with the state that holds after the first one executes.
So the State monad implementation models that directly as a function of type st -> (st, a). Composing two such functions is just a matter of generating a composite function that feeds the initial state to the first one, passes the state that results from that to the second one, and returns the final state and result of the second one. In code:
bindState :: State st a -> (a -> State st b) -> State st b
bindState (State function1) f =
State $ \initialState -> let (nextState, firstResult) = function1 initialState
in f firstResult
Yes and yes. The st is the state type and the a is the answer type.

Resources