
#12622: Unboxed static pointers lead to missing SPT entries -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundo.dominguez Type: bug | Status: patch 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): Phab:D2709 Wiki Page: | Phab:D2720 -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Hello, I have an implementation of this approach using `makeStatic`. It works most of the time, but I'm having some strange behavior when building with `--fno-full-laziness`. This is the test program: {{{ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE StaticPointers #-} -- | A test to use symbols produced by the static form. module Main(main) where import GHC.StaticPtr main :: IO () main = do lookupKey (static (id . id)) >>= \f -> print $ f (1 :: Int) lookupKey :: StaticPtr a -> IO a lookupKey p = unsafeLookupStaticPtr (staticKey p) >>= \case Just p -> return $ deRefStaticPtr p Nothing -> error $ "couldn't find " ++ show (staticPtrInfo p) }}} At some intermediate phase, core looks like this: {{{ -- RHS size: {terms: 3, types: 2, coercions: 0} lvl_s2fm :: StaticPtr (Int -> Int) [LclId, Str=x] lvl_s2fm = base-4.10.0.0:GHC.StaticPtr.Internal.makeStatic @ (Int -> Int) lvl_s2fk lvl_s2fl -- RHS size: {terms: 3, types: 3, coercions: 0} p_aEP [OS=OneShot] :: StaticPtr (Int -> Int) [LclId] p_aEP = fromStaticPtr @ StaticPtr GHC.StaticPtr.$fIsStaticStaticPtr @ (Int -> Int) lvl_s2fm -- RHS size: {terms: 2, types: 2, coercions: 0} main_s2eP :: StaticKey [LclId] main_s2eP = staticKey @ (Int -> Int) p_aEP -- RHS size: {terms: 2, types: 2, coercions: 0} main_s2eO :: IO (Maybe (StaticPtr (Int -> Int))) [LclId, Arity=1] main_s2eO = unsafeLookupStaticPtr @ (Int -> Int) main_s2eP ... }}} Before the call to `makeStatic` is replaced with an entry in the static pointer table, a simplifier pass labeled as {{{ ==================== Simplifier ==================== Max iterations = 4 SimplMode {Phase = 2 [main], inline, rules, eta-expand, case-of-case} Result size of Simplifier = {terms: 42, types: 55, coercions: 9} }}} transforms it to {{{ -- RHS size: {terms: 17, types: 13, coercions: 0} lvl_s2fm :: StaticPtr (Int -> Int) [LclId, Str=x, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=True, Guidance=NEVER}] lvl_s2fm = base-4.10.0.0:GHC.StaticPtr.Internal.makeStatic @ (Int -> Int) (GHC.StaticPtr.StaticPtrInfo (GHC.Base.build @ Char (\ (@ b_a2dI) -> GHC.CString.unpackFoldrCString# @ b "main"#)) (GHC.Base.build @ Char (\ (@ b_a2dI) -> GHC.CString.unpackFoldrCString# @ b "Main"#)) (GHC.Types.I# 13#, GHC.Types.I# 21#)) (\ (x_a2dj :: Int) -> x_a2dj) -- RHS size: {terms: 3, types: 5, coercions: 0} main_s32D :: GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) [LclId, Arity=1, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}] main_s32D = \ _ [Occ=Dead] -> case lvl_s2fm of wild_00 { } }}} which looks wrong, as the program becomes now a case with an empty list of alternatives. This is the definition of `makeStatic` {{{ module GHC.StaticPtr.Internal (makeStatic) where import GHC.StaticPtr {-# NOINLINE makeStatic #-} makeStatic :: StaticPtrInfo -> a -> StaticPtr a makeStatic (StaticPtrInfo pkg m (line, col)) _ = error $ "makeStatic: Unresolved static form at " ++ pkg ++ ":" ++ m ++ ":" ++ show line ++ ":" ++ show col }}} Perhaps the simplifier is somehow using the fact that `makeStatic` calls to error despite of the function being tagged with `NOINLINE`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler