Skip to content

Commit

Permalink
Check for connection status in finalizer
Browse files Browse the repository at this point in the history
Connection could be closed via explicit `connectionClose` call
or via finalizer attached to it. Both should check status to
prevent writing to or reading from closed connection.
See snoyberg#225
  • Loading branch information
Yuras committed Sep 2, 2016
1 parent 9a39b4b commit 3622305
Show file tree
Hide file tree
Showing 2 changed files with 38 additions and 9 deletions.
13 changes: 7 additions & 6 deletions http-client/Network/HTTP/Client/Connection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,12 @@ makeConnection r w c = do
-- already closed connection.
closedVar <- newIORef False

_ <- mkWeakIORef istack c
let close = do
closed <- atomicModifyIORef closedVar (\closed -> (True, closed))
unless closed $
c

_ <- mkWeakIORef istack close
return $! Connection
{ connectionRead = do
closed <- readIORef closedVar
Expand All @@ -113,11 +118,7 @@ makeConnection r w c = do
when closed $ throwHttp ConnectionClosed
w x

, connectionClose = do
closed <- readIORef closedVar
unless closed $
c
writeIORef closedVar True
, connectionClose = close
}

-- | Create a new 'Connection' from a 'Socket'.
Expand Down
34 changes: 31 additions & 3 deletions http-client/test-nonet/Network/HTTP/ClientSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,21 +2,24 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Network.HTTP.ClientSpec where

import Control.Concurrent (threadDelay)
import Control.Concurrent (threadDelay, yield)
import Control.Concurrent.Async (withAsync)
import qualified Control.Concurrent.Async as Async
import Control.Exception (bracket)
import Control.Exception (bracket, throwIO, ErrorCall(..))
import qualified Control.Exception as E
import Control.Monad (forever, replicateM_)
import Control.Monad (forever, replicateM_, when, unless)
import Network.HTTP.Client hiding (port)
import qualified Network.HTTP.Client as NC
import qualified Network.HTTP.Client.Internal as Internal
import Network.HTTP.Types (status413)
import Network.Socket (sClose)
import Test.Hspec
import qualified Data.Streaming.Network as N
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as SL
import Data.ByteString.Lazy.Char8 () -- orphan instance
import Data.IORef
import System.Mem (performGC)

main :: IO ()
main = hspec spec
Expand Down Expand Up @@ -213,3 +216,28 @@ spec = describe "Client" $ do
case e of
HttpExceptionRequest _ (TooManyRedirects _) -> True
_ -> False

it "should not write to closed connection" $ do
-- see https://github.com/snoyberg/http-client/issues/225
closedRef <- newIORef False
okRef <- newIORef True
let checkStatus = do
closed <- readIORef closedRef
when closed $ do
writeIORef okRef False

conn <- makeConnection
(return S.empty)
(const checkStatus)
(checkStatus >> writeIORef closedRef True)

Internal.connectionClose conn

-- let GC release the connection and run finalizers
performGC
yield
performGC

ok <- readIORef okRef
unless ok $
throwIO (ErrorCall "already closed")

0 comments on commit 3622305

Please sign in to comment.