
#13043: GHC 7.10->8.0 regression: GHC code-generates duplicate _closures -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a minimized version with no dependencies: {{{#!hs {-# LANGUAGE BangPatterns #-} module Bug (foo, bar) where import Data.IORef (IORef, newIORef, readIORef, writeIORef) import System.IO.Unsafe (unsafePerformIO) {-# NOINLINE scServerState #-} scServerState :: SCServerState scServerState = unsafePerformIO (return undefined) data SCServerState = SCServerState { scServer_socket :: IORef (Maybe Int) } foo :: IO Int foo = do let !_ = scServerState readIORef (scServer_socket scServerState) >>= \xs -> case xs of Nothing -> do s <- undefined writeIORef (scServer_socket scServerState) (Just s) return s Just s -> return s bar :: IO () bar = do let !_ = scServerState return () }}} You can get this error message with GHC 8.0.1, 8.0.2, or HEAD: {{{ $ /opt/ghc/8.0.1/bin/ghc -fforce-recomp -O1 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) /tmp/ghc654_0/ghc_2.s: Assembler messages: /tmp/ghc654_0/ghc_2.s:562:0: error: Error: symbol `Bug_scServerState_closure' is already defined `gcc' failed in phase `Assembler'. (Exit code: 1) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13043#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler