Skip to content

Commit

Permalink
Print unhandled exception to stdout depending on verbosity
Browse files Browse the repository at this point in the history
  • Loading branch information
cblp committed Feb 11, 2024
1 parent 66d60f7 commit 910ca3d
Show file tree
Hide file tree
Showing 6 changed files with 50 additions and 23 deletions.
6 changes: 3 additions & 3 deletions Web/Scotty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ scottySocket opts sock = Trans.scottySocketT opts sock id
-- | Turn a scotty application into a WAI 'Application', which can be
-- run with any WAI handler.
scottyApp :: ScottyM () -> IO Application
scottyApp = Trans.scottyAppT id
scottyApp = Trans.scottyAppT defaultOptions id

-- | Global handler for user-defined exceptions.
defaultHandler :: ErrorHandler IO -> ScottyM ()
Expand All @@ -141,8 +141,8 @@ nested :: Application -> ActionM ()
nested = Trans.nested

-- | Set global size limit for the request body. Requests with body size exceeding the limit will not be
-- processed and an HTTP response 413 will be returned to the client. Size limit needs to be greater than 0,
-- otherwise the application will terminate on start.
-- processed and an HTTP response 413 will be returned to the client. Size limit needs to be greater than 0,
-- otherwise the application will terminate on start.
setMaxRequestBodySize :: Kilobytes -> ScottyM ()
setMaxRequestBodySize = Trans.setMaxRequestBodySize

Expand Down
19 changes: 13 additions & 6 deletions Web/Scotty/Action.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE LambdaCase #-}
Expand Down Expand Up @@ -82,6 +83,7 @@ import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TLE
import Data.Time (UTCTime)
import Data.Time.Format (parseTimeM, defaultTimeLocale)
import Data.Typeable (typeOf)
import Data.Word

import Network.HTTP.Types
Expand All @@ -105,15 +107,16 @@ import Network.Wai.Internal (ResponseReceived(..))
-- 'Nothing' indicates route failed (due to Next) and pattern matching should try the next available route.
-- 'Just' indicates a successful response.
runAction :: MonadUnliftIO m =>
Maybe (ErrorHandler m) -- ^ this handler (if present) is in charge of user-defined exceptions
Options
-> Maybe (ErrorHandler m) -- ^ this handler (if present) is in charge of user-defined exceptions
-> ActionEnv
-> ActionT m () -- ^ Route action to be evaluated
-> m (Maybe Response)
runAction mh env action = do
runAction options mh env action = do
ok <- flip runReaderT env $ runAM $ tryNext $ action `catches` concat
[ [actionErrorHandler]
, maybeToList mh
, [statusErrorHandler, scottyExceptionHandler, someExceptionHandler]
, [statusErrorHandler, scottyExceptionHandler, someExceptionHandler options]
]
res <- getResponse env
return $ bool Nothing (Just $ mkResponse res) ok
Expand Down Expand Up @@ -171,9 +174,13 @@ scottyExceptionHandler = Handler $ \case
text $ T.unwords [ "Failed to parse parameter", k, v, ":", e]

-- | Uncaught exceptions turn into HTTP 500 Server Error codes
someExceptionHandler :: MonadIO m => ErrorHandler m
someExceptionHandler = Handler $ \case
(_ :: E.SomeException) -> status status500
someExceptionHandler :: MonadIO m => Options -> ErrorHandler m
someExceptionHandler Options{verbose} =
Handler $ \(E.SomeException e) -> do
when (verbose > 0) $
liftIO $
putStrLn $ "Caught and exception of " <> show (typeOf e) <> ": " <> show e
status status500

