#7270: Incorrect optimization with Data.ByteString.append ----------------------------------+----------------------------------------- Reporter: ocheron | Owner: duncan Type: bug | Status: new Priority: highest | Milestone: 7.6.2 Component: libraries (other) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: Incorrect result at runtime Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------+----------------------------------------- Changes (by igloo):
* owner: igloo => duncan * priority: normal => highest * milestone: => 7.6.2 Comment: Thanks for the report. This is due to bytestring's misuse of its `inlinePerformIO`; Duncan knows what to do. Here's a small standalone program demonstrating the problem: {{{ {-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-} module Main (main) where import GHC.Base import GHC.ForeignPtr import Foreign main :: IO () main = do let !r = make 68 !s = make 70 dump r dump s dump :: ForeignPtr Word8 -> IO () dump fp = do print fp withForeignPtr fp $ \p -> do x <- peek p print x make :: Word8 -> ForeignPtr Word8 make w = inlinePerformIO $ do fp <- mallocPlainForeignPtrBytes 1 withForeignPtr fp $ \p -> poke p w return fp inlinePerformIO :: IO a -> a inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r }}} {{{ $ ghc --make q -O $ ./q 0x00007f95b0706010 68 0x00007f95b0706010 68 }}} -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7270#comment:3> GHC <http://www.haskell.org/ghc/> The Glasgow Haskell Compiler _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs