Search code examples
haskellmonadsmonad-transformerseitherio-monad

Using returned EitherT in haskell program


I'm trying to use the "citation-resolve" package in a Haskell project I'm working on, but I'm having trouble getting my head around using EitherT's in real code. I get that they're monad transformers, and I think I understand what that means, however I can't seem to actually work out how to use them. The toy example that represents what I'm trying to do is as follows:

module Main where
import Text.EditDistance
import Text.CSL.Input.Identifier
import Text.CSL.Reference
import Control.Monad.Trans.Class 
import Control.Monad.Trans.Either 

main = do
    putStrLn "Resolving definition"
    let resRef = runEitherT $ resolveEither "doi:10.1145/2500365.2500595"
    case resRef of 
                Left e -> do 
                    putStrLn ("Got error: "++ e)
                Right ref -> do
                    putStrLn ("Added reference to database: "++ (show ref))

Here, resolveEither has the type:

resolveEither :: (HasDatabase s,
                  Control.Monad.IO.Class.MonadIO m,
                  mtl-2.1.3.1:Control.Monad.State.Class.MonadState s m)
                   => String -> EitherT String m Reference

and runEitherT $ resolveEither "ref" has the type:

runEitherT $ resolveEither "ref"
   :: (HasDatabase s,
       Control.Monad.IO.Class.MonadIO m,
       mtl-2.1.3.1:Control.Monad.State.Class.MonadState s m)
         => m (Either String Reference)

However, this gives the following error:

Main.hs:10:34:
    No instance for (Control.Monad.IO.Class.MonadIO (Either [Char]))
      arising from a use of ‘resolveEither’
    In the first argument of ‘runEitherT’, namely
      ‘(resolveEither "doi:10.1145/2500365.2500595")’
    In the expression:
      runEitherT (resolveEither "doi:10.1145/2500365.2500595")
    In an equation for ‘resRef’:
        resRef = runEitherT (resolveEither "doi:10.1145/2500365.2500595")

Which I have no idea how to resolve, or work around.

Any help would be appreciated, especially pointers to tutorials dealing with monad transformers from a usage perspective, not an implementation one.

Edit:

To reflect the comments on answers by dfeuer and Christian, I still get errors if I change main to the following:

main = do
    putStrLn "Resolving definition"
    resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595")
    case resRef of 
                Left e -> do 
                    putStrLn ("Got error: "++ e)
                Right ref -> do
                    putStrLn ("Added reference to database: "++ (show ref))

The error I get now is:

No instance for (MonadState s0 IO)
  arising from a use of ‘resolveEither’
In the first argument of ‘runEitherT’, namely
  ‘(resolveEither "doi:10.1145/2500365.2500595")’
In a stmt of a 'do' block:
  resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595")
In the expression:
  do { putStrLn "Resolving definition";
       resRef <- runEitherT (resolveEither "doi:10.1145/2500365.2500595");
       case resRef of {
         Left e -> do { ... }
         Right ref -> do { ... } } }

I'm editing my question as well as commenting, as nice code formatting is substantially easier here than in a comment.


Solution

  • You've encountered one of the shortcomings of the mtl class-based approach: intimidating type errors. I think it'll be helpful to imagine what the situation would look like with normal transformers-based monad transformers. I hope this will also help you get your feet with monad transformers in general. (It looks like you already understand most of this, by the way; I'm just spelling it out.)

    Giving the types is a great way to start. Here's what you had:

    resolveEither :: (HasDatabase s,
                      MonadIO m,
                      MonadState s m)
                       => String -> EitherT String m Reference
    

    There's a type hidden in the constraints, s, which came back to bite you a little later. The constraints, roughly speaking, express the following: s has a database (whatever that means in context); the monad or monad stack m has IO at its base, and somewhere in the monad stack m is a StateT s layer. The simplest monad stack m satisfying those properties would be HasDatabase s => StateT s IO. So we could write this:

    resolveEither' :: HasDatabase s
                      => String -> EitherT String (StateT s IO) Reference
    resolveEither' = resolveEither
    

    All we've done is specify the type of m so it's no longer a variable. We don't need to do that as long as we satisfy the class constraints.

    Now it's clearer that there are two layers of monad transformers. Since our main function is in the IO monad, we want to end up with a value of type IO, which we can "run", for instance using <- in do notation. I think of it as "stripping away" layers of the monad transformer, from out to in. (This is what "using" monad transformers boils down to.)

    For EitherT, there's a function runEitherT :: EitherT e m a -> m (Either e a). See how the m moves from "inside" the EitherT to "outside"? For me, that's the critical intuitive observation. Similarly for StateT, there's runStateT :: StateT s m a -> s -> m (a, s).

    (Incidentally, both are defined as record accessors, which is idiomatic but causes them to show up a bit oddly in Haddock and with the "wrong" type signature; it took me a while to learn to look in the "Constructor" section on Haddocks and mentally add the EitherT e m a -> etc. to the front of the signature.)

    So this adds up to a general solution, which you've basically worked out: we need an appropriate value of type s (which I'll call s), then we can use flip runStateT s . runEitherT $ resolveEither "ref" which has type IO ((Either String Reference), s). (Assuming I've kept the types straight in my head, which I probably didn't. I had forgotten flip the first time.) We can then pattern-match or use fst to get to the Either, which seems to be what you really want.

    If you'd like me to explicate the errors GHC was giving you, I'd be glad. Informally, it was saying that you weren't "running" or stripping off all the monad transformers. More precisely, it was observing that IO wasn't something like StateT s IO. By using runStateT and runEitherT, you force or constrain the type such that the class constraints end up satisfied. This is kind of confusing when you get things slightly wrong.

    Oh, regarding an idiomatic way to write the solution: I'm not sure that a separate retEither function would be idiomatic here, because it looks like it's meddling with global state, i.e. opening some sort of database file. It depends what the library's idiom is like.

    Also, by using evalStateT, you're implicitly throwing away the state after evaluation, which may or may not be a bad idea. Does the library expect you to reuse the database connection?

    Finally, you have some extra parentheses and some missing type signatures; hlint will help you with those.