[GHC] #9390: Inlining prevents evaluation of ignored parts of unboxed tuples

GHC ghc-devs at haskell.org
Fri Aug 1 04:57:44 UTC 2014


#9390: Inlining prevents evaluation of ignored parts of unboxed tuples
-------------------------------------+-------------------------------------
       Reporter:  snoyberg           |                   Owner:
           Type:  bug                |                  Status:  new
       Priority:  normal             |               Milestone:
      Component:  Compiler           |                 Version:  7.8.3
       Keywords:                     |        Operating System:  Linux
   Architecture:  x86_64 (amd64)     |         Type of failure:  Incorrect
     Difficulty:  Unknown            |  result at runtime
     Blocked By:                     |               Test Case:
Related Tickets:                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------
 Consider the following code:

 {{{#!hs
 {-# LANGUAGE MagicHash, UnboxedTuples #-}
 import GHC.IO (IO (..))
 import GHC.Prim

 writeB :: MutableArray# RealWorld Char -> IO ()
 writeB arr# =
     IO $ \s0# ->
         (# writeArray# arr# 0# 'B' s0#, () #)

 inlineWriteB :: MutableArray# RealWorld Char -> ()
 inlineWriteB arr# =
     case f realWorld# of
         (# _, x #) -> x
   where
     IO f = writeB arr#

 test :: IO Char
 test = IO $ \s0# ->
   case newArray# 1# 'A' s0# of
     (# s1#, arr# #) ->
       case seq# (inlineWriteB arr#) s1# of
         (# s2#, () #) ->
           readArray# arr# 0# s2#

 main :: IO ()
 main = test >>= print
 }}}

 I would expect this code to output the letter 'B'. When compiled without
 optimizations, that's exactly what it does. However, with optimizations
 turned on, it seems that it decides that, in `inlineWriteB`, the state
 value does not need to be evaluated, which results in the `writeArray#`
 call never occurring.

 This affected me when working with the vector and primitive packages. I
 believe I have a workaround in place (see
 https://github.com/haskell/primitive/pull/11), but this should probably be
 fixed in GHC as well.

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


More information about the ghc-tickets mailing list