[Haskell-cafe] Portability of MonadError
Peter Robinson
thaldyron at gmail.com
Mon Jan 5 15:48:10 EST 2009
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... :-)
More information about the Haskell-Cafe
mailing list