Haskell, parameters of ask - haskell

Could you help what parameter is getting by ask ?
We often can see ask >>= f
It means that ask >>= f = (\k -> f (ask k) k)
So ask must be able to get k, function from enviroment.
However, in docs it is written: ask :: m r.
Where am I wrong ?

It's the Reader monad. Ultimately the best answer is just to study its implementation, which in it simplest version (no monad transformers, no classes) can be defined like this:
newtype Reader r a = Reader { runReader :: r -> a }
This is a newtype declaration, so Reader r a is just a "relabeling" (so to speak) of the function type r -> a. ask is defined like this:
ask :: Reader r r
ask = Reader (\r -> r)
Which means that ask is a relabeled identity function—the function that just returns its own argument. We can see this if we use the runReader operation to feed values to it :
ghci> runReader ask 5
5
ghci> runReader ask "Hello world!"
"Hello world!"
That doesn't look very useful, but the magic comes from the fact that Reader has instances for Functor, Applicative and Monad:
instance Functor (Reader r) where
fmap f (Reader g) =
-- A `Reader` that applies `f` to the original `Reader`'s results
Reader (\r -> f (g r))
instance Applicative (Reader r) where
pure a =
-- A `Reader` that ignores its `r` argument and just produces
-- a fixed value.
Reader (\_ -> a)
Reader ff <*> Reader fa =
-- A `Reader` that "combines" two `Reader`s by feeding the same
-- `r` value to both, and then combining their results
Reader (\r -> ff r (fa r))
instance Monad (Reader r) where
return = pure
Reader fa >>= k =
-- A `Reader` that feeds the same `r` both to the original one
-- and to the one computed by the `k` function
Reader (\r -> k (fa r) r)
If you study these, you'll notice that what Reader is about is delaying the point of the program where you apply the wrapper r -> a function to an r. Normally, if you have a function of type r -> a and you want to get a value of type a, you have to feed the function an argument of type r. The Reader class instances allow you instead to supply functions that will be used to operate on the a ahead of time, and then supply the r in the end.
The ReaderT type and the MonadReader class (which has the ask :: MonadReader r m => m r method) are just more advanced versions of this.

