[Haskell-cafe] FastCGI error handling
Victor Nazarov
asviraspossible at gmail.com
Mon Aug 3 08:32:07 EDT 2009
I've been trying to write some simple web application in haskell using
FastCGI, HDBC and HStringTemplate. I've got stuck with the following
problem.
HDBC throws some exceptions and I wanted them to be caught and logged.
The code was:
-- Main.hs
module Main (main) where
...
import Control.Concurrent
import Network.FastCGI
driver :: CGI CGIResult
driver = ...
main :: IO ()
main = runFastCGIConcurrent' forkIO 10 (handleErrors test)
But all I've got on the page and in the log is "SomeException" string.
I've tried the workaround:
-- Main.hs
module Main (main) where
import Network.FastCGI
import Control.Exception
import System.IO
driver :: CGI CGIResult
driver = ...
...
main :: IO ()
main = runFastCGI driver `catch` \ex -> hPutStr stderr $ show
(ex::SomeException)
And this worked fine. I've got a detaied SqlException string in the log file.
So I've decided to update exception handling in CGI package and
written the following module:
-- Network/CGI/Monad/NewException.hs
module Network.CGI.Monad.NewException where
import Prelude hiding (catch)
import Control.Exception
import Control.Monad
import Control.Monad.Writer
import Control.Monad.Reader
import Network.CGI.Monad hiding (throwCGI, catchCGI, tryCGI)
import Network.CGI (outputInternalServerError)
-- | Throw an exception in a CGI monad. The monad is required to be
-- a 'MonadIO', so that we can use 'throwIO' to guarantee ordering.
throwCGI :: (MonadCGI m, MonadIO m, Exception e) => e -> m a
throwCGI = liftIO . throwIO
-- | Catches any expection thrown by a CGI action, and uses the given
-- exception handler if an exception is thrown.
catchCGI :: (Exception e) => CGI a -> (e -> CGI a) -> CGI a
catchCGI c h = tryCGI c >>= either h return
handleCGI :: (Exception e) => (e -> CGI a) -> CGI a -> CGI a
handleCGI = flip catchCGI
-- | Catches any exception thrown by an CGI action, and returns either
-- the exception, or if no exception was raised, the result of the action.
tryCGI :: (Exception e) => CGI a -> CGI (Either e a)
tryCGI (CGIT c) = CGIT (ReaderT (\r -> WriterT (f (runWriterT
(runReaderT c r)))))
where
f = liftM (either (\ex -> (Left ex,mempty)) (\(a,w) -> (Right a,w))) . try
handleErrors = handleCGI outputException
outputException e = outputInternalServerError [show (e :: SomeException)]
Then I've updated Main.hs accordingly:
module Main (main) where
...
import Control.Concurrent
import Network.FastCGI hiding (throwCGI, catchCGI, tryCGI,
handleErrors, outputException)
import Network.CGI.Monad.NewException
driver :: CGI CGIResult
driver = ...
main :: IO ()
-- main = runFastCGIConcurrent' forkIO 10 (handleErrors test) -- This
allways gives internal error without a chance to find out what happens
main = runFastCGI $ handleErrors test -- This works fine
So one variant of main function works, the other allways gives no
output. What can be the case?
--
Victor Nazarov
More information about the Haskell-Cafe
mailing list