[GHC] #11312: GHC inlining primitive string literals can affect program output

GHC ghc-devs at haskell.org
Tue Dec 29 04:33:02 UTC 2015


#11312: GHC inlining primitive string literals can affect program output
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #11292
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 First noted in #11292, this program, when compiled with `-O1` or higher:

 {{{#!hs
 {-# LANGUAGE MagicHash #-}
 module Main (main) where

 import GHC.Exts (Addr#, isTrue#)
 import GHC.Prim (eqAddr#)

 data A = A { runA :: Addr# }

 a :: A
 a = A "a"#

 main :: IO ()
 main = print (isTrue# (eqAddr# (runA a) (runA a)))
 }}}

 will result in the following after inlining:

 {{{
 Main.main2 =
   case GHC.Prim.tagToEnum#
          @ GHC.Types.Bool (GHC.Prim.eqAddr# "a"# "a"#)
   of _ [Occ=Dead] {
     GHC.Types.False -> GHC.Show.shows26;
     GHC.Types.True -> GHC.Show.shows24
   }
 }}}

 As a result, there are two of the same string constant with different
 addresses, which causes `eqAddr#` to return `False`. If compiled without
 optimizations, `"a"#` is not inlined, and as a result, `eqAddr#` returns
 `True`.

 Two questions:

 1. Is this okay semantics-wise? Or is this a necessary risk when working
 with primitive string literals, and should programmers judiciously use
 `{-# NOINLINE #-}` with them?
 2. Is this okay from a code duplication standpoint? As Reid Barton noted
 in #11292, `"a"#` is duplicated due to inlining. In this example, not much
 is duplicated, but if it were a longer string constant, that could result
 in a noticeable increase in the object file size.

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


More information about the ghc-tickets mailing list