A value of type m a where m is a Monad, can be thought of as a "monadic action". So ask doesn't take any parameters, it's just a value that you can bind (>>=) to extract some value from a Reader monad.
Look at the definition of ask for ReaderT in Control.Monad.Trans.Reader:
-- | Fetch the value of the environment.
ask :: (Monad m) => ReaderT r m r
ask = ReaderT return
ReaderT is just a data constructor that contains a value of type r -> m a, so ReaderT return is a value of type ReaderT r m r that contains a function, return (of the monad m).
In other words, ask here is a "monadic action" that extracts the value of stored inside the Reader.
ask >>= f
Which is
(ReaderT return) >>= f
Using definition of >>= for Reader, we get:
ReaderT $ \ r -> do
a <- runReaderT (ReaderT return) r
runReaderT (f a) r
Which reduces to
ReaderT $ \ r -> do
a <- return r
runReaderT (f a) r
Or
ReaderT $ \r -> runReaderT (f r) r
So, it passes the stored value along to decide the next action and also passes the value so the next actions can read it as it was before.
(If this wasn't clear, look for a Reader tutorial maybe)

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.

Lifting a complete monadic action to a transformer (>>= but for Monad Transformers)

I looked hard to see if this may be a duplicate question but couldn't find anything that addressed specifically this. My apologies if there actually is something.
So, I get how lift works, it lifts a monadic action (fully defined) from the outer-most transformer into the transformed monad. Cool.
But what if I want to apply a (>>=) from one level under the transformer into the transformer? I'll explain with an example.
Say MyTrans is a MonadTrans, and there is also an instance Monad m => Monad (MyTrans m). Now, the (>>=) from this instance will have this signature:
instance Monad m => Monad (MyTrans m) where
(>>=) :: MyTrans m a -> (a -> MyTrans m b) -> MyTrans m b
but what I need is something like this:
(>>=!) :: Monad m => MyTrans m a -> (m a -> MyTrans m b) -> MyTrans m b
In general:
(>>=!) :: (MonadTrans t, Monad m) => t m a -> (m a -> t m b) -> t m b
It looks like a combination of the original (>>=) and lift, except it really isn't. lift can only be used on covariant arguments of type m a to transform them into a t m a, not the other way around. In other words, the following has the wrong type:
(>>=!?) :: Monad m => MyTrans m a -> (a -> m b) -> MyTrans m b
x >>=!? f = x >>= (lift . f)
Of course a general colift :: (MonadTrans t, Monad m) => t m a -> m a makes absolutely zero sense, because surely the transformer is doing something that we cannot just throw away like that in all cases.
But just like (>>=) introduces contravariant arguments into the monad by ensuring that they will always "come back", I thought something along the lines of the (>>=!) function would make sense: Yes, it in some way makes an m a from a t m a, but only because it does all of this within t, just like (>>=) makes an a from an m a in some way.
I've thought about it and I don't think (>>=!) can be in general defined from the available tools. In some sense it is more than what MonadTrans gives. I haven't found any related type classes that offer this either. MFunctor is related but it is a different thing, for changing the inner monad, but not for chaining exclusively transformer-related actions.
By the way, here is an example of why you would want to do this:
EDIT: I tried to present a simple example but I realized that that one could be solved with the regular (>>=) from the transformer. My real example (I think) cannot be solved with this. If you think every case can be solved with the usual (>>=), please do explain how.
Should I just define my own type class for this and give some basic implementations? (I'm interested in StateT, and I'm almost certain it can be implemented for it) Am I doing something in a twisted way? Is there something I overlooked?
Thanks.
EDIT: The answer provided by Fyodor matches the types, but does not do what I want, since by using pure, it is ignoring the monadic effects of the m monad. Here is an example of it giving the wrong answer:
Take t = StateT Int and m = [].
x1 :: StateT Int [] Int
x1 = StateT (\s -> [(1,s),(2,s),(3,s)])
x2 :: StateT Int [] Int
x2 = StateT (\s -> [(1,s),(2,s),(3,s),(4,s))])
f :: [Int] -> StateT Int [] Int
f l = StateT (\s -> if (even s) then [] else (if (even (length l)) then (fmap (\z -> (z,z+s)) l) else [(123,123)]))
runStateT (x1 >>= (\a -> f (pure a))) 1 returns [(123,123),(123,123),(123,123)] as expected, since both 1 is odd and the list in x1 has odd length.
But runStateT (x2 >>= (\a -> f (pure a))) 1 returns [(123,123),(123,123),(123,123),(123,123)], whereas I would have expected it to return [(1,2),(2,3),(3,4),(4,5)], since the 1 is odd and the length of the list is even. Instead, the evaluation of f is happening on the lists [(1,1)], [(2,1)], [(3,1)] and [(4,1)] independently, due to the pure call.
This can be very trivially implemented via bind + pure. Consider the signature:
(>>=!) :: (Monad m, MonadTrans t) => t m a -> (m a -> t m a) -> t m a
If you use bind on the first argument, you get yourself a naked a, and since m is a Monad, you can trivially turn that naked a into an m a via pure. Therefore, the straightforward implementation would be:
(>>=!) x f = x >>= \a -> f (pure a)
And because of this, bind is always strictly more powerful than your proposed new operation (>>=!), which is probably the reason it doesn't exist in the standard libraries.
I think it may be possible to propose more clever interpretations of (>>=!) for some specific transformers or specific underlying monads. For example, if m ~ [], one might imagine passing the whole list as m a instead of its elements one by one, as my generic implementation above would do. But this sort of thing seems too specific to be implemented in general.
If you have a very specific example of what you're after, and you can show that my above general implementation doesn't work, then perhaps I can provide a better answer.
Ok, to address your actual problem from the comments:
I have a function f :: m a -> m b -> m c that I want to transform into a function ff :: StateT s m a -> StateT s m b -> StateT s m c
I think looking at this example may illustrate the difficulty better. Consider the required signature:
liftish :: Monad m => (m a -> m b -> m c) -> StateT m a -> StateT m b -> StateT m c
Presumably, you'd want to keep the effects of m that are already "imprinted" within the StateT m a and StateT m b parameters (because if you don't - my simple solution above will work). To do this, you can "unwrap" the StateT via runStateT, which will get you m a and m b respectively, which you can then use to obtain m c:
liftish f sa sb = do
s <- get
let ma = fst <$> runStateT sa s
mb = fst <$> runStateT sb s
lift $ f ma mb
But here's the trouble: see those fst <$> in there? They are throwing away the resulting state. The call to runStateT sa s results not only in the m a value, but also in the new, modified state. And same goes for runStateT sb s. And presumably you'd want to get the state that resulted from runStateT sa and pass it to runStateT sb, right? Otherwise you're effectively dropping some state mutations.
But you can't get to the resulting state of runStateT sa, because it's "wrapped" inside m. Because runStateT returns m (a, s) instead of (m a, s). If you knew how to "unwrap" m, you'd be fine, but you don't. So the only way to get that intermediate state is to run the effects of m:
liftish f sa sb = do
s <- get
(c, s'') <- lift $ do
let ma = runStateT sa s
(_, s') <- ma
let mb = runStateT sb s'
(_, s'') <- mb
c <- f (fst <$> ma) (fst <$> mb)
pure (c, s'')
put s''
pure c
But now see what happens: I'm using ma and mb twice: once to get the new states out of them, and second time by passing them to f. This may lead to double-running effects or worse.
This problem of "double execution" will, I think, show up for any monad transformer, simply because the transformer's effects are always wrapped inside the underlying monad, so you have a choice: either drop the transformer's effects or execute the underlying monad's effects twice.
I think what you "really want" is
(>>>==) :: MyTrans m a -> (forall b. m b -> MyTrans n b) -> MyTrans n a
-- (=<<) = flip (>>=) is nicer to think about, because it shows that it's a form of function application
-- so let's think about
(==<<<) :: (forall a. m b -> MyTrans n b) -> (forall a. MyTrans m a -> MyTrans n a)
-- hmm...
type (~>) a b = forall x. a x -> b x
(==<<<) :: (m ~> MyTrans n) -> MyTrans m ~> MyTrans n
-- look familiar?
That is, you are describing monads on the category of monads.
class MonadTrans t => MonadMonad t where
-- returnM :: m ~> t m
-- but that's just lift, therefore the MonadTrans t superclass
-- note: input must be a monad homomorphism or else all bets are off
-- output is also a monad homomorphism
(==<<<) :: (Monad m, Monad n) => (m ~> t n) -> t m ~> t n
instance MonadMonad (StateT s) where
-- fairly sure this is lawful
-- EDIT: probably not
f ==<<< StateT x = do
(x, s) <- f <$> x <$> get
x <$ put s
However, making your example work is just not going to happen. It is too unnatural. StateT Int [] is the monad for programs that nondeterministically evolve the state. It is an important property of that monad that each "parallel universe" receives no communication from the others. The specific operation you are performing will probably not be provided by any useful typeclass. You can only do part of it:
f :: [] ~> StateT Int []
f l = StateT \s -> if odd s && even (length l) then fmap (\x -> (x, s)) l else []
f ==<<< x1 = []
f ==<<< x2 = [(1,1),(2,1),(3,1),(4,1)]

How does the Reader monad's "ask" function work?

data T b = E | N b (T b) (T b)
f :: T b -> Reader Int (T Int)
f (N i l r) = ask >>= \x -> local ((-)4) (f l) >>= \l' -> local ((-)1) (f r) >>= \r' -> return (N x l' r')
f E = return E
I have a problem with understanding how this code works. Especially, how does ask know where the environment is (in our case just Int)?
To be more precise: I am an imperative programmer and in such languages it is easy. Methods can be called on any object like: obj.f(), or we have to pass data by argument when we want function use external data.
That's kind of what the Reader monad does; it gives you an ask function, which "magically" pops up a value out of thin air. To actually use this, you need to call runReader, and give it the Int environment. The Reader type then automatically propagates that from the runReader call to each of the ask calls.
Short, hand-wavy answer. The Reader Int (T Int) value is essentially just a wrapped-up function of type Int -> (T Int). In order to run that function, we first need to extract it. We do that with runReader.
data T b = ... deriving (Show)
main = let tree = (N 10 (N 8 E E) E)
g = f tree
h = runReader g
in print $ h 20
(Typically, you would simply write print $ runReader (f tree) 20; I split it up to correspond to the sketchy analogy below.)
ask (defined by the MonadReader typeclass and as implemented by the ReaderT monad transformer used to define the Reader type) essentially retrieves the value of the argument passed to h.
In some sense, the Reader Int (T Int) is an object that contains a function g that calls a function ask. runReader g creates a new function which, when called, defines a function ask that simply returns its argument, then calls g. Now when g calls ask, it gets back the argument originally passed to h.
I recomend reading this first. Ask is defined:
ask :: (Monad m) => ReaderT r m r
ask = ReaderT return
and reader:
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
type Reader r = ReaderT r Identity
so
do
r <- ask
...
is equivalent to
do
r <- ReaderT return
...
So essentially <- just reaches into the identity monad, and grabs what ever value that will eventually be lifted by runReader R = return.
This enables global variables in haskell.

Adding state to an Either

I have a function which is something like myFunction below:
data MyError = E1 | E2
f s = if s == "" then Left E1 else Right $ reverse s
g = (fmap reverse) . f
myFunction :: String -> Either MyError (String, String)
myFunction s = do
s1 <- f s
s2 <- g s1
return (s2, s2)
So it calls various other functions which are also in the Either monad, so everything is OK.
Now I have a situation where the type of one of the functions, say g, changes to
g :: CPRG r => r -> String -> (Either MyError String, r)
For reference, the "real-world" code is the decode function here and the function that changes is Jwe.rsaDecode (I'm adding RSA blinding to the decryption function).
As a result, myFunction needs to have the same type, so that I can pass in the CPRG and return it. I'm having trouble seeing how I can carry on using something like the Either monad in combination with passing the RNG, and still be able to extract the final state of the RNG in both the failure and success cases, so that it can be returned.
The type
r -> (Either e a, r)
is a monad transformer. In particular, it's the ExceptT transformer
newtype ExceptT e m a = ExceptT (m (Either e a))
We'll specialize it for State such that
r -> (Either e a, r)
~
ExceptT e (State r) a
So what is a monad transformer? Well, it turns out that often when you take two monads together and stack them you end up with yet another monad. It is not always the case and is a bit tricky to do in general (unlike Applicative where stacks of Applicative functors are always yet again Applicative functors).
That said, the library linked above, mtl, demonstrates a list of common "transformers" which encode common ways of stacking monads. Thus, ExceptT is one of these "recipes" and it is designed such that ExceptT e m a is a monad so long as m is also a Monad.
So now we can create a new type alias
type M r a = ExceptT MyError (State r) a
and write g as a function like
g' :: CPRG r => String -> M r String
g' s = do
r <- lift get -- lift "lifts" State monad computations up
let (e, r') = g r s
lift $ put r'
either throwError return e -- here we generalize an Either
-- into the M monad.

Type error while trying to implement the (>>=) function in order to create a custom monad transformer

I'm trying to create a monad transformer for a future project, but unfortunately, my implementation of the Monad typeclasse's (>>=) function doesn't work.
First of all, here is the underlying monad's implementation :
newtype Runtime a = R {
unR :: State EInfo a
} deriving (Monad)
Here, the implementation of the Monad typeclasse is done automatically by GHC (using the GeneralizedNewtypeDeriving language pragma).
The monad transformer is defined as so :
newtype RuntimeT m a = RuntimeT {
runRuntimeT :: m (Runtime a)
}
The problem comes from the way I instanciate the (>>=) function of the Monad typeclasse :
instance (Monad m) => Monad (RuntimeT m) where
return a = RuntimeT $ (return . return) a
x >>= f = runRuntimeT x >>= id >>= f
The way I see it, the first >>= runs in the underlying m monad. Thus, runRuntimeT x >>= returns a value of type Runtime a (right ?). Then, the following code, id >>=, should return a value of type a. This value is the passed on to the function f of type f :: (Monad m) => a -> RuntimeT m b.
And here comes the type problem : the f function's type doesn't match the type required by the (>>=) function. Jow can I make this coherent ? I can see why this doesn't work, but I can't manage to turn it into something functionnal.
Edit : The error message :
Core.hs:34:4:
Occurs check: cannot construct the infinite type: m = RuntimeT m
When generalising the type(s) for `>>='
In the instance declaration for `Monad (RuntimeT m)'
Failed, modules loaded: none.
Thank you for you help, and do not hesitate to correct any flaws in my message,
Charlie P.
The usual StateT s m monad sends a to s -> m (a, s) but you are working with m (s -> (a, s)) instead. I don't think the latter forms a monad for general s. Are you sure you don't just want to use StateT?
Here's why I don't think a → m (s -> (a, s)) is a monad: To write >>= I need a function that takes arguments of types
m (s -> (a, s))
a -> m (s -> (b, s))
and returns a value of type
m (s -> (b, s))
The "effects" (i.e. fmap (const ())) of the result must be those of the first argument, since we have no way to get an a to pass to the second argument. Since m appears only on the outside of the result type, we then cannot use the second argument for anything at all—there will be no way to get rid of the m it introduces.
To follow on from what Reid Barton said about StateT - here's how you would define RuntimeT using StateT. The Runtime monad can then be trivially defined using the identity monad.
newtype RuntimeT m a = R {
unR :: StateT EInfo m a
}
type Runtime = RuntimeT Identity
instance Monad m => Monad (RuntimeT m) where
return = R . return
(R m) >>= f = R (m >>= unR . f)

Resources