make cleanup in Delayed more resistant to exceptions
This commit is contained in:
parent
4a52cce9b8
commit
9beedb59a9
2 changed files with 14 additions and 10 deletions
|
@ -22,6 +22,7 @@ module Servant.Server.Internal
|
||||||
, module Servant.Server.Internal.ServantErr
|
, module Servant.Server.Internal.ServantErr
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Control.Exception (finally)
|
||||||
import Control.Monad.Trans (liftIO)
|
import Control.Monad.Trans (liftIO)
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
import qualified Data.ByteString.Char8 as BC8
|
import qualified Data.ByteString.Char8 as BC8
|
||||||
|
@ -398,11 +399,13 @@ instance HasServer Raw context where
|
||||||
type ServerT Raw m = Application
|
type ServerT Raw m = Application
|
||||||
|
|
||||||
route Proxy _ rawApplication = RawRouter $ \ env request respond -> do
|
route Proxy _ rawApplication = RawRouter $ \ env request respond -> do
|
||||||
(r, _) <- runDelayed rawApplication env request
|
(r, cleanup) <- runDelayed rawApplication env request
|
||||||
case r of
|
go r request respond `finally` cleanup
|
||||||
Route app -> app request (respond . Route)
|
|
||||||
Fail a -> respond $ Fail a
|
where go r request respond = case r of
|
||||||
FailFatal e -> respond $ FailFatal e
|
Route app -> app request (respond . Route)
|
||||||
|
Fail a -> respond $ Fail a
|
||||||
|
FailFatal e -> respond $ FailFatal e
|
||||||
|
|
||||||
-- | If you use 'ReqBody' in one of the endpoints for your API,
|
-- | If you use 'ReqBody' in one of the endpoints for your API,
|
||||||
-- this automatically requires your server-side handler to be a function
|
-- this automatically requires your server-side handler to be a function
|
||||||
|
|
|
@ -9,6 +9,7 @@
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
module Servant.Server.Internal.RoutingApplication where
|
module Servant.Server.Internal.RoutingApplication where
|
||||||
|
|
||||||
|
import Control.Exception (bracket)
|
||||||
import Control.Monad (ap, liftM)
|
import Control.Monad (ap, liftM)
|
||||||
import Control.Monad.Trans (MonadIO(..))
|
import Control.Monad.Trans (MonadIO(..))
|
||||||
import Control.Monad.Trans.Except (runExceptT)
|
import Control.Monad.Trans.Except (runExceptT)
|
||||||
|
@ -271,11 +272,11 @@ runAction :: Delayed env (Handler a)
|
||||||
-> (RouteResult Response -> IO r)
|
-> (RouteResult Response -> IO r)
|
||||||
-> (a -> RouteResult Response)
|
-> (a -> RouteResult Response)
|
||||||
-> IO r
|
-> IO r
|
||||||
runAction action env req respond k = do
|
runAction action env req respond k =
|
||||||
(routeResult, cleanup) <- runDelayed action env req
|
bracket (runDelayed action env req)
|
||||||
resp <- go routeResult
|
snd
|
||||||
cleanup
|
(\(res, _) -> go res >>= respond)
|
||||||
respond resp
|
|
||||||
where
|
where
|
||||||
go (Fail e) = return $ Fail e
|
go (Fail e) = return $ Fail e
|
||||||
go (FailFatal e) = return $ FailFatal e
|
go (FailFatal e) = return $ FailFatal e
|
||||||
|
|
Loading…
Reference in a new issue