Why is FunctionalDependency needed for defining MonadReader? - haskell

I just managed to understand the definition of the class MonadReader
class Monad m => MonadReader r m | m -> r where
...
After reading the document of Functional Dependency in Haskell, now I can understand that | m -> r specifies that type variable r is uniquely decided by m. I think this requirement is reasonable based on the few typical instances of MonadReader I have seen so far (e.g. Reader), but it seems to me that we can still define instances like Reader even without this functional dependency clause.
My question is why we need functional dependency in the definition of MonadReader? Is this functionally necessary for defining MonadReader in a sense that MonadReader cannot be properly defined without it, or it is merely a restriction to limit the ways how MonadReader can be used so that the instances of MonadReader will all behave in a certain expected way?

It is needed to make type inference work in a way which is more convenient to the user.
For example, without the fundep this would not compile:
action :: ReaderT Int IO ()
action = do
x <- ask
liftIO $ print x
To make the above compile we would need to write
action :: ReadertT Int IO ()
action = do
x <- ask :: ReadertT Int IO Int
liftIO $ print x
This is because, without the fundep, the compiler can not infer that x is an Int. After all a monad ReadertT Int IO might have multiple instances
instance MonadReader Int (ReaderT Int IO) where
ask = ReaderT (\i -> return i)
instance MonadReader Bool (ReaderT Int IO) where
ask = ReaderT (\i -> return (i != 0))
instance MonadReader String (ReaderT Int IO) where
ask = ReaderT (\i -> return (show i))
-- etc.
so the programmer must provide some annotation which forces x :: Int, or the code is ambiguous.

This is not really an answer, but it's much too long for a comment. You are correct that it's possible to define the MonadReader class without a fundep. In particular, the type signature of each method determines every class parameter. It would be quite possible to define a finer hierarchy.
class MonadReaderA r m where
askA :: m r
askA = readerA id
readerA :: (r -> a) -> m a
readerA f = f <$> askA
-- This effect is somewhat different in
-- character and requires special lifting.
class MonadReaderA r m => MonadReaderB r m where
localB :: (r -> r) -> m a -> m a
class MonadReaderB r m
=> MonadReader r m | m -> r
ask :: MonadReader r m => m r
ask = askA
reader
:: MonadReader r m
=> (r -> a) -> m a
reader = readerA
local
:: MonadReader r m
=> (r -> r) -> m a -> m a
local = localB
The main problem with this approach is that users have to write a bunch of instances.

I think the source of confusion is that in the definition of
class Monad m => MonadReader r m | m -> r where
{- ... -}
It is implicitly asumed that m contains r itself (for common instances). Let me use a lighter definiton of Reader as
newtype Reader r a = Reader {runReader :: r -> a}
When the r parameter is chosen you can easely define a monad instance for Reader r. That means that in the type class definition m should be substitute for Reader r. So take a look at how the expresion ends up being:
instance MonadReader r (Reader r) where -- hey!! r is duplicated now
{- ... -} -- The functional dependecy becomes Reader r -> r which makes sense
But why do we need this?. Look at the definition of ask within the MonadReader class.
class Monad m => MonadReader r m | m -> r where
ask :: m r -- r and m are polymorphic here
{- ... -}
Without the fun-dep nothing could stop me for defining ask in a way to return a different type as the state. Even more, I could define many instances of monad reader for my type. As an example, this would be valid definitions without func-dep
instance MonadReader Bool (Reader r) where
-- ^^^^ ^
-- | |- This is state type in the user defined newtype
-- |- this is the state type in the type class definition
ask :: Reader r Bool
ask = Reader (\_ -> True) -- the function that returns True constantly
{- ... -}
instance MonadReader String (Reader r) where
-- ^^^^^^ ^
-- | |- This is read-state type in the user defined newtype
-- |- this is the read-state type in the type class definition
ask :: Reader r String
ask = Reader (\_ -> "ThisIsBroken") -- the function that returns "ThisIsBroken" constantly
{- ... -}
So if I had a value val :: ReaderT Int IO Double what would be the result of ask. We'd need to specify a type signature as below
val :: Reader Int Double
val = do
r <- ask :: Reader Int String
liftIO $ putStrLn r -- Just imagine you can use liftIO
return 1.0
> val `runReader` 1
"ThisIsBroken"
1.0
val :: Reader Int Double
val = do
r <- ask :: Reader Int Bool
liftIO $ print r -- Just imagine you can use liftIO
return 1.0
> val `runReader` 1
True
1.0
Aside from being senseless, it is unconvinient to be specifiying the type over and over.
As a conclusion using the actual definition of ReaderT. When you have something like val :: ReaderT String IO Int the functional dependency says Such a type might have only one single instance of MonadReader typeclass which is defined to be the one that uses String as r

