
I have some exception types defined ... data POSTOnlyException = POSTOnlyException deriving ( Show, Typeable ) instance Exception POSTOnlyException data BadPathException = BadPathException deriving ( Show, Typeable ) instance Exception BadPathException ... and I want to use Data.Enumerator.catchError ... catchError :: Monad m => Iteratee a m b -> (SomeException -> Iteratee a m b) -> Iteratee a m b ... so I define an error handler ... handleErrors :: SomeException -> Iteratee a m String handleErrors ex = case fromException ex of Just POSTOnlyException -> return "POSTs only!" Just BadPathException -> return "Bad path!" _ -> return "Unknown exception!" ... but of course this doesn't compile, because the types of the LHSs in the case statement are different. I can get around it with some ugliness ... handleErrors :: SomeException -> Iteratee a m String handleErrors ex = case fromException ex of Just POSTOnlyException -> return "POSTs only!" _ -> case fromException ex of Just BadPathException -> return "Bad path!" _ -> return "Unknown exception!" ... but there must be a better way. Enlighten me? Cheers, Mike S Craig

On Tue, Nov 22, 2011 at 4:35 AM, Michael Craig
... but of course this doesn't compile, because the types of the LHSs in the case statement are different. I can get around it with some ugliness ... handleErrors :: SomeException -> Iteratee a m String handleErrors ex = case fromException ex of Just POSTOnlyException -> return "POSTs only!" _ -> case fromException ex of Just BadPathException -> return "Bad path!" _ -> return "Unknown exception!" ... but there must be a better way. Enlighten me?
If you enable the ViewPatterns extension {-# LANGUAGE ViewPatterns #-} then you can write handleErrors as handleErrors :: SomeException -> Iteratee a m String handleErrors (fromException -> Just POSTOnlyException) = return "POSTs only!" handleErrors (fromException -> Just BadPathException) = return "Bad path!" handleErrors _ = return "Unknown exception!" Cheers, -- Felipe.

That works well, but is there an extension free way of doing this cleanly? I tried handleErrors :: (Monad m, Exception e) => Maybe e -> Iteratee a m Response handleErrors (Just POSTOnlyException) = return "POSTs only!" handleErrors (Just BadPathException) = return "Bad path!" handleErrors _ = return "Unknown exception!" app = catchError myApp (handleErrors . fromException) But this won't compile because GHC "Couldn't match type `POSTOnlyException' with `BadPathException'". I think I'm settling towards something like this: data MyAppException = POSTOnlyException | BadPathException deriving ( Show, Typeable ) instance Exception MyAppException handleErrors :: (Monad m) => SomeException -> Iteratee a m Response handleErrors = hErr . fromException where hErr (Just POSTOnlyException) = return "POSTs only!" hErr (Just BadPathException) = return "Bad path!" hErr Nothing = return "Unknown exception!" Mike S Craig On Tue, Nov 22, 2011 at 1:42 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
... but of course this doesn't compile, because the types of the LHSs in
On Tue, Nov 22, 2011 at 4:35 AM, Michael Craig
wrote: the case statement are different. I can get around it with some ugliness ... handleErrors :: SomeException -> Iteratee a m String handleErrors ex = case fromException ex of Just POSTOnlyException -> return "POSTs only!" _ -> case fromException ex of Just BadPathException -> return "Bad path!" _ -> return "Unknown exception!" ... but there must be a better way. Enlighten me?
If you enable the ViewPatterns extension
{-# LANGUAGE ViewPatterns #-}
then you can write handleErrors as
handleErrors :: SomeException -> Iteratee a m String handleErrors (fromException -> Just POSTOnlyException) = return "POSTs only!" handleErrors (fromException -> Just BadPathException) = return "Bad path!" handleErrors _ = return "Unknown exception!"
Cheers,
-- Felipe.
participants (2)
-
Felipe Almeida Lessa
-
Michael Craig