-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'catch'.
--
Expand Down
3 changes: 2 additions & 1 deletion Web/Scotty/Internal/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,8 @@ updateMaxRequestBodySize RouteOptions { .. } s@ScottyState { routeOptions = ro }
let ro' = ro { maxRequestBodySize = maxRequestBodySize }
in s { routeOptions = ro' }

newtype ScottyT m a = ScottyT { runS :: State (ScottyState m) a }
newtype ScottyT m a =
ScottyT { runS :: ReaderT Options (State (ScottyState m)) a }
deriving ( Functor, Applicative, Monad )


Expand Down
26 changes: 20 additions & 6 deletions Web/Scotty/Route.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ import Control.Arrow ((***))
import Control.Concurrent.STM (newTVarIO)
import Control.Monad.IO.Class (MonadIO(..))
import UnliftIO (MonadUnliftIO(..))
import qualified Control.Monad.Reader as MR
import qualified Control.Monad.State as MS

import Data.String (fromString)
Expand All @@ -20,7 +21,7 @@ import Network.Wai (Request(..))
import qualified Text.Regex as Regex

import Web.Scotty.Action
import Web.Scotty.Internal.Types (RoutePattern(..), RouteOptions, ActionEnv(..), ActionT, ScottyState(..), ScottyT(..), ErrorHandler, Middleware, BodyInfo, handler, addRoute, defaultScottyResponse)
import Web.Scotty.Internal.Types (Options, RoutePattern(..), RouteOptions, ActionEnv(..), ActionT, ScottyState(..), ScottyT(..), ErrorHandler, Middleware, BodyInfo, handler, addRoute, defaultScottyResponse)

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.3

The import of ‘ActionT’

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

The import of ‘ActionT’

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.6

The import of ‘ActionT’

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.2

The import of ‘ActionT’

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

The import of ‘ActionT’

Check warning on line 24 in Web/Scotty/Route.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

The import of ‘ActionT’
import Web.Scotty.Util (decodeUtf8Lenient)
import Web.Scotty.Body (cloneBodyInfo, getBodyAction, getBodyChunkAction, getFormParamsAndFilesAction)

Expand Down Expand Up @@ -78,7 +79,13 @@ options = addroute OPTIONS

-- | Add a route that matches regardless of the HTTP verb.
matchAny :: (MonadUnliftIO m) => RoutePattern -> ActionT m () -> ScottyT m ()
matchAny pat action = ScottyT $ MS.modify $ \s -> addRoute (route (routeOptions s) (handler s) Nothing pat action) s
matchAny pat action =
ScottyT $ do
serverOptions <- MR.ask
MS.modify $ \s ->
addRoute
(route serverOptions (routeOptions s) (handler s) Nothing pat action)
s

-- | Specify an action to take if nothing else is found. Note: this _always_ matches,
-- so should generally be the last route specified.
Expand All @@ -101,12 +108,19 @@ let server = S.get "/foo/:bar" (S.pathParam "bar" >>= S.text)
"something"
-}
addroute :: (MonadUnliftIO m) => StdMethod -> RoutePattern -> ActionT m () -> ScottyT m ()
addroute method pat action = ScottyT $ MS.modify $ \s -> addRoute (route (routeOptions s) (handler s) (Just method) pat action) s
addroute method pat action =
ScottyT $ do
serverOptions <- MR.ask
MS.modify $ \s ->
addRoute
(route serverOptions (routeOptions s) (handler s) (Just method) pat action)
s

route :: (MonadUnliftIO m) =>
RouteOptions
Options
-> RouteOptions
-> Maybe (ErrorHandler m) -> Maybe StdMethod -> RoutePattern -> ActionT m () -> BodyInfo -> Middleware m
route opts h method pat action bodyInfo app req =
route serverOpts opts h method pat action bodyInfo app req =
let tryNext = app req
-- We match all methods in the case where 'method' is 'Nothing'.
-- See https://github.com/scotty-web/scotty/issues/196 and 'matchAny'
Expand All @@ -125,7 +139,7 @@ route opts h method pat action bodyInfo app req =
clonedBodyInfo <- cloneBodyInfo bodyInfo

env <- mkEnv clonedBodyInfo req captures opts
res <- runAction h env action
res <- runAction serverOpts h env action
maybe tryNext return res
Nothing -> tryNext
else tryNext
Expand Down
14 changes: 8 additions & 6 deletions Web/Scotty/Trans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,7 @@ import Blaze.ByteString.Builder.Char8 (fromString)

