Type inference seems like a magic - haskell

I have following code snippet and could not configure it out, how it works:
embedded :: MaybeT (ExceptT String (ReaderT () IO)) Int
embedded = return 1
How it is possible to give only a number and get such as type signature back? How does the compiler do that?

The choice of wording is a bit unfortunate. It's not the case that the expression return 1 gives back the type signature MaybeT (ExceptT String (ReaderT () IO)) Int.
As n.m. writes in the comments, if you don't supply a type, the expression is much more general:
Prelude> embedded = return 1
Prelude> :type embedded
embedded :: (Num a, Monad m) => m a
By annotating with a type, you explicitly state that you want something less general than that.
Specifically, you state that you want the type MaybeT (ExceptT String (ReaderT () IO)) Int.
How does return work? MaybeT m a is a Monad when m is a Monad, and return is defined like this:
return = lift . return
The right-hand return is the return function that belongs to the 'inner' Monad, whereas lift is defined by MonadTrans and lifts the underlying monadic value up to MaybeT.
That explains how a MaybeT value is created, but isn't the whole story.
In this case, the 'inner' Monad is ExceptT String (ReaderT () IO), which is another Monad (in fact, another MonadTrans). return is defined like this:
return a = ExceptT $ return (Right a)
Notice that this is another nested return, where the right-hand return belongs to yet another nested Monad.
In this case, the nested Monad is ReaderT () IO - another MonadTrans. It defines return like this:
return = lift . return
Yet another nested return, where the right-hand return is the return defined for IO (in this particular case).
All of this is parametrised with a, which in this case you've constrained to Int.
So return 1 first takes the pure value 1 and packages it in IO Int. This then gets lifted to ReaderT () IO Int, which again gets packaged into an ExceptT String (ReaderT () IO) Int. Finally, this values gets lifted to MaybeT.

Related

Return multiple monads

I´m reading some code in Haskell and I cannot understand and found an explanation of how if a function return a IO (whatever) it can have other types before that.
This function it would be clear a Maybe that return a IO Maybe
Maybe User -> IO (Maybe User)
But the next one from the scotty library return a monad ActionT of Text of IO Maybe??? My mind is about to explode!
Maybe User -> ActionT Text IO (Maybe User)
Type constructors in Haskell have their own "kind" system, which you can think of as a kind of type-system-for-types. The kinds themselves don't have names; instead they are represented as just stars. So:
Integer :: *
IO :: * -> *
(Actually kinds can have names, but that is a more advanced extension; never mind for now)
The ActionT type constructor in Scotty takes 3 arguments and has kind
ActionT :: * -> (* -> *) -> * -> *
The types are:
An error type, in this case Text.
An "inner" monad, which must of course be a type constructor itself taking one argument. If you try passing a Text as this parameter GHC will report a "kind error". In this case the inner monad is IO.
A return type. ActionT is a monad, so in this case the function you are talking about returns a Maybe User in exactly the same way as your first example does.
ActionT is a monad transformer: this means it takes an existing monad and layers more functionality on top. This allows the programmer to separate the new functionality from the monad being modified, increasing modularity.
For more insight, study the instances for ActionT. For instance, one of them is
(Monad m, ScottyError e) => Monad (ActionT e m)
This says that if m is an instance of monad and e is an instance of ScottyError then ActionT e m is also an instance of monad. The kind system allows for currying in much the same way as the type system does for function application, so the Monad typeclass knows that it's argument must be of kind * -> *, and behold, ActionT e m does indeed have kind * -> *.

Haskell and calling function.

data S = Sa Int
type PMO = StateT Int (ErrorT String IO)
cs :: S -> PMO ()
cs _ = do
mem <- get -- (*)
return ()
I've highlighted the line with (*). I have doubts why get function can be called. I know that get is function from State monad but I cannot see/grasp how it is known that there is such monad in fact. I see that returned type is PMO but it is just returned value. What does it has in common with get?
Mainly, I have an experience with imperative language programming so it makes me trouble to understand it.
Check out the type of get:
get :: MonadState s m => m s
And since in the type signature of cs you've told the compiler what m is, get becomes:
get :: StateT Int (ErrorT String IO) Int
That's just a monadic value, not a function. So where does the value named mem come from? Ultimately, the value that get provides comes from the initial state value supplied by runStateT (or execStateT or evalStateT).
If that still seems mysterious, I recommend studying up on how the state monad works.

Haskell: function signature

