This post will undoubtedly change as I further refine my understanding. This first pass is mainly so that I do not forget what I have learnt so far.
Let’s begin as is customary with a ridiculous example
{-# LANGUAGE OverloadedStrings #-}
import System.Directory
import Control.Monad.Trans.Class
import Control.Monad.Trans.Either
import Control.Monad.IO.Class
file :: FilePath -> IO (Either String String)
file fp = do
    b <- doesFileExist fp
    return $ f b fp
        where
            f :: Bool -> String -> Either String String
            f True fp' = Right $ "Found: " ++ fp'
            f False _ = Left $ "No such file: " ++ fp
cabalFile :: FilePath
cabalFile = "prime.cabal"
licenseFile :: FilePath
licenseFile = "LICENSE"
stackFile :: FilePath
stackFile = "stack.yaml"
fileChecking :: IO ()
fileChecking = do
    f <- file cabalFile
    case f of
      Left err  -> putStrLn err
      Right msg -> do
          putStrLn msg
          f' <- file licenseFile
          case f' of
            Left err'  -> putStrLn err'
            Right msg' -> do
                putStrLn msg'
                f'' <- file stackFile
                case f'' of
                    Left err''  -> putStrLn err''
                    Right msg''  -> do
                        putStrLn msg''
                        putStrLn "fin."
    putStrln "All checks completed."What the above code does is report on the existence (or lack thereof) of each
of the three files in turn (cabalFile, licenseFile, stackFile). As soon
as a file is encountered that no longer exists then no further checks are
performed. Note that the final message is always printed.
The chain of dependent case statements causes the ugly cascading
indentation. Luckily we can remove this with eitherT.
Well, reading from the eitherT
docs
EitherT is a version of ErrorT that does not require a spurious Error instance for the Left case.
ErrorT
is actually on the path to deprecation and
ExceptT
should be preferred but the docs of both indicate that they have the same
basic functionality:
This monad transformer extends a monad with the ability to throw exceptions.
A sequence of actions terminates normally, producing a value, only if none of the actions in the sequence throws an exception. If one throws an exception, the rest of the sequence is skipped and the composite action exits with that exception.
so this allows us to exit from a code block early on the first failure. Our modified version now looks like this:
fileChecking :: IO ()
fileChecking = do
    fileChecks <- runEitherT $ do
        f <- lift $ file cabalFile
        case f of
          Left err  -> left err
          Right msg -> lift (putStrLn msg) >> right msg
        f' <- lift $ file licenseFile
        case f' of
          Left err'  -> left err'
          Right msg' -> lift (putStrLn msg') >> right msg'
        f'' <- lift $ file stackFile
        case f'' of
          Left err''  -> left err''
          Right msg'' -> lift (putStrLn msg'') >> right msg''
        right "fin."
    either putStrLn putStrLn fileChecks
    putStrLn "All checks completed."The first time we encounter a Left we return left err and that terminates
the processing of the entire do block. If no Lefts are encountered we get
to the end of this do block and simply return right "fin.".
Note that we don’t explicitly create an instance of EitherT ourselves and
instead make use of runEitherT.
A little bit about (my understanding of) what is going on with the
runExceptT function.
The first thing that our original fileChecking function does is call file cabalFile to determine if that file exists. In ghci we can see the type of
this action
λ> :t file cabalFile
file cabalFile :: IO (Either String String)This makes sense, the interesting part for us is the Either that wraps up
the failure/success paths but since checking the file exists is an IO action
we get our result wrapped in the IO type. So far so good.
Now if we look at the type of lift (imported from
Control.Monad.Trans.Class) we see
λ> :t lift
lift :: (Monad m, MonadTrans t) => m a -> t m ait takes a monad m a and “transforms” it by augmenting it with the
transformer monad t. In our case we can see the outcome of lifting our
call to file cabalFile
λ> :t lift $ file cabalFile
lift $ file cabalFile
  :: MonadTrans t => t IO (Either String String)Looking at this types shows that we’re now just missing the transforming
monad so lets now look at the type of EitherT
λ> :t EitherT
EitherT :: m (Either e a) -> EitherT e m aEitherT creates a transformed Either with e (the failure case) on the
left as expected and m a on the right. Remember that a is the success case
and m is the monad that we’re augmenting (which in this case is IO). The
effect of this is that our original action
IO (Either String String)now becomes
EitherT String IO Stringnotice that we didn’t explicitly create EitherT ourselves though; lets look
at the type of runEitherT to see what it does.
λ> :t runEitherT
runEither :: EitherT e m a -> m (Either e a)so runEitherT is the reverse of EitherT and reverts an EitherT to its
original type which means that action we get back is the IO (Either String String) we started with except now we’ve performed all of our error checking.