Network.Wai.Middleware.Catch
Description
Exception handling for Wai and Warp.
By default Warp not handles exceptions well. It just log them to
console. This package - an attempt to solve the problem.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Typeable (Typeable)
import Control.Exception (Exception, throw)
import Network.HTTP.Types
import Network.Wai.Handler.Warp (run)
import Data.ByteString.Lazy.Char8 (pack) -- Just for an orphan instance
import Network.Wai
import Network.Wai.Middleware.Catch
data MyException = MyException String deriving (Show, Typeable)
instance Exception MyException
main :: IO ()
main = do
putStrLn $ "http://localhost:8888/"
run 8888 $ (protect handler) $ app
-- ... try 'protect'' and you see what /err/ request will
-- be handled with code 500
app :: Application
app req = case rawPathInfo req of
"/ok" -> return $ responseLBS status200
[("Content-Type", "text/plain")] "OK"
"/err" -> error "Error"
"/exc" -> throw $ MyException "Raised exception"
_ -> return $ responseLBS status200 [("Content-Type", "text/plain")]
"Try any of /ok, /exc, /err"
-- Our handler
handler (e :: MyException) _ = return $
responseLBS status200 [("Content-Type", "text/plain")] (pack $ show e)
The only drawback stems from the basic advantages of Haskell - laziness.
All errors within Wai ResponseBuilder will not be caught. Thus, the
following code will not work:
... return $ responseLBS undefined ...
To ensure catch all errors, you need to consume all data before feeding the builder.
- protect :: Exception e => (e -> Application) -> Middleware
- protect' :: Exception e => (e -> Application) -> Middleware
Documentation
Arguments
| :: Exception e | |
| => (e -> Application) | Handler |
| -> Middleware |
Handles exceptions in responses. If exception isn't handled - it will be
rethrown further. To ensure handle all errors use protect'.
Arguments
| :: Exception e | |
| => (e -> Application) | Handler |
| -> Middleware |