module Hack.Contrib.ShowExceptions where import Hack import Hack.Utils import Hack.Contrib.Hub import MPSUTF8 import Prelude hiding ((.), (^), (>)) import Data.Maybe import Data.Default import System.IO import System.IO.Error program = "ShowExceptions" show_exceptions :: Maybe Stream -> MiddleWare show_exceptions stream app = \env -> do let my_stream = stream.fromMaybe (env.hack_errors) let log = simple_logger my_stream program app env `catch` (handler log) where handler :: Logger -> IOError -> IO Response handler log e = do let message = e.show Error. log message return $ def { status = 500, body = message }