import Control.Exception (assert)
import Control.Monad (when)
import Control.Monad.Reader (runReaderT)
import Control.Monad.State.Strict (execState, modify)
import Control.Monad.IO.Class

Expand Down Expand Up @@ -101,7 +102,7 @@ scottyOptsT :: (Monad m, MonadIO n)
scottyOptsT opts runActionToIO s = do
when (verbose opts > 0) $
liftIO $ putStrLn $ "Setting phasers to stun... (port " ++ show (getPort (settings opts)) ++ ") (ctrl-c to quit)"
liftIO . runSettings (settings opts) =<< scottyAppT runActionToIO s
liftIO . runSettings (settings opts) =<< scottyAppT opts runActionToIO s

-- | Run a scotty application using the warp server, passing extra options, and
-- listening on the provided socket.
Expand All @@ -116,17 +117,18 @@ scottySocketT opts sock runActionToIO s = do
when (verbose opts > 0) $ do
d <- liftIO $ socketDescription sock
liftIO $ putStrLn $ "Setting phasers to stun... (" ++ d ++ ") (ctrl-c to quit)"
liftIO . runSettingsSocket (settings opts) sock =<< scottyAppT runActionToIO s
liftIO . runSettingsSocket (settings opts) sock =<< scottyAppT opts runActionToIO s

-- | Turn a scotty application into a WAI 'Application', which can be
-- run with any WAI handler.
-- NB: scottyApp === scottyAppT id
scottyAppT :: (Monad m, Monad n)
=> (m W.Response -> IO W.Response) -- ^ Run monad 'm' into 'IO', called at each action.
=> Options
-> (m W.Response -> IO W.Response) -- ^ Run monad 'm' into 'IO', called at each action.
-> ScottyT m ()
-> n W.Application
scottyAppT runActionToIO defs = do
let s = execState (runS defs) defaultScottyState
scottyAppT options runActionToIO defs = do

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.3

This binding for ‘options’ shadows the existing binding

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

This binding for ‘options’ shadows the existing binding

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.6

This binding for ‘options’ shadows the existing binding

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.2

This binding for ‘options’ shadows the existing binding

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

This binding for ‘options’ shadows the existing binding

Check warning on line 130 in Web/Scotty/Trans.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

This binding for ‘options’ shadows the existing binding
let s = execState (runReaderT (runS defs) options) defaultScottyState
let rapp req callback = do
bodyInfo <- newBodyInfo req
resp <- runActionToIO (applyAll notFoundApp ([midd bodyInfo | midd <- routes s]) req)
Expand Down Expand Up @@ -160,7 +162,7 @@ middleware :: W.Middleware -> ScottyT m ()
middleware = ScottyT . modify . addMiddleware

-- | Set global size limit for the request body. Requests with body size exceeding the limit will not be
-- processed and an HTTP response 413 will be returned to the client. Size limit needs to be greater than 0,
-- processed and an HTTP response 413 will be returned to the client. Size limit needs to be greater than 0,
-- otherwise the application will terminate on start.
setMaxRequestBodySize :: Kilobytes -- ^ Request size limit
-> ScottyT m ()
Expand Down
5 changes: 4 additions & 1 deletion bench/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Lucid.Base
import Lucid.Html5
import Web.Scotty
import Web.Scotty.Internal.Types
import qualified Control.Monad.Reader as R
import qualified Control.Monad.State.Lazy as SL
import qualified Control.Monad.State.Strict as SS
import qualified Data.ByteString.Lazy as BL
Expand All @@ -23,7 +24,9 @@ main = do
setColumns [Case,Allocated,GCs,Live,Check,Max,MaxOS]
setFormat Markdown
io "ScottyM Strict" BL.putStr
(SS.evalState (runS $ renderBST htmlScotty) defaultScottyState)
(SS.evalState
(R.runReaderT (runS $ renderBST htmlScotty) defaultOptions)
defaultScottyState)
io "ScottyM Lazy" BL.putStr
(SL.evalState (runScottyLazy $ renderBST htmlScottyLazy) defaultScottyState)
io "Identity" BL.putStr
Expand Down

0 comments on commit 910ca3d

Please sign in to comment.