
#12622: Unboxed static pointers lead to missing SPT entries -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundominguez Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Here's a smaller test case: {{{ -- A.hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StaticPointers #-} module A where import Data.Typeable import GHC.StaticPtr g :: a -> Bool g _ = True data T a = T {-# UNPACK #-} !(StaticPtr a) sg :: Typeable a => T (a -> Bool) sg = T (static g) }}} {{{ -- Main.hs {-# LANGUAGE StaticPointers #-} {-# LANGUAGE LambdaCase #-} import GHC.StaticPtr import A g = True main :: IO () main = do let T s = sg :: T (Bool -> Bool) lookupKey s >>= \f -> print (f True) lookupKey :: StaticPtr a -> IO a lookupKey p = unsafeLookupStaticPtr (staticKey p) >>= \case Just p -> return $ deRefStaticPtr p Nothing -> error $ "couldn't find " ++ show (staticPtrInfo p) }}} Build with {{{ $ ghc -O Main.hs [1 of 2] Compiling A ( A.hs, A.o ) [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main Main: couldn't find StaticPtrInfo {spInfoUnitId = "main", spInfoModuleName = "A", spInfoSrcLoc = (14,16)} CallStack (from HasCallStack): error, called at Main.hs:17:14 in main:Main }}} Using `-dverbose-core2core` one can see that the FloatOut pass does the right thing (i.e. moving the static form to the top-level in Main.hs), {{{ lvl_sG5 :: forall a_aEy. StaticPtr (a_aEy -> Bool) lvl_sG5 = \ (@ a_aEy) -> GHC.StaticPtr.StaticPtr @ (a_aEy -> Bool) 13520098690657238824## 6110703080284699228## lvl_sG4 (g @ a_aEy) }}} but the simplifier later rewrites the top-level binding to use the T constructor instead: {{{ lvl_sG7 :: forall a_aEy. T (a_aEy -> Bool) lvl_sG7 = \ (@ a_aEy) -> A.T @ (a_aEy -> Bool) 13520098690657238824## 6110703080284699228## lvl_sGn (g @ a_aEy) }}} Thus, when the SPT is built, the StaticPtr constructor is not found and the entry is never inserted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler