Skip to content

Commit

Permalink
Deprecate liftAndCatchIO and rescue
Browse files Browse the repository at this point in the history
  • Loading branch information
fumieval committed Oct 12, 2023
1 parent c341c1a commit 16f8750
Show file tree
Hide file tree
Showing 8 changed files with 38 additions and 33 deletions.
22 changes: 13 additions & 9 deletions Web/Scotty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ module Web.Scotty
, getResponseHeaders, getResponseStatus, getResponseContent
-- ** Exceptions
, raise, raiseStatus, throw, rescue, next, finish, defaultHandler, liftAndCatchIO
, liftIO, catch
, StatusError(..)
-- * Parsing Parameters
, Param, Trans.Parsable(..), Trans.readEither
Expand All @@ -45,6 +46,7 @@ module Web.Scotty
import qualified Web.Scotty.Trans as Trans

import qualified Control.Exception as E
import Control.Monad.IO.Class
import Data.Aeson (FromJSON, ToJSON)
import qualified Data.ByteString as BS
import Data.ByteString.Lazy.Char8 (ByteString)
Expand All @@ -56,7 +58,7 @@ import Network.Wai (Application, Middleware, Request, StreamingBody)
import Network.Wai.Handler.Warp (Port)

import Web.Scotty.Internal.Types (ScottyT, ActionT, ErrorHandler, Param, RoutePattern, Options, defaultOptions, File, Kilobytes, ScottyState, defaultScottyState, StatusError(..), Content(..))
import UnliftIO.Exception (Handler(..))
import UnliftIO.Exception (Handler(..), catch)

type ScottyM = ScottyT IO
type ActionM = ActionT IO
Expand Down Expand Up @@ -107,19 +109,19 @@ nested = Trans.nested
setMaxRequestBodySize :: Kilobytes -> ScottyM ()
setMaxRequestBodySize = Trans.setMaxRequestBodySize

-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'rescue'.
-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'catch'.
--
-- Uncaught exceptions turn into HTTP 500 responses.
raise :: Text -> ActionM a
raise = Trans.raise

-- | Throw a 'StatusError' exception that has an associated HTTP error code and can be caught with 'rescue'.
-- | Throw a 'StatusError' exception that has an associated HTTP error code and can be caught with 'catch'.
--
-- Uncaught exceptions turn into HTTP responses corresponding to the given status.
raiseStatus :: Status -> Text -> ActionM a
raiseStatus = Trans.raiseStatus

-- | Throw an exception which can be caught within the scope of the current Action with 'rescue' or 'catch'.
-- | Throw an exception which can be caught within the scope of the current Action with 'catch'.
--
-- If the exception is not caught locally, another option is to implement a global 'Handler' (with 'defaultHandler') that defines its interpretation and a translation to HTTP error codes.
--
Expand Down Expand Up @@ -164,13 +166,15 @@ finish = Trans.finish

-- | Catch an exception e.g. a 'StatusError' or a user-defined exception.
--
-- > raise JustKidding `rescue` (\msg -> text msg)
-- > raise JustKidding `catch` (\msg -> text msg)
rescue :: E.Exception e => ActionM a -> (e -> ActionM a) -> ActionM a
rescue = Trans.rescue

Check warning on line 171 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

In the use of ‘rescue’

Check warning on line 171 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

In the use of ‘rescue’

Check warning on line 171 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

In the use of ‘rescue’

Check warning on line 171 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.6

In the use of ‘rescue’

Check warning on line 171 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.2

