Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Inserting ErrorT at the base of transformer stack

What is the best way to run a code with type t (ErrorT String IO) a from within a t IO a monad? Consider the code below:

module Sample where

import System.IO
import Control.Monad.Reader
import Control.Monad.Error

type Env = String

inner :: ReaderT Env (ErrorT String IO) ()
inner = do
    s <- ask
    fail s

outer :: ReaderT Env IO ()
outer = do
    env <- ask
    res <- lift $ runErrorT $ runReaderT inner env
    case res of
        Left err -> liftIO $ hPutStrLn stderr err
        Right _ -> return ()
    outer

This works, but I've been looking for a more graceful way of inserting ErrorT at the base of my stack. Especially that I'm using several different monad transformer stacks in my project and writing the above for each of them is quite tedious.

I was looking for something like:

outer :: ReaderT Env IO ()
outer = do
    res <- (hoist runErrorT) inner
    ...

But I cannot use hoist due to type mismatch.


Edit:

I use StateT in some of my stacks and that's the reason for trying to put ErrorT at the base and not on the top.

The outer is supposed to be an infinite loop.

like image 620
Wojciech Baranowski Avatar asked Dec 25 '22 15:12

Wojciech Baranowski


2 Answers

Note that as Edward says, it would generally a lot simpler to put the ErrorT at the top of the stack, not the bottom.

This can change the semantics of the stack, at least for more complicated transformers than ReaderT - e.g. if you have StateT in the stack, then with ErrorT at the bottom changes to the state will be rolled back when there's an error, whereas with ErrorT at the top, changes to the state will be kept when there's an error.

If you do really need it at the bottom, then something like this passes the type checker:

import Control.Monad.Error
import Control.Monad.Morph
import System.IO

toOuter :: MFunctor t => t (ErrorT String IO) a -> t IO a
toOuter = hoist runErrorTWithPrint

runErrorTWithPrint :: ErrorT String IO a -> IO a
runErrorTWithPrint m = do
   res <- runErrorT m
   case res of
       Left err -> do
           hPutStrLn stderr err
           fail err
       Right v -> return v

Note that it calls fail when the inner computation fails, which isn't what your code above does.

The main reason is that to use hoist we need to provide a function of type forall a . ErrorT String IO a -> IO a - i.e. to handle any kind of value, not just (). This is because the depending on the rest of the monad stack might mean that the actual return type when you get to the ErrorT is different to the return type you started with.

In the failure case, we don't have a value of type a so one option is to fail.

In your original code you also loop infinitely in outer, which this doesn't do.

like image 90
GS - Apologise to Monica Avatar answered Jan 14 '23 10:01

GS - Apologise to Monica


The right answer here is "don't do that".

The problem here is you're picking the layering. If you move the Error to the outside it'll behave properly for fail in this situation. In general view the transformer stack as some kind of quantum waveform you shouldn't collapse until the last minute.

inner :: MonadReader Env m => m ()
inner = do
  s <- ask
  fail s

outer :: (MonadReader Env m, MonadIO m) => m ()
outer = do
  res <- runErrorT inner
  case res of
    Left err -> liftIO $ hPutStrLn stderr err
    Right _  -> return ()
  outer

Notice how much simpler everything gets. No hoisting, no explicit lifting, nada. inner is run in a different monad where we've extended our current monad whatever it is, with ErrorT on the outside.

By not picking the stack explicitly you maximize the number of situations in which you can use the code.

If you absolutely have to do it, then follow Ganesh's path, but think hard about whether you actually need to morph in the situation you described!

like image 44
Edward Kmett Avatar answered Jan 14 '23 11:01

Edward Kmett