[Haskell-cafe] IO (Either a Error) question

Ryan Ingram ryani.spam at gmail.com
Wed May 5 17:54:27 EDT 2010


ErrorT is just a newtype wrapper, changing the order/application of
the type variables.

newtype ErrorT e m a = ErrorT (m (Either e a))
runErrorT (ErrorT action) = action

This gives the bijection:

ErrorT :: m (Either e a) -> ErrorT e m a
runErrorT :: ErrorT e m a -> m (Either e a)

We can now redefine >>= for this new type to handle plumbing the error:

instance (Error e, Monad m) => Monad (ErrorT e m) where
    return a = ErrorT (return (Right a))
    m >>= f = ErrorT $ do
        ea <- runErrorT m
        case ea of
            Left e -> return (Left e)
            Right a -> runErrorT (f a)
    fail s = ErrorT (return $ Left $ strMsg s)

On Sun, May 2, 2010 at 1:50 AM, Eugene Dzhurinsky <bofh at redwerk.com> wrote:
>> > :t ErrorT
>> ErrorT :: m (Either e a) -> ErrorT e m a
>
> At this point I am lost. I'm not sure that I do understand this type
> transformation correctly. So we have some sort of monadic type m, error type e
> and resut of type a. If m = IO, e - Error, a - String, than
>
> ErrorT :: IO (Either Error String) -> ErrorT Error IO String

Yep.

> I can think that can be written as
>
> ErrorT :: IO (Either Error String) -> ErrorT Error (IO String)
>
> Am I correct?

Nope.

At the type level:

ErrorT :: * -> (* -> *) -> * -> *
That is, the to make the ErrorT concrete (kind *), you need
   a concrete type (e :: *)
   a type that takes a parameter (m :: * -> *)
   and finally, a parameter (a :: *)

(IO String) :: *
whereas
IO :: * -> *
String :: *

The reason for this is because ErrorT is inserting "Either" in the proper place:
   ErrorT :: m (Either e a) -> ErrorT e m a

There's no way for ErrorT to do anything at the type level with (IO
String).  (Although if you go into crazy type system extensions, you
could use GADTs to make a type that worked like that.  Probably not
useful, though!)

Now we have (ErrorT e m) :: * -> *
which means it is eligible to be an instance of Monad, Functor, etc.

>> So, if you can make your Error type an instance of this class, you can do this:
>> runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)
>
> Sorry, I don't understand how does it work. Can you please explain the type
> transformations involved here?

Sorry, I typoed a bit here.
runCalc p = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)

Lets just do some inference:

func1 :: Int -> IO (Either Error String)
p :: Int
func1 p :: IO (Either Error String)
ErrorT (func1 p) :: ErrorT Error IO String

func2 :: String -> IO (Either Error [String])
(ErrorT . func2) :: String -> ErrorT Error IO String

(>>=) :: forall m a b. Monad m => m a -> (a -> m b) -> m b
IO is an instance of Monad
If you make Error into an instance of Control.Monad.Error.Error
then (ErrorT Error IO) is an instance of Monad

So one instance of the type of (>>=):
(>>=) :: ErrorT Error IO String -> (String -> ErrorT Error IO
[String]) -> ErrorT Error IO [String]
(func1 p >>= ErrorT . func2) :: ErrorT Error IO [String]

runErrorT (func1 p >>= ErrorT . func2) :: IO (Either Error [String])

And finally:
runCalc :: Int -> IO (Either Error [String])

  -- ryan


More information about the Haskell-Cafe mailing list