
Hello, One thing that's been bothering me about MonadError monads is the non-portability of code that uses a custom Error type. Meaning, if I have libraries A and B that use different error types, I won't be able to write a function func: func = (funcA >> funcB) `catchError` (\e -> ...) funcA :: ErrorT MyErrorA m () funcB :: ErrorT MyErrorB m () So I'm wondering whether there's a reason not to introduce a type class hierarchy instead of custom error types to make the code more portable. Something like this: -------------------- import Control.Exception(IOException) import Control.Monad.Error class (Eq e,Show e,Error e) => MyExc e where myExc1 :: e myExc1 = strMsg "myExc1" -- Now we can simply extend MyExc and catch all errors defined in MyExc and -- MyExc2 in the same error-handler (see handler2 below): class MyExc e => MyExc2 e where myExc2 :: e myExc2 = strMsg "myExc2" -- Uses the error class MyExc test1:: (MonadError e m, Monad m, MonadIO m, MyExc e) => m () test1 = do liftIO $ putStrLn "############ Throwing myExc1: " throwError myExc1 `catchError` handler1 -- Uses the error class MyExc2 that extends MyExc test2 :: (MonadError e m,MonadIO m, MyExc2 e) => m () test2 = do liftIO $ putStrLn "\n############ Throwing myExc2: " throwError myExc2 `catchError` handler2 -- Uses the error type class MyExc2 but throws an error -- already defined in MyExc test3 :: (MonadError e m,MonadIO m,MyExc2 e) => m () test3 = do liftIO $ putStrLn "\n############ Throwing myExc1 within context MyExc2: " throwError myExc1 `catchError` handler2 -- Error handler for class MyExc handler1 :: (MonadError e m, MonadIO m,Monad m,MyExc e) => e -> m () handler1 e = do when (e == myExc1) $ liftIO $ putStrLn $ "Caught a MyExc1 " ++ show e -- Error handler for class MyExc2 (catches errors in MyExc1) handler2 :: (MonadError e m, MonadIO m,Monad m,MyExc2 e) => e -> m () handler2 e = do when (e == myExc1) $ do liftIO $ putStrLn $ "Caught a MyExc1 " ++ show e throwError e when (e == myExc2) $ liftIO $ putStrLn $ "Caught a MyExc2 " ++ show e -- To run the code in the IO monad we need: instance MyExc IOException where myExc1 = userError "myExc1 has occurred" instance MyExc2 IOException where myExc2 = userError "myExc2 has occurred" -- Run test1 and test2 in the IO monad mymain :: IO () mymain = (test1 >> test2 >> test3) `catchError` (\e -> putStrLn $ "Something went wrong...\n" ++ show e) -- Now let's try a custom monad: newtype MyMonad e a = MyMonad { runMM :: ErrorT e IO a } deriving(Monad,MonadError e,MonadIO) runMyMonad :: Error e => MyMonad e a -> IO (Either e a) runMyMonad = runErrorT . runMM mymainT :: IO () mymainT = do res <- runMyMonad (test1 >> test2 >> test3 :: MyMonad IOException ()) case res of Left e -> putStrLn $ "Something went wrong...\n" ++ show e _ -> return () ---------------------- Maybe I'm missing something but is there any advantage of using custom data types rather than the typeclass approach? Cheers, Peter PS: Please be frank if I'm reinventing the wheel here... :-)

