[GHC] #7170: Foreign.Concurrent finalizer called twice in some cases

GHC ghc-devs at haskell.org
Sun Oct 19 16:45:09 UTC 2014


#7170: Foreign.Concurrent finalizer called twice in some cases
-------------------------------------+-------------------------------------
              Reporter:  joeyadams   |            Owner:
                  Type:  bug         |           Status:  new
              Priority:  high        |        Milestone:  7.6.1
             Component:              |          Version:  7.8.3
  libraries/base                     |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:  Runtime     |  Related Tickets:
  crash                              |
             Test Case:              |
  ffi/should_run/7170                |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Changes (by arybczak):

 * cc: hvr, ekmett (added)
 * owner:  simonmar =>
 * status:  closed => new
 * resolution:  fixed =>
 * version:  7.4.2 => 7.8.3


Comment:

 This is still happening, albeit is much harder to reproduce (I wasn't able
 to write simple testcase for that).

 Steps to reproduce (hopefully):
 1. git clone https://github.com/scrive/hpqtypes.git
 2. git checkout 8b4d57876dc573759c2935064306806b793844c5 (this is the last
 commit before the workaround I applied to solve the issue)
 3. git apply custom_finalizer.diff (to be sure it's haskell that tries to
 free the same memory twice)
 4. Change tests/Main.hs to the following code:
 {{{
 module Main where

 import Control.Applicative
 import Control.Concurrent
 import Control.Exception
 import Control.Monad
 import Debug.Trace
 import System.Environment
 import qualified Data.ByteString.Char8 as BS

 import Database.PostgreSQL.PQTypes

 mkConnSource :: String -> ConnectionSource
 mkConnSource ci = defaultSource $ defaultSettings {
     csConnInfo = BS.pack ci
   }

 main :: IO ()
 main = do
   cs <- mkConnSource . head <$> getArgs
   let dts = defaultTransactionSettings

   flip finally (runDBT cs dts $ return ()) $ do
     void . forkIO $ do
       forM_ [1..100000::Int] $ \n -> trace (show n) $ return ()
       return ()
     threadDelay 1000000
 }}}
 4. cabal sandbox init
 5. cabal install --dependencies-only
 6. cabal configure -ftests --ghc-options="-O0"
 7. cabal build
 8. cd dist/build/tests
 9. valgrind ./tests user=postgres

 The last step must be repeated a couple of times to get the error we are
 interested in. I attach the output of running it on my machine (valgrind-
 output.txt).

 If you look at the output file, at line 1112 I pressed Ctrl-C to interrupt
 the program, then the finalizer was called for the first time at line 1880
 and then for the second time at line 2255, which results in tons of output
 from valgrind about invalid reads of already freed memory.

 Relevant file:
 https://github.com/scrive/hpqtypes/blob/8b4d57876dc573759c2935064306806b793844c5/src/Database/PostgreSQL/PQTypes/Internal/Connection.hs

 runDBT calls withConnection of the defaultSource (line 89), which is a
 simple wrapper for {{{bracket connect disconnect}}}. In disconnect (line
 152) the destruction of the database connection is forced by calling
 finalizeForeignPtr. When finalizeForeignPtr is removed, the bug
 disappears.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/7170#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list