[GHC] #12875: GHC fails to link all StaticPointers-defining modules of a library in an executable

GHC ghc-devs at haskell.org
Wed Nov 23 23:28:36 UTC 2016


#12875: GHC fails to link all StaticPointers-defining modules of a library in an
executable
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.2.1
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
  StaticPointers                     |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Consider that you have a package called `lib` which exposes these modules,
 {{{#!hs
 module ALib.Types where

 data AThing = AThing String
             deriving (Show)

 {-# LANGUAGE StaticPointers #-}
 module ALib.Things where

 import GHC.StaticPtr
 import ALib.Types

 thing1 :: StaticPtr AThing
 thing1 = static (AThing "hello")
 }}}


 Now consider that you have a server which reads a `StaticKey` of
 `StaticPtr AThing` and shows it,
 {{{#!hs
 import ALib.Types

 main :: IO ()
 main = do
     key <- readFingerprint <$> getContents :: IO StaticKey
     Just thing <- unsafeLookupStaticPtr key :: IO (Maybe (StaticPtr
 AThing))
     print $ deRefStaticPtr thing
 }}}

 Naturally this executable will link against `lib`. However, this
 executable as-written will fail if given the key of `ALib.Things.thing1`.
 Fixing this requires that the executable explicitly import and use a
 definition from `ALib.Things`.

 The problem appears to be that the linker elides the `ALib.Things` object
 from the final executable unless it refers to a symbol. Note that things
 also work fine if the server executable is dynamically linked.

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


More information about the ghc-tickets mailing list