Related

What's the use case for the MonadReader instance for (->) r

I find the MonadReader instance for (->) r difficult to understand.
Someone from irc mentions one use case for extending some polymorphic functions found in other people's package. I couldn't recall exactly what he meant. Here's an example that relates to what he said but I don't see the point. Could anyone give another example on the usecase of MonadReader for (->) r
func :: (Show a, MonadReader Int m) => Bool -> m a
func b = case b of
True -> do
i <- ask
show i
False -> "error"
main :: IO ()
main = print $ func True 5
The point is to make it easier to combine functions that all take the same environment.
Consider the type a -> Env -> b, where Env is some data type that contains all your "global" variables. Let's say you wanted to compose two such functions. You can't just write h = f2 . f1, because f1's return type Env -> b doesn't match f2's argument type b.
f1 :: a -> Env -> b -- a -> ((->) Env b)
f2 :: b -> Env -> c -- b -> ((->) Env c)
h :: a -> Env -> c
h x e = let v = f1 x e
in f2 v e
Because there is an applicable MonadReader instance for the monad (->) Env, you can write this as
-- The class, ignoring default method implementations, is
-- class Monad m => MonadReader r m | m -> r where
-- ask :: m r
-- local :: (r -> r) -> m a -> m a
-- reader :: (r -> a) -> m a
--
-- The functional dependency means that if you try to use (->) Env
-- as the monad, Env is forced to be the type bound to r.
--
-- instance MonadReader r ((->) r) where
-- ask = id
-- local f m = m . f
-- reader = id
h :: MonadReader Env m => a -> m c
h x = do
v <- f1 x
f2 v
-- h x = f1 x >>= f2
without explicit reference to the environment, which h doesn't
care about; only f1 and f2 do.
More simply, you can use the Kleisli composition operator to define the same function.
import Control.Monad
h :: MonadReader Env m => a -> m c
h = f1 >=> f2
In your example, ask is simply how you get access to the environment from inside the body of the function, rather than having it as a preexisting argument to the function. Without the MonadReader instance, you would write something like
func :: Show a => Bool -> Int -> a -- m ~ (->) Int
func b i = case b of
True -> show i
False -> error "nope"
The definition of main stays the same. However, (->) Int isn't the only type that has a MonadReader instance; there could be a more complicated monad stack
that you are using elsewhere, which the more general type (Show a, MonadReader Int m) => Bool -> m a allows you to use instead of "just" (->) Int.
I'm not sure it was intended to have a use case separate from the Reader monad.
Here's some of the history...
The inspiration for the transformers library was the set of lecture notes Functional Programming with Overloading and Higher-Order Polymorphism (Mark P. Jones, 1995). In these notes, several named monads (State, Id, List, Maybe, Error, and Writer) were discussed. For example, the Writer monad type and its instance were defined as:
data Writer a = Result String a
instance Monad Writer where
result x = Result "" x
Result s x ‘bind‘ f = Result (s ++ s’) y
where Result s’ y = f x
The reader monad was also discussed, but it wasn't defined as a separate type. Rather a Read type alias was used together with a Monad instance defined directly in terms of the partially applied function type (->) r:
type Read r = (r ->)
instance Monad (r->) where
result x = \r -> x
x ‘bind‘ f = \r -> f (x r) r
I don't actually know if these type-level "sections" (r ->) were valid Haskell syntax at the time. Anyway, it's not valid syntax with modern GHC versions, but that's how it appeared in the notes.
The first version of the transformers library authored by Andy Gill -- or at least the first that I was able to find, and it was actually still part of the base library at that time -- was checked into Git in June, 2001. It introduced the MonadReader class and the newtype wrapped Reader:
newtype Reader r a = Reader { runReader :: r -> a }
together with its Functor, Monad, MonadFix, and MonadReader instances. (No Applicative -- that hadn't been invented yet.) It also included a set of instances for (->) r with the comment:
The partially applied function type is a simple reader monad
So, I think the original formulation in the lecture notes led Andy to include these instances for (->) r, even though he also introduced a dedicated Reader newtype for consistency with the other monads in the transformers library.
Anyway, that's the history. As for use cases, I can only think of one serious one, though perhaps it isn't that compelling. The lens library is designed to interface well with MonadState and MonadReader to access complex states/contexts. Because functions like:
view :: MonadReader s m => Getting a s a -> m a
preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
review :: MonadReader b m => AReview t b -> m t
are defined in terms of the MonadReader instance, they can be used both in a traditional Reader context:
do ...
outdir <- view (config.directories.output)
...
and in a plain function context:
map (view (links.parent.left)) treeStructure
Again, not necessarily a compelling use case, but it's a use case.

How to read MonadReader and ask definition?

I am trying to figure out, how to read the following class type definition:
Prelude Data.Functor.Identity Control.Monad.Reader> :i ask
class Monad m => MonadReader r (m :: * -> *) | m -> r where
ask :: m r
...
m is a higher kinded type and it has to be a monad.
But what does m -> r means?
Trying to play a bit with ask as the following:
Prelude Data.Functor.Identity Control.Monad.Reader> ask "Hello"
"Hello"
Why can I pass an argument to ask? Looking at the type signature:
ask :: m r
I can not recognize, that I can pass an argument to ask.
The m -> r is a functional dependency, which roughly states that when trying to choose an instance of MonadReader to use, knowing m is sufficient for knowing r. Put another way, you can't define two separate instances with the same m but different r.
Now, to determine which definition of ask to use, we turn to type inference. From its definition, we know ask has type MonadReader r m => m r. From its use in ask "Hello", we know it also has to have a type like a -> b; more specifically, we know that a unifies with String, since that's the type of "Hello". So our task is to unify MonadReader r m => m r with String -> b.
This is pretty straightforward. Rewriting String -> b in prefix notation and using explicit parentheses , we can line them up together:
MonadReader r m => m r
((->) String) b
So m ~ ((->) String) and r ~ b (though we still don't know what r/b should be). Looking at the available instances of MonadReader, we find the (unique) instance for m ~ (->) String (or more generally, (->) r):
instance MonadReader r ((->) r) where
ask = id
local f m = m . f
So now we know that for our choice of m, ask = id. (This lets us see that r ~ b ~ String as well.)
And so, ask "Hello" == id "Hello" == "Hello".
Note that ask doesn't necessarily have to be a function. It might also be a value of type Reader r a, in which case runReader has to be used to extract the function.
> :t runReader ask
runReader ask :: a -> a
> runReader ask "Hello"
"Hello"
It might also be a more complicated monad involving ReaderT:
> :t runReaderT ask
runReaderT ask :: Monad m => a -> m a
> runReaderT ask "Hello" :: Maybe String
Just "Hello"
> runReaderT ask "Hello" :: Either String String
Right "Hello"

Can one compose types in a Haskell instance declaration?

I've written a Haskell typeclass and it would be convenient to declare instances of it using types of the form (a -> m _), where m is of kind (* -> *), such as a monad, and _ is a slot to be left unsaturated. I know how to write newtype X a m b = X (a -> m b), and declaring an instance for X a m. But what I'm looking for is to instead use the bare, unwrapped -> type, if that's possible.
If one wants to declare instances for types of the form (a -> _), then you can just write:
instance Foo a ((->) a) where ...
but I don't know how/whether one can do it with types of the form (a -> m _). I guess I'm looking to compose the type constructor (->) a _ and the type constructor m _ in my instance declaration.
I'd like to write something like this:
instance Foo a ((->) a (m :: *->*)) where ...
or:
instance Foo a ((->) a (m *)) where ...
but of course these don't work. Is it possible to do this?
Concretely, here's what I'm trying to achieve. I wrote a typeclass for
MonadReaders that are embedded inside (one level) of other MonadReaders,
like this:
{-# LANGUAGE FunctionalDependencies FlexibleInstances
UndecidableInstances #-}
class MonadReader w m => DeepMonadReader w r m | m -> r where
{ deepask :: m r
; deepask = deepreader id
; deeplocal :: (r -> r) -> m a -> m a
; deepreader :: (r -> a) -> m a
; deepreader f = do { r <- deepask; return (f r) }
}
instance MonadReader r m => DeepMonadReader w r (ReaderT w m) where
{ deepask = lift ask
; deeplocal = mapReaderT . local
; deepreader = lift . reader
}
It'd be nice to also provide an instance something like this:
instance MonadReader r m => DeepMonadReader w r ((->) w (m :: * ->
*)) where
{ deepask = \w -> ask
; deeplocal f xx = \w -> local f (xx w)
; deepreader xx = \w -> reader xx
}
I think you're on the wrong track and are making things a lot more
complicated than they need to be.
Some observations:
... ((->) w (m :: * -> *)) ...
Let's explore what you mean by this. You are using it for the type parameter m in your DeepMonadReader class, and therefore it needs to be a monad. Can you give a concrete example of a monad which
has this type? Why not just use ((->) w) ?
class MonadReader w m => DeepMonadReader w r m | m -> r where ...
The fact that w never apears in any member signatures is an indication something is amiss.
... I wrote a typeclass for MonadReaders that are embedded inside (one level) of other MonadReaders ...
I would take the reverse perspective. It makes sense to talk of monad stacks which are a transformed
version of another monad stack. E.g.:
StateT s (WriterT w IO) "contains" IO
WriterT w (Maybe a) "contains" Maybe a
And what does it mean for a monad stack m1 to "contain" another monad m2?
It just means that there is a way to convert computations in m2 to computations in m1:
convert :: m2 a -> m1 a
Of course, this is just lift when using monad transformers.
To express your concept of a monad reader embedded in another monad, I would use this
type class:
class HasReader m m' r where ...
deepAsk :: m r
deepLocal :: (r -> r) -> m' a -> m a
The idea here is that an instance HasReader m m' r expresses the fact that
monad m "contains" a monad m' which itself is a reader with
environment r.
deepAsk returns the environment of m' but as a computation in m.
deepLocal runs a computation in m' with a environment modification function
but returns it as a computation in m. Note how this type signature is different from yours:
my deepLocal uses different monads, m' and m whereas yours just goes from m to m.
The next step is decide which triples (m, m', r) do we want to write instances
of HasReader for. Clearly it seems you had instances like this in mind:
m m' r
--------------------- ----------- --
ReaderT s (ReaderT r m) ReaderT r m r
ReaderT t (ReaderT s (ReaderT r m) ReaderT s (Reader T r m) s
...
but it also seems reasonable to want to have these instances:
StateT s (ReaderT r m) ReaderT r m r
WriterT w (ReaderT r m) ReaderT r m r
MaybeT (ReaderT r m) ReaderT r m r
...
It turns out, though, that we don't need the HasReader class for any of these cases.
We can just write the expression as a computation in m' and lift it up to m.

Understanding (->) r as instance of Reader [duplicate]

This question already has answers here:
How to use (->) instances of Monad and confusion about (->)
(2 answers)
Closed 7 years ago.
So I'm told (->) r is an instance of the Reader monad, but I can't seem to find any concrete examples of how this is supposed to work. I want to use this without having to explicitly wrap some of my code in a Reader
import Control.Monad.Reader
testOne :: Reader String String
testOne = do
env <- ask
return $ "Hello, " ++ env
testTwo :: String -> String
testTwo = do
env <- ask
return $ "G'day, " ++ env
Running runReader testOne "there" works fine, but running runReader testTwo "mate" fails spectacularly with the following message:
Couldn't match type ‘String -> String’
with ‘ReaderT [Char] Data.Functor.Identity.Identity a’
Expected type: Reader [Char] a
Actual type: String -> String
So what am I missing here?
The type of runReader is runReader :: ReaderT r Identity -> r -> a, if you expand out the newtype Reader = ReaderT r Identity. I think you want something very generic, along the lines of this:
foo :: (MonadReader r m) => m a -> r -> a
So that you could evaluate both foo testOne "there" and foo testTwo "mate".
Unfortunately, no such function exists. The mtl library's job is to abstract the choice of the underlying concrete type. Both (->) String and Reader String = ReaderT String Identity are concrete types that obey the Monad and MonadReader laws, but that only guarantees you an interface of return, >>=, ask, reader, and local (and <$>, <*>, pure).
This is both limiting and useful!
Limiting: In order to "run" the computation represented by either type, you need to use the appropriate type-specific API. For (->) String, that's simply calling the function (the invisible function application operator); for Reader String, that's runReader.
Useful: you can expose, with a library, values constrained by MonadReader, knowing that users will only be able to use them with the MonadReader interface. This is nice, as you can use this trick to make sure that users aren't doing anything untoward, like doing early runs of your values with their own environments (r's).
runReader :: Reader r a -> r -> a is specifically for Reader newtype, which you want to avoid. Since testTwo is just a function, you simply use testTwo "mate".
If you want a generic way to run MonadReader, you could define your own type class for this. Approximately like this (untested):
class MonadReader r m => RunReader r m | m -> r where
type Output m a :: *
runReader' :: m a -> r -> Output m a
instance RunReader r ((->) r) where
type Output ((->) r) a = a
runReader' = ($)
instance Monad m => RunReader r (ReaderT r m) where
type Output (ReaderT r m) a = m a
runReader' = runReaderT
instance RunReader r m => RunReader r (MaybeT m) where
type Output (MaybeT m) a = Output m (Maybe a)
runReader' = runMaybeT . runReader'
-- any other instances
and then runReader' testOne and runReader' testTwo will work. See "Associated data and type families" for an explanation of use of type here.

Implicit type coercion?

I don't understand why this code typechecks:
error1 :: ErrorT String (ReaderT Int IO) Int
error1 = asks id
fyi, the asks has this type:
asks :: Monad m => (r -> a) -> ReaderT r m a
On the other hand, I'm able to understand, that this code typechecks:
reader1 :: ReaderT Int IO Int
reader1 = asks id
id has type a -> a and there is an instance of Monad for IO, so the compiler can infer the type. That's clear for me.
The ErrorT is newtype and haskell spec states, (in the section about newtypes):
... it creates a distinct type that must be explicitly coerced to or
from the original type ...
According to my interpretation, I should be able to get the same type as in error1 only explicitly, with some coercion similar to this:
reader2 :: ReaderT Int IO (Either String Int)
reader2 = fmap (\i -> Right i) reader1
error2 :: ErrorT String (ReaderT Int IO) Int
error2 = ErrorT reader2
But, apparently, since the error1 typechecks just fine, there is some knowledge hidden from me. Can You help uncovering it for me?
The imports needed for running the example code:
import Control.Monad.Error (ErrorT(ErrorT))
import Control.Monad.Reader (ReaderT, asks)
The function asks is exported by two related modules with slightly different types. The version from Control.Monad.Trans.Reader (part of the transformers package), has the type given in the question:
asks :: Monad m => (r -> a) -> ReaderT r m a
However, the version used seems to be the one in the mtl package, from the Control.Monad.Reader module, which has the following, more general, type:
asks :: MonadReader r m => (r -> a) -> m a
So the example definition
error1 :: ErrorT String (ReaderT Int IO) Int
error1 = asks id
means that
MonadReader Int (ErrorT String (ReaderT Int IO))
must hold.
Also defined by mtl are the following instances for MonadReader:
instance Monad m => MonadReader r (ReaderT r m)
instance (Error e, MonadReader r m) => MonadReader r (ErrorT e m)
With these, the constraint above reduces to
(Error String, Monad IO)
which both hold as well.
I think part of your answer is that the monadic functions like asks, put, get, throwError, etc. in the mtl package are written to automatically lift themselves depending on how the monad stack is evaluated.
For example, the following function:
foo = do a <- asks id
if a < 0 then throwError "oops"
else return $ sqrt a
can have both of the types:
ErrorT String (ReaderT Double m) Double
ReaderT (ErrorT String m Double) Double
depending on the order in which runReaderT and runErrorT are run.
The most general type of this function is:
foo :: (MonadError [Char] m, MonadReader b m, Ord b, Floating b) => m b
which shows there is no a priori ordering to the monad layers.
In your example you gave a type signature which says that there is an ErrorT layer in your monad even though you didn't use the throwError function. That's just equivalent to adding the MonadError [Char] m constraint to the type signature.

Resources