Hello community,

here is the log from the commit of package ghc-warp for openSUSE:Factory 
checked in at 2017-02-21 13:46:01
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-warp (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-warp.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-warp"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-warp/ghc-warp.changes        2016-12-09 
09:38:00.206358895 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-warp.new/ghc-warp.changes   2017-02-21 
13:46:02.336774970 +0100
@@ -1,0 +2,10 @@
+Sun Feb  5 19:32:29 UTC 2017 - [email protected]
+
+- Update to version 3.2.11 with cabal2obs.
+
+-------------------------------------------------------------------
+Mon Jan 30 09:34:53 UTC 2017 - [email protected]
+
+- Update to version 3.2.10 with cabal2obs.
+
+-------------------------------------------------------------------

Old:
----
  warp-3.2.9.tar.gz

New:
----
  warp-3.2.11.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-warp.spec ++++++
--- /var/tmp/diff_new_pack.plI5vy/_old  2017-02-21 13:46:03.160658740 +0100
+++ /var/tmp/diff_new_pack.plI5vy/_new  2017-02-21 13:46:03.160658740 +0100
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-warp
 #
-# Copyright (c) 2016 SUSE LINUX GmbH, Nuernberg, Germany.
+# Copyright (c) 2017 SUSE LINUX GmbH, Nuernberg, Germany.
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -19,7 +19,7 @@
 %global pkg_name warp
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        3.2.9
+Version:        3.2.11
 Release:        0
 Summary:        A fast, light-weight web server for WAI applications
 License:        MIT

++++++ warp-3.2.9.tar.gz -> warp-3.2.11.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/ChangeLog.md new/warp-3.2.11/ChangeLog.md
--- old/warp-3.2.9/ChangeLog.md 2016-11-08 04:53:07.000000000 +0100
+++ new/warp-3.2.11/ChangeLog.md        2017-02-02 02:57:32.000000000 +0100
@@ -1,6 +1,14 @@
+## 3.2.11
+
+* Fixing 10 HTTP2 bugs pointed out by h2spec v2.
+
+## 3.2.10
+
+* Add `connFree` to `Connection`. Close socket connections on timeout 
triggered. Timeout exceptions extend from `SomeAsyncException`. 
[#602](https://github.com/yesodweb/wai/pull/602) 
[#605](https://github.com/yesodweb/wai/pull/605)
+
 ## 3.2.9
 
-* Fixing a space leak. [#586] https://github.com/yesodweb/wai/pull/586
+* Fixing a space leak. [#586](https://github.com/yesodweb/wai/pull/586)
 
 ## 3.2.8
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/HPACK.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/HPACK.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/HPACK.hs      2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/HPACK.hs     2017-02-02 
02:57:32.000000000 +0100
@@ -83,13 +83,16 @@
 {-# INLINE checkRequestHeader #-}
 checkRequestHeader :: ValueTable -> Bool
 checkRequestHeader reqvt
+  | just mMethod (== "CONNECT") = mPath == Nothing && mScheme == Nothing
   | mStatus     /= Nothing      = False
   | mMethod     == Nothing      = False
+  | mScheme     == Nothing      = False
+  | mPath       == Nothing      = False
+  | mPath       == Just ""      = False
   | mAuthority  == Nothing      = False
   | mConnection /= Nothing      = False
   | just mTE (/= "trailers")    = False
-  | just mMethod (== "CONNECT") = mPath == Nothing && mScheme == Nothing
-  | otherwise                   = mPath /= Nothing
+  | otherwise                   = True
   where
     mStatus     = getHeaderValue tokenStatus reqvt
     mScheme     = getHeaderValue tokenScheme reqvt
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Receiver.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Receiver.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Receiver.hs   2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Receiver.hs  2017-02-02 
02:57:32.000000000 +0100
@@ -159,6 +159,8 @@
                      when (ftyp == FrameHeaders) $ do
                          st <- readIORef $ streamState strm0
                          when (isHalfClosed st) $ E.throwIO $ ConnectionError 
StreamClosed "header must not be sent to half closed"
+                         -- Priority made an idele stream
+                         when (isIdle st) $ opened ctx strm0
                      return js
                  Nothing
                    | isResponse streamId -> return Nothing
@@ -166,19 +168,23 @@
                          when (ftyp `notElem` [FrameHeaders,FramePriority]) $
                              E.throwIO $ ConnectionError ProtocolError "this 
frame is not allowed in an idel stream"
                          csid <- readIORef clientStreamId
-                         when (streamId <= csid) $
-                             E.throwIO $ ConnectionError ProtocolError "stream 
identifier must not decrease"
-                         when (ftyp == FrameHeaders) $ do
-                             writeIORef clientStreamId streamId
-                             cnt <- readIORef concurrency
-                             -- Checking the limitation of concurrency
-                             when (cnt >= maxConcurrency) $
-                                 E.throwIO $ StreamError RefusedStream streamId
-                         ws <- initialWindowSize <$> readIORef http2settings
-                         newstrm <- newStream streamId (fromIntegral ws)
-                         when (ftyp == FrameHeaders) $ opened ctx newstrm
-                         insert streamTable streamId newstrm
-                         return $ Just newstrm
+                         if streamId <= csid then do
+                             if ftyp == FramePriority then
+                                 return Nothing -- will be ignored
+                               else
+                                 E.throwIO $ ConnectionError ProtocolError 
"stream identifier must not decrease"
+                           else do
+                             when (ftyp == FrameHeaders) $ do
+                                 writeIORef clientStreamId streamId
+                                 cnt <- readIORef concurrency
+                                 -- Checking the limitation of concurrency
+                                 when (cnt >= maxConcurrency) $
+                                     E.throwIO $ StreamError RefusedStream 
streamId
+                             ws <- initialWindowSize <$> readIORef 
http2settings
+                             newstrm <- newStream streamId (fromIntegral ws)
+                             when (ftyp == FrameHeaders) $ opened ctx newstrm
+                             insert streamTable streamId newstrm
+                             return $ Just newstrm
 
     consume = void . recvN
 
@@ -191,14 +197,18 @@
 ----------------------------------------------------------------
 
 control :: FrameTypeId -> FrameHeader -> ByteString -> Context -> IO Bool
-control FrameSettings header@FrameHeader{flags} bs Context{http2settings, 
controlQ,firstSettings} = do
+control FrameSettings header@FrameHeader{flags} bs Context{http2settings, 
controlQ, firstSettings, streamTable} = do
     SettingsFrame alist <- guardIt $ decodeSettingsFrame header bs
     case checkSettingsList alist of
         Just x  -> E.throwIO x
         Nothing -> return ()
     -- HTTP/2 Setting from a browser
     unless (testAck flags) $ do
+        oldws <- initialWindowSize <$> readIORef http2settings
         modifyIORef' http2settings $ \old -> updateSettings old alist
+        newws <- initialWindowSize <$> readIORef http2settings
+        let diff = newws - oldws
+        when (diff /= 0) $ updateAllStreamWindow (+ diff) streamTable
         let !frame = settingsFrame setAck []
         sent <- readIORef firstSettings
         let !setframe
@@ -210,7 +220,7 @@
 
 control FramePing FrameHeader{flags} bs Context{controlQ} =
     if testAck flags then
-        E.throwIO $ ConnectionError ProtocolError "the ack flag of this ping 
frame must not be set"
+        return True -- just ignore
       else do
         let !frame = pingFrame bs
         enqueueControl controlQ $ CFrame frame
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Types.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Types.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Types.hs      2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Types.hs     2017-02-02 
02:57:32.000000000 +0100
@@ -11,7 +11,7 @@
 import Control.Concurrent (forkIO)
 import Control.Concurrent.STM
 import Control.Exception (SomeException, bracket)
-import Control.Monad (void)
+import Control.Monad (void, forM_)
 import Data.ByteString (ByteString)
 import qualified Data.ByteString as BS
 import Data.IntMap.Strict (IntMap, IntMap)
@@ -256,6 +256,11 @@
 search :: StreamTable -> M.Key -> IO (Maybe Stream)
 search (StreamTable ref) k = M.lookup k <$> readIORef ref
 
+updateAllStreamWindow :: (WindowSize -> WindowSize) -> StreamTable -> IO ()
+updateAllStreamWindow adst (StreamTable ref) = do
+    strms <- M.elems <$> readIORef ref
+    forM_ strms $ \strm -> atomically $ modifyTVar (streamWindow strm) adst
+
 {-# INLINE forkAndEnqueueWhenReady #-}
 forkAndEnqueueWhenReady :: IO () -> PriorityTree Output -> Output -> Manager 
-> IO ()
 forkAndEnqueueWhenReady wait outQ out mgr = bracket setup teardown $ \_ ->
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Worker.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Worker.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/HTTP2/Worker.hs     2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/HTTP2/Worker.hs    2017-02-02 
02:57:32.000000000 +0100
@@ -236,7 +236,8 @@
 worker ctx@Context{inputQ,controlQ} set app responder tm = do
     sinfo <- newStreamInfo
     tcont <- newThreadContinue
-    E.bracket (T.registerKillThread tm) T.cancel $ go sinfo tcont
+    let timeoutAction = return () -- cannot close the shared connection
+    E.bracket (T.registerKillThread tm timeoutAction) T.cancel $ go sinfo tcont
   where
     go sinfo tcont th = do
         setThreadContinue tcont True
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/Run.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/Run.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/Run.hs      2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/Run.hs     2017-02-02 
02:57:32.000000000 +0100
@@ -24,8 +24,8 @@
 import Data.Streaming.Network (bindPortTCP)
 import Foreign.C.Error (Errno(..), eCONNABORTED)
 import GHC.IO.Exception (IOException(..))
-import Network (sClose, Socket)
-import Network.Socket (accept, withSocketsDo, SockAddr(SockAddrInet, 
SockAddrInet6), setSocketOption, SocketOption(..))
+import Network (Socket)
+import Network.Socket (close, accept, withSocketsDo, SockAddr(SockAddrInet, 
SockAddrInet6), setSocketOption, SocketOption(..))
 import qualified Network.Socket.ByteString as Sock
 import Network.Wai
 import Network.Wai.Handler.Warp.Buffer
@@ -35,6 +35,7 @@
 import qualified Network.Wai.Handler.Warp.FileInfoCache as I
 import Network.Wai.Handler.Warp.HTTP2 (http2, isHTTP2)
 import Network.Wai.Handler.Warp.Header
+import Network.Wai.Handler.Warp.IORef
 import Network.Wai.Handler.Warp.ReadInt
 import Network.Wai.Handler.Warp.Recv
 import Network.Wai.Handler.Warp.Request
@@ -63,7 +64,8 @@
         connSendMany = Sock.sendMany s
       , connSendAll = sendall
       , connSendFile = sendFile s writeBuf bufferSize sendall
-      , connClose = sClose s >> freeBuffer writeBuf
+      , connClose = close s
+      , connFree = freeBuffer writeBuf
       , connRecv = receive s bufferPool
       , connRecvBuf = receiveBuf s
       , connWriteBuffer = writeBuf
@@ -104,7 +106,7 @@
 runSettings set app = withSocketsDo $
     bracket
         (bindPortTCP (settingsPort set) (settingsHost set))
-        sClose
+        close
         (\socket -> do
             setSocketCloseOnExec socket
             runSettingsSocket set socket app)
@@ -137,7 +139,7 @@
         conn <- socketConnection s
         return (conn, sa)
 
-    closeListenSocket = sClose socket
+    closeListenSocket = close socket
 
 -- | The connection setup action would be expensive. A good example
 -- is initialization of TLS.
@@ -262,6 +264,10 @@
      -> InternalInfo0
      -> IO ()
 fork set mkConn addr app counter ii0 = settingsFork set $ \ unmask ->
+    -- Allocate a new IORef indicating whether the connection has been
+    -- closed, to avoid double-freeing a connection
+    withClosedRef $ \ref ->
+
     -- Run the connection maker to get a new connection, and ensure
     -- that the connection is closed. If the mkConn call throws an
     -- exception, we will leak the connection. If the mkConn call is
@@ -272,11 +278,14 @@
     -- We grab the connection before registering timeouts since the
     -- timeouts will be useless during connection creation, due to the
     -- fact that async exceptions are still masked.
-    bracket mkConn closeConn $ \(conn, transport) ->
+    bracket mkConn (\(conn, _) -> closeConn ref conn `finally` connFree conn)
+    $ \(conn, transport) ->
 
     -- We need to register a timeout handler for this thread, and
-    -- cancel that handler as soon as we exit.
-    bracket (T.registerKillThread (timeoutManager0 ii0)) T.cancel $ \th ->
+    -- cancel that handler as soon as we exit. We additionally close
+    -- the connection immediately in case the child thread catches the
+    -- async exception or performs some long-running cleanup action.
+    bracket (T.registerKillThread (timeoutManager0 ii0) (closeConn ref conn)) 
T.cancel $ \th ->
 
     let ii1 = toInternalInfo1 ii0 th
         -- We now have fully registered a connection close handler
@@ -294,7 +303,11 @@
        -- bracket with closeConn above ensures the connection is closed.
        when goingon $ serveConnection conn ii1 addr transport set app
   where
-    closeConn (conn, _transport) = connClose conn
+    withClosedRef inner = newIORef False >>= inner
+
+    closeConn ref conn = do
+        isClosed <- atomicModifyIORef' ref $ \x -> (True, x)
+        unless isClosed $ connClose conn
 
     onOpen adr    = increase counter >> settingsOnOpen  set adr
     onClose adr _ = decrease counter >> settingsOnClose set adr
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/Timeout.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/Timeout.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/Timeout.hs  2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/Timeout.hs 2017-02-02 
02:57:32.000000000 +0100
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 
 module Network.Wai.Handler.Warp.Timeout (
@@ -97,19 +98,24 @@
     return h
 
 -- | Registering a timeout action of killing this thread.
-registerKillThread :: Manager -> IO Handle
-registerKillThread m = do
+registerKillThread :: Manager -> TimeoutAction -> IO Handle
+registerKillThread m onTimeout = do
     -- If we hold ThreadId, the stack and data of the thread is leaked.
     -- If we hold Weak ThreadId, the stack is released. However, its
     -- data is still leaked probably because of a bug of GHC.
     -- So, let's just use ThreadId and release ThreadId by
     -- overriding the timeout action by "cancel".
     tid <- myThreadId
-    register m $ E.throwTo tid TimeoutThread
+    -- First run the timeout action in case the child thread is masked.
+    register m $ onTimeout `E.finally` E.throwTo tid TimeoutThread
 
 data TimeoutThread = TimeoutThread
     deriving Typeable
-instance E.Exception TimeoutThread
+instance E.Exception TimeoutThread where
+#if MIN_VERSION_base(4,7,0)
+    toException = E.asyncExceptionToException
+    fromException = E.asyncExceptionFromException
+#endif
 instance Show TimeoutThread where
     show TimeoutThread = "Thread killed by Warp's timeout reaper"
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp/Types.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp/Types.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp/Types.hs    2016-11-08 
04:53:07.000000000 +0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp/Types.hs   2017-02-02 
02:57:32.000000000 +0100
@@ -92,8 +92,13 @@
     , connSendAll     :: ByteString -> IO ()
     -- | The sending function for files in HTTP/1.1.
     , connSendFile    :: SendFile
-    -- | The connection closing function.
+    -- | The connection closing function. Warp guarantees it will only be
+    -- called once. Other functions (like 'connRecv') may be called after
+    -- 'connClose' is called.
     , connClose       :: IO ()
+    -- | Free any buffers allocated. Warp guarantees it will only be
+    -- called once, and no other functions will be called after it.
+    , connFree        :: IO ()
     -- | The connection receiving function. This returns "" for EOF.
     , connRecv        :: Recv
     -- | The connection receiving function. This tries to fill the buffer.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/Network/Wai/Handler/Warp.hs 
new/warp-3.2.11/Network/Wai/Handler/Warp.hs
--- old/warp-3.2.9/Network/Wai/Handler/Warp.hs  2016-11-08 04:53:07.000000000 
+0100
+++ new/warp-3.2.11/Network/Wai/Handler/Warp.hs 2017-02-02 02:57:32.000000000 
+0100
@@ -286,6 +286,16 @@
 -- handler. The handler should call the first argument,
 -- which closes the listen socket, at shutdown.
 --
+-- Example usage:
+--
+-- @
+-- settings :: IO () -> 'Settings'
+-- settings shutdownAction = 'setInstallShutdownHandler' shutdownHandler 
'defaultSettings'
+--   __where__
+--     shutdownHandler closeSocket =
+--       void $ 'System.Posix.Signals.installHandler' 
'System.Posix.Signals.sigTERM' ('System.Posix.Signals.Catch' $ shutdownAction 
>> closeSocket) 'Nothing'
+-- @
+--
 -- Default: does not install any code.
 --
 -- Since 3.0.1
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/warp-3.2.9/warp.cabal new/warp-3.2.11/warp.cabal
--- old/warp-3.2.9/warp.cabal   2016-11-08 04:53:07.000000000 +0100
+++ new/warp-3.2.11/warp.cabal  2017-02-02 02:57:32.000000000 +0100
@@ -1,5 +1,5 @@
 Name:                warp
-Version:             3.2.9
+Version:             3.2.11
 Synopsis:            A fast, light-weight web server for WAI applications.
 License:             MIT
 License-file:        LICENSE


Reply via email to