In the use of ‘rescue’
{-# DEPRECATED rescue "Use catch instead" #-}

-- | Like 'liftIO', but catch any IO exceptions and turn them into Scotty exceptions.
liftAndCatchIO :: IO a -> ActionM a
liftAndCatchIO = Trans.liftAndCatchIO

Check warning on line 176 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

In the use of ‘liftAndCatchIO’

Check warning on line 176 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

In the use of ‘liftAndCatchIO’

Check warning on line 176 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

In the use of ‘liftAndCatchIO’

Check warning on line 176 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.6

In the use of ‘liftAndCatchIO’

Check warning on line 176 in Web/Scotty.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.2

In the use of ‘liftAndCatchIO’
{-# DEPRECATED liftAndCatchIO "Use liftIO instead" #-}

-- | Redirect to given URL. Like throwing an uncatchable exception. Any code after the call to redirect
-- will not be run.
Expand Down Expand Up @@ -215,7 +219,7 @@ jsonData = Trans.jsonData

-- | Get a parameter. First looks in captures, then form data, then query parameters.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found.
-- * Raises an exception which can be caught by 'catch' if parameter is not found.
--
-- * If parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
-- This means captures are somewhat typed, in that a route won't match if a correctly typed
Expand All @@ -226,7 +230,7 @@ param = Trans.param

-- | Get a capture parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 500 ("Internal Server Error") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 500 ("Internal Server Error") to the client.
--
-- * If the parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
--
Expand All @@ -236,7 +240,7 @@ captureParam = Trans.captureParam

-- | Get a form parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
--
Expand All @@ -246,7 +250,7 @@ formParam = Trans.formParam

-- | Get a query parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
--
Expand Down
29 changes: 14 additions & 15 deletions Web/Scotty/Action.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ import Numeric.Natural

import Web.Scotty.Internal.Types
import Web.Scotty.Util (mkResponse, addIfNotPresent, add, replace, lazyTextToStrictByteString, strictByteStringToLazyText)
import UnliftIO.Exception (Handler(..), catch, catches, tryAny)
import UnliftIO.Exception (Handler(..), catch, catches)

import Network.Wai.Internal (ResponseReceived(..))

Expand Down Expand Up @@ -134,21 +134,21 @@ someExceptionHandler :: MonadIO m => ErrorHandler m
someExceptionHandler = Handler $ \case
(_ :: E.SomeException) -> status status500

-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'rescue'.
-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'catch'.
--
-- Uncaught exceptions turn into HTTP 500 responses.
raise :: (MonadIO m) =>
T.Text -- ^ Error text
-> ActionT m a
raise = raiseStatus status500

-- | Throw a 'StatusError' exception that has an associated HTTP error code and can be caught with 'rescue'.
-- | Throw a 'StatusError' exception that has an associated HTTP error code and can be caught with 'catch'.
--
-- Uncaught exceptions turn into HTTP responses corresponding to the given status.
raiseStatus :: Monad m => Status -> T.Text -> ActionT m a
raiseStatus s = E.throw . StatusError s

-- | Throw an exception which can be caught within the scope of the current Action with 'rescue' or 'catch'.
-- | Throw an exception which can be caught within the scope of the current Action with 'catch'.
--
-- If the exception is not caught locally, another option is to implement a global 'Handler' (with 'defaultHandler') that defines its interpretation and a translation to HTTP error codes.
--
Expand Down Expand Up @@ -178,16 +178,15 @@ next = E.throw AENext

-- | Catch an exception e.g. a 'StatusError' or a user-defined exception.
--
-- > raise JustKidding `rescue` (\msg -> text msg)
-- > raise JustKidding `catch` (\msg -> text msg)
rescue :: (MonadUnliftIO m, E.Exception e) => ActionT m a -> (e -> ActionT m a) -> ActionT m a
rescue = catch
{-# DEPRECATED rescue "Use catch instead" #-}

-- | Catch any synchronous IO exceptions
liftAndCatchIO :: MonadIO m => IO a -> ActionT m a
liftAndCatchIO io = liftIO $ do
r <- tryAny io
either E.throwIO pure r

liftAndCatchIO = liftIO
{-# DEPRECATED liftAndCatchIO "Use liftIO instead" #-}

-- | Redirect to given URL. Like throwing an uncatchable exception. Any code after the call to redirect
-- will not be run.
Expand Down Expand Up @@ -271,7 +270,7 @@ jsonData = do

-- | Get a parameter. First looks in captures, then form data, then query parameters.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found.
-- * Raises an exception which can be caught by 'catch' if parameter is not found.
--
-- * If parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
-- This means captures are somewhat typed, in that a route won't match if a correctly typed
Expand All @@ -286,7 +285,7 @@ param k = do

-- | Look up a capture parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 500 ("Internal Server Error") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 500 ("Internal Server Error") to the client.
--
-- * If the parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
--
Expand All @@ -297,7 +296,7 @@ captureParam = paramWith CaptureParam envCaptureParams status500

-- | Look up a form parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
--
Expand All @@ -307,7 +306,7 @@ formParam = paramWith FormParam envFormParams status400

-- | Look up a query parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
-- * Raises an exception which can be caught by 'catch' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
--
Expand Down Expand Up @@ -548,6 +547,6 @@ nested app = do
-- Is MVar really the best choice here? Not sure.
r <- request
ref <- liftIO $ newEmptyMVar
_ <- liftAndCatchIO $ app r (\res -> putMVar ref res >> return ResponseReceived)
res <- liftAndCatchIO $ readMVar ref
_ <- liftIO $ app r (\res -> putMVar ref res >> return ResponseReceived)
res <- liftIO $ readMVar ref
rawResponse res
2 changes: 1 addition & 1 deletion Web/Scotty/Internal/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,7 @@ newtype ActionT m a = ActionT { runAM :: ReaderT ActionEnv m a }
instance (MonadUnliftIO m) => MonadError StatusError (ActionT m) where
throwError = E.throw
catchError = catch
-- | Modeled after the behaviour in scotty < 0.20, 'fail' throws a 'StatusError' with code 500 ("Server Error"), which can be caught with 'E.catch' or 'rescue'.
-- | Modeled after the behaviour in scotty < 0.20, 'fail' throws a 'StatusError' with code 500 ("Server Error"), which can be caught with 'E.catch'.
instance (MonadIO m) => MonadFail (ActionT m) where
fail = E.throw . StatusError status500 . pack
-- | 'empty' throws 'ActionError' 'AENext', whereas '(<|>)' catches any 'ActionError's or 'StatusError's in the first action and proceeds to the second one.
Expand Down
3 changes: 2 additions & 1 deletion Web/Scotty/Trans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module Web.Scotty.Trans
, getResponseHeaders, getResponseStatus, getResponseContent
-- ** Exceptions
, raise, raiseStatus, throw, rescue, next, finish, defaultHandler, liftAndCatchIO
, liftIO, catch
, StatusError(..)
-- * Parsing Parameters
, Param, Parsable(..), readEither
Expand Down Expand Up @@ -66,7 +67,7 @@ import Web.Scotty.Route
import Web.Scotty.Internal.Types (ActionT(..), ScottyT(..), defaultScottyState, Application, RoutePattern, Options(..), defaultOptions, RouteOptions(..), defaultRouteOptions, ErrorHandler, Kilobytes, File, addMiddleware, setHandler, updateMaxRequestBodySize, routes, middlewares, ScottyException(..), ScottyState, defaultScottyState, StatusError(..), Content(..))
import Web.Scotty.Util (socketDescription)
import Web.Scotty.Body (newBodyInfo)
import UnliftIO.Exception (Handler(..), catches)
import UnliftIO.Exception (Handler(..), catch, catches)

-- | Run a scotty application using the warp server.
-- NB: scotty p === scottyT p id
Expand Down
1 change: 1 addition & 0 deletions changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

* add getResponseHeaders, getResponseStatus, getResponseContent (#214)
* add `captureParamMaybe`, `formParamMaybe`, `queryParamMaybe` (#322)
* deprecate `rescue` and `liftAndCatchIO`

## 0.20.1 [2023.10.03]

Expand Down
2 changes: 1 addition & 1 deletion examples/basic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ main = scotty 3000 $ do
-- Of course you can catch your own errors.
get "/rescue" $ do
(do void $ throw Boom; redirect "http://www.we-never-go-here.com")
`rescue` (\(e :: Err) -> text $ "we recovered from " `mappend` pack (show e))
`catch` (\(e :: Err) -> text $ "we recovered from " `mappend` pack (show e))

-- Parts of the URL that start with a colon match
-- any string, and capture that value as a parameter.
Expand Down
2 changes: 1 addition & 1 deletion examples/exceptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,4 +58,4 @@ main = scottyT 3000 id $ do -- note, we aren't using any additional transformer
i <- liftIO randomIO
let catchOne Forbidden = html "<h1>Forbidden was randomly thrown, but we caught it."
catchOne other = throw other
throw (if rBool then Forbidden else NotFound i) `rescue` catchOne
throw (if rBool then Forbidden else NotFound i) `catch` catchOne
10 changes: 5 additions & 5 deletions test/Web/ScottySpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ spec = do
withApp (do
let h = Handler (\(_ :: E.ArithException) -> status status503)
defaultHandler h
Scotty.get "/" (liftAndCatchIO $ E.throwIO E.DivideByZero)) $ do
Scotty.get "/" (liftIO $ E.throwIO E.DivideByZero)) $ do
it "allows to customize the HTTP status code" $ do
get "/" `shouldRespondWith` "" {matchStatus = 503}

Expand Down Expand Up @@ -145,7 +145,7 @@ spec = do
withApp (Scotty.get "/" $ fail "boom!") $ do
it "returns 500 if not caught" $
get "/" `shouldRespondWith` 500
withApp (Scotty.get "/" $ (fail "boom!") `rescue` (\(_ :: StatusError) -> text "ok")) $
withApp (Scotty.get "/" $ (fail "boom!") `catch` (\(_ :: StatusError) -> text "ok")) $
it "can catch the StatusError thrown by fail" $ do
get "/" `shouldRespondWith` 200 { matchBody = "ok"}

Expand Down Expand Up @@ -188,7 +188,7 @@ spec = do
get "/search/potato" `shouldRespondWith` 500
context "recover from missing parameter exception" $ do
withApp (Scotty.get "/search/:q" $
(captureParam "z" >>= text) `rescue` (\(_::StatusError) -> text "z")
(captureParam "z" >>= text) `catch` (\(_::StatusError) -> text "z")
) $ do
it "catches a StatusError" $ do
get "/search/xxx" `shouldRespondWith` 200 { matchBody = "z"}
Expand All @@ -206,7 +206,7 @@ spec = do
get "/search?query=potato" `shouldRespondWith` 400
context "recover from type mismatch parameter exception" $ do
withApp (Scotty.get "/search" $
(queryParam "z" >>= (\v -> json (v :: Int))) `rescue` (\(_::StatusError) -> text "z")
(queryParam "z" >>= (\v -> json (v :: Int))) `catch` (\(_::StatusError) -> text "z")
) $ do
it "catches a StatusError" $ do
get "/search?query=potato" `shouldRespondWith` 200 { matchBody = "z"}
Expand Down Expand Up @@ -238,7 +238,7 @@ spec = do
postForm "/" "p=42" `shouldRespondWith` "42"
context "recover from type mismatch parameter exception" $ do
withApp (Scotty.post "/search" $
(formParam "z" >>= (\v -> json (v :: Int))) `rescue` (\(_::StatusError) -> text "z")
(formParam "z" >>= (\v -> json (v :: Int))) `catch` (\(_::StatusError) -> text "z")
) $ do
it "catches a StatusError" $ do
postForm "/search" "z=potato" `shouldRespondWith` 200 { matchBody = "z"}
Expand Down

0 comments on commit 16f8750

Please sign in to comment.