Accessing Reader input (environment) in monad stack

I will try to give the most simplified conceptual example of my problem. Hope there is nothing reprehensible in this. I think in this form the question will be more general and useful.

I encountered a problem and solved it. But the method I used looks a little terrible. I want some guidance on how to achieve the effect I’ve described, but in the right way.

Simplified example

Perhaps it is called differently, because… my nested Reader strictly speaking is not a transformer, but consider the following monad stack:

type MyStack a = MaybeT (Reader String) a
-- ~ String -> Maybe a
-- This is correct order, right? `Reader` is the base monad.

and the value:

produce :: MyStack Int
produce = MaybeT $ Reader $ \n -> Just (read n)

I’m trying to access an input value of Reader inside a function like this

compute :: MyStack Int
compute = do
  let pack      =    MaybeT . Reader
      unpack    = runReader . runMaybeT
      modify fn = \inp -> (,) inp <$> fn inp -- ~ `Just (inp, read inp)`
  (inp, out) <-  pack . modify . unpack $ produce
  -- computatons involving `inp` and `out`

I guess this is the wrong approach, but nothing else comes to mind.
Сould anyone point me to how this should be done correctly, please?


Sorry if there are typos or misleadings in some places. I tried to simplify the example as much as possible and may have made mistakes. It is also very likely that I understand something completely wrong and describe nonsense. You can point this out to me and I will try to correct or supplement the question.

Please do not judge harshly. I’m far from a professional and not trying to seem like one.


P.S. You may notice that it looks like I’m trying to temporarily turn Reader into State. You can also advise me to use it this way:

type MyStack a = MaybeT (State String) a
produce :: MyStack Int
produce = MaybeT $ State \s -> (Just (read s), s)
compute :: MyStack Int
compute = do
  res <- produce
  stt <- get
  -- computatons involving `inp` and `stt`

But I can’t change the stack definition in my situation. This is the limitation given in this question.

My feedback would be that you could be using more of the library functions that mtl gives you. Monad transformer stacks are best accessed using the class members in the Control.Monad.*.Class modules; this saves you from having to duplicate a lot of the plumbing yourself.

For example, your produce function can be simply

produce :: MyStack Int
produce = asks read

with asks imported from Control.Monad.Reader.Class (or Control.Monad.Reader, which re-exports it).

Similarly, unless I’m misunderstanding compute, can it be just this?

compute :: MyStack Int
compute = do
  inp <- ask
  out <- produce
  -- use `inp` and `out`

That should work with your existing stack type; I don’t really understand your postscript about changing Reader to State.

(Note that there is also an ask function exported from Control.Monad.Trans.Reader, but it doesn’t have the same type and won’t be as useful when Reader is not the top of your stack. You could still use it with lift if you wanted to, but the other ask is more convenient.)

3 Likes

This is exactly what I need. You know, I already looked at the pages you linked to, but I didn’t delve enough into the description of ask and asks. Thanks for pointing them out.

You can take the subscript to indicate that I wanted an analogue of get from Control.Monad.State but for Reader, and I didn’t find it.

In any case, your answer is comprehensive and helped me a lot. I’m ashamed of my carelessness. Thanks!

2 Likes

You can also derive this interface when you decide to make your stack its own type: asks read :: MyStack Int will still work if you derive MonadReader String.

{-# language DerivingVia #-}

newtype MyStack a = MyStack { runMyStack :: String -> Maybe a }
  deriving
    ( Functor, Applicative, Alternative
    , Monad, MonadPlus, MonadZip, MonadFail, MonadFix
    , MonadReader String )
  via MaybeT (Reader String)

Tangentially related to your question, I have also been working on a PR that adds the ability to derive the class Monad* through types that have the capability by wrapping them with the Lifting* type.