make cleanup in Delayed more resistant to exceptions

This commit is contained in:
Alp Mestanogullari 2016-10-21 19:24:15 +02:00 committed by Oleg Grenrus
parent 6ab0296d62
commit 7fb11dae3c
2 changed files with 14 additions and 10 deletions

View File

@ -23,6 +23,7 @@ module Servant.Server.Internal
, module Servant.Server.Internal.ServantErr
) where
import Control.Exception (finally)
import Control.Monad.Trans (liftIO)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC8
@ -400,11 +401,13 @@ instance HasServer Raw context where
type ServerT Raw m = Application
route Proxy _ rawApplication = RawRouter $ \ env request respond -> do
(r, _) <- runDelayed rawApplication env request
case r of
Route app -> app request (respond . Route)
Fail a -> respond $ Fail a
FailFatal e -> respond $ FailFatal e
(r, cleanup) <- runDelayed rawApplication env request
go r request respond `finally` cleanup
where go r request respond = case r of
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,
-- this automatically requires your server-side handler to be a function

View File

@ -9,6 +9,7 @@
{-# LANGUAGE TupleSections #-}
module Servant.Server.Internal.RoutingApplication where
import Control.Exception (bracket)
import Control.Monad (ap, liftM)
import Control.Monad.Trans (MonadIO(..))
import Control.Monad.Trans.Except (runExceptT)
@ -272,11 +273,11 @@ runAction :: Delayed env (Handler a)
-> (RouteResult Response -> IO r)
-> (a -> RouteResult Response)
-> IO r
runAction action env req respond k = do
(routeResult, cleanup) <- runDelayed action env req
resp <- go routeResult
cleanup
respond resp
runAction action env req respond k =
bracket (runDelayed action env req)
snd
(\(res, _) -> go res >>= respond)
where
go (Fail e) = return $ Fail e
go (FailFatal e) = return $ FailFatal e