This program compiles without problems:
bar :: MonadIO m
=> m String
bar = undefined
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO bar
When I change bar to foo (argument name),
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO foo
I get:
Couldn't match type ‘m’ with ‘IO’
‘m’ is a rigid type variable bound by
the type signature for run2IO :: MonadIO m => m String -> m String
...
Expected type: IO String
Actual type: m String ...
Why are the 2 cases are not equivalent?
Remember the type of liftIO:
liftIO :: MonadIO m => IO a -> m a
Importantly, the first argument must be a concrete IO value. That means when you have an expression liftIO x, then x must be of type IO a.
When a Haskell function is universally quantified (using an implicit or explicit forall), then that means the function caller chooses what the type variable is replaced by. As an example, consider the id function: it has type a -> a, but when you evaluate the expression id True, then id takes the type Bool -> Bool because a is instantiated as the Bool type.
Now, consider your first example again:
run2IO :: MonadIO m => m Integer -> m Integer
run2IO foo = liftIO bar
The foo argument is completely irrelevant here, so all that actually matters is the liftIO bar expression. Since liftIO requires its first argument to be of type IO a, then bar must be of type IO a. However, bar is polymorphic: it actually has type MonadIO m => m Integer.
Fortunately, IO has a MonadIO instance, so the bar value is instantiated using IO to become IO Integer, which is okay, because bar is universally quantified, so its instantiation is chosen by its use.
Now, consider the other situation, in which liftIO foo is used, instead. This seems like it’s the same, but it actually isn’t at all: this time, the MonadIO m => m Integer value is an argument to the function, not a separate value. The quantification is over the entire function, not the individual value. To understand this more intuitively, it might be helpful to consider id again, but this time, consider its definition:
id :: a -> a
id x = x
In this case, x cannot be instantiated to be Bool within its definition, since that would mean id could only work on Bool values, which is obviously wrong. Effectively, within the implementation of id, x must be used completely generically—it cannot be instantiated to a specific type because that would violate the parametricity guarantees.
Therefore, in your run2IO function, foo must be used completely generically as an arbitrary MonadIO value, not a specific MonadIO instance. The liftIO call attempts to use the specific IO instance, which is disallowed, since the caller might not provide an IO value.
It is possible, of course, that you might want the argument to the function to be quantified in the same way as bar is; that is, you might want its instantiation to be chosen by the implementation, not the caller. In that case, you can use the RankNTypes language extension to specify a different type using an explicit forall:
{-# LANGUAGE RankNTypes #-}
run3IO :: MonadIO m => (forall m1. MonadIO m1 => m1 Integer) -> m Integer
run3IO foo = liftIO foo
This will typecheck, but it’s not a very useful function.
In the first, you're using liftIO on bar. That actually requires bar :: IO String. Now, IO happens to be (trivially) an instance on MonadIO, so this works – the compiler simply throws away the polymorphism of bar.
In the second case, the compiler doesn't get to decide what particular monad to use as the type of foo: it's fixed by the environment, i.e. the caller can decide what MonadIO instance it should be. To again get the freedom to choose IO as the monad, you'd need the following signature:
{-# LANGUAGE Rank2Types, UnicodeSyntax #-}
run2IO' :: MonadIO m
=> (∀ m' . MonadIO m' => m' String)
-> m String
run2IO' foo = liftIO foo
... however I don't think you really want that: you might then as well write
run2IO' :: MonadIO m => IO String -> m String
run2IO' foo = liftIO foo
or simply run2IO = liftIO.

Haskell synonym definition

Could someone explain me what the following synonim means and how to read it:
type TCM a = ErrorT String (StateT MyEnv IO) a
What I was able to understand up till now:
we say that we introduce new name for some type and now we say that we call it TCM and it has some parameter a
We have value constructor ErrorT (what makes ErrorT?) that takes three arguments: String, (StateT MyEnv IO) and a
(StateT MyEnv IO) - we say here that we have value constructor StateT and args MyEnv and IO. But what this type makes?
Am I right? Could anyone explain me how it works? Thanks for any responses.
Edit: Maybe someone could help me also with this. I have sth the following function in my program that evaluate Integer:
ms_exp :: Exp -> TCM ()
ms_exp (EInt integer) = do
return integer
and it have such error:
Couldn't match expected type `()' with actual type `Integer'
Any hints?
Well, the ErrorT type already had the a type parameter, if we wished, we could specialize it, that is, make type
type TCMInt = ErrorT String (StateT MyEnv IO) Int
However, we can leave it as a type parameter, as you did in your example.
No, ErrorT is not a value constructor, it is a type constructor. What makes an element of ErrorT? Well, that depends on what ErrorT is. I suppose it is Control.Monad.Error, and it is said that is is constructed by the runErrorT function.
Again, StateT is not a value constructor, it is a type constructor (created with newtype keyword acoording to this). As you can see from newtype State s a, the State type constructors expects two type names to construct a type, so your code passes MyEnv and IO, yielding the StateT MyEnv IO type.
To the update: your function expects to inject an element of () into the TCM monad by doing return () while you do return integer. You need either return () or change the type of ms_exp to Exp -> TCM Integer.

Combining ReaderT monads?

It seems that it would be useful to be able to combine different ReaderT environments.
For instance, a generic logging facility might look something like this:
logit :: Text -> ReaderT Bool IO ()
logit str = do debugflag <- ask
liftIO $ if debugflag then putStrLn ("debug: " ++ str) else return ()
This looks like a nice reusable component. So how would I go about integrating this definition with another ReaderT environment so that I could use both of them?
For instance, suppose I want to combine it with this ReaderT instance:
foo :: ReaderT Text IO ()
foo = ...
so that I can use both foo and logit in the same function.
You'll want to layer them into a stacked monad, but they can't be stacked together since both of them declare that IO is exactly the wrapped monad. Fortunately, your code is already general enough to lift this restriction. The most general types of your functions use MonadIO instead of specifically using IO. If you change the types to
logit :: MonadIO m => Text -> ReaderT Bool m ()
foo :: MonadIO m => ReaderT Text m ()
then the liftIO call will lift the IO actions through the entire stack to an IO monad at the bottom.
To be clear, the types you've written do not need to use liftIO—the same type would be satisfied by just lift, but since IO is (trivially) an instance of MonadIO then your (overly) specialized type will also pass the checker.

Resources