On Mon, Jan 5, 2009 at 1:48 PM, Peter Robinson
Hello,
One thing that's been bothering me about MonadError monads is the non-portability of code that uses a custom Error type. Meaning, if I have libraries A and B that use different error types, I won't be able to write a function func:
func = (funcA >> funcB) `catchError` (\e -> ...)
funcA :: ErrorT MyErrorA m ()
funcB :: ErrorT MyErrorB m ()
So I'm wondering whether there's a reason not to introduce a type class hierarchy instead of custom error types to make the code more portable.
I think this worry is related to a world view of "large monads", which also proliferates claims like "monads are not appropriate for large programs", and is related to fat interfaces in OOP. I claim that, like objects, monads are appropriate for little pieces of computations, and monadic computations in different monads deserve to be composed just as much so as those in the same monad. The complex type-directed approach gives the feel of exceptions from mainstream languages, but will run into problems when eg. two computations both use ErrorT String, but you want to differentiate the errors. All that is necessary is a simple function: mapError :: (e -> e') -> ErrorT e a -> ErrorT e' a mapError f = ErrorT . liftM (left f) . runErrorT (Where "left" is from Control.Arrow, and is a "semantic editor") Then your example can become:: func = (mapError Left funcA >> mapError Right funcB) `catchError` (\e -> ...) Luke

On Mon, Jan 5, 2009 at 2:13 PM, Luke Palmer
On Mon, Jan 5, 2009 at 1:48 PM, Peter Robinson
wrote: Hello,
One thing that's been bothering me about MonadError monads is the non-portability of code that uses a custom Error type. Meaning, if I have libraries A and B that use different error types, I won't be able to write a function func:
func = (funcA >> funcB) `catchError` (\e -> ...)
funcA :: ErrorT MyErrorA m ()
funcB :: ErrorT MyErrorB m ()
So I'm wondering whether there's a reason not to introduce a type class hierarchy instead of custom error types to make the code more portable.
I think this worry is related to a world view of "large monads", which also proliferates claims like "monads are not appropriate for large programs", and is related to fat interfaces in OOP. I claim that, like objects, monads are appropriate for little pieces of computations, and monadic computations in different monads deserve to be composed just as much so as those in the same monad.
The complex type-directed approach gives the feel of exceptions from mainstream languages, but will run into problems when eg. two computations both use ErrorT String, but you want to differentiate the errors. All that is necessary is a simple function:
mapError :: (e -> e') -> ErrorT e a -> ErrorT e' a mapError f = ErrorT . liftM (left f) . runErrorT
Modulo obvious errors, as usual. Haskell type inference knows better than I do: mapError :: Monad m => (e -> e') -> ErrorT e m a -> ErrorT e' m a Luke
(Where "left" is from Control.Arrow, and is a "semantic editor")
Then your example can become::
func = (mapError Left funcA >> mapError Right funcB) `catchError` (\e -> ...)
Luke

On Mon, Jan 5, 2009 at 2:13 PM, Luke Palmer
wrote: On Mon, Jan 5, 2009 at 1:48 PM, Peter Robinson
wrote: Hello,
One thing that's been bothering me about MonadError monads is the non-portability of code that uses a custom Error type. Meaning, if I have libraries A and B that use different error types, I won't be able to write a function func:
func = (funcA >> funcB) `catchError` (\e -> ...)
funcA :: ErrorT MyErrorA m ()
funcB :: ErrorT MyErrorB m ()
So I'm wondering whether there's a reason not to introduce a type class hierarchy instead of custom error types to make the code more portable.
I think this worry is related to a world view of "large monads", which also proliferates claims like "monads are not appropriate for large programs", and is related to fat interfaces in OOP. I claim that, like objects, monads are appropriate for little pieces of computations, and monadic computations in different monads deserve to be composed just as much so as those in the same monad.
Well my main concern was that composability issue of "similar" (modulo error type) monads.
The complex type-directed approach gives the feel of exceptions from mainstream languages, but will run into problems when eg. two computations both use ErrorT String, but you want to differentiate the errors.
Not sure I got this: When using the type class approach you would not use an instantiation like ErrorT String in code intended to be portable, but rather something like "ErrorT MyClass". Either two computations have the same error type class or they don't, so there shouldn't be any problem differentiating errors, right?
All that is necessary is a simple function: mapError :: (e -> e') -> ErrorT e a -> ErrorT e' a mapError f = ErrorT . liftM (left f) . runErrorT
Modulo obvious errors, as usual. Haskell type inference knows better than I do: mapError :: Monad m => (e -> e') -> ErrorT e m a -> ErrorT e' m a Luke
(Where "left" is from Control.Arrow, and is a "semantic editor") Then your example can become:: func = (mapError Left funcA >> mapError Right funcB) `catchError` (\e -> ...)
Yes that does look interesting. Thanks for the hint! Peter

On Mon, Jan 5, 2009 at 2:13 PM, Luke Palmer
Then your example can become::
func = (mapError Left funcA >> mapError Right funcB) `catchError` (\e -> ...)
Luke
Oh bother! My new year's resolution: think before I speak. While I do think this is the right answer, it is not the right answer in the status quo. This is because ErrorT e m is only a monad when e is an Error, which Either (and most types) are not. It will be the right answer when fail is factored out of Monad into MonadFail (which will happen someday hopefully), because then the typechecker will verify that the above composition cannot fail. But now I can't think of a good answer. Darn. Luke

On Mon, 5 Jan 2009, Luke Palmer wrote:
Oh bother! My new year's resolution: think before I speak.
While I do think this is the right answer, it is not the right answer in the status quo. This is because ErrorT e m is only a monad when e is an Error, which Either (and most types) are not. It will be the right answer when fail is factored out of Monad into MonadFail (which will happen someday hopefully), because then the typechecker will verify that the above composition cannot fail.
But now I can't think of a good answer. Darn.
In the explicit-exception package I omit 'fail' and allow an exception type without constraints.
participants (3)
-
Henning Thielemann
-
Luke Palmer
-
Peter Robinson