[GHC] #12622: Unboxed static pointers lead to missing SPT entries

#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 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I found what appears to be a regression following the merge of the new FloatOut based static pointers support. See github.com/mboes/bug-ptr-not- in-spt for a fully developed minimal example. It seems to be quite hard to trigger this bug: * I need to be using distributed-closure (not bare `StaticPtr`). * The static pointer needs to be defined in a separate module. * The static pointer must refer to a value with at least one polymorphic argument. * Compiler optimization level 1 needs to be turned on. At any rate, I wasn't able to trigger it without all conditions above being true. Initial investigations by facundominguez point to static pointer unpacking in distributed-closure as the culprit. Likely unpacked static pointers are no longer recognized as such by the FloatOut pass and therefore never floated to top-level, hence breaking a fundamental invariant about static pointers. This might explain why sometimes static pointers don't get added to the static pointer table (SPT), as in the above minimal example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Description changed by mboes: @@ -2,2 +2,2 @@ - FloatOut based static pointers support. See github.com/mboes/bug-ptr-not- - in-spt for a fully developed minimal example. + FloatOut based static pointers support. See https://github.com/mboes/bug- + ptr-not-in-spt for a fully developed minimal example. New description: I found what appears to be a regression following the merge of the new FloatOut based static pointers support. See https://github.com/mboes/bug- ptr-not-in-spt for a fully developed minimal example. It seems to be quite hard to trigger this bug: * I need to be using distributed-closure (not bare `StaticPtr`). * The static pointer needs to be defined in a separate module. * The static pointer must refer to a value with at least one polymorphic argument. * Compiler optimization level 1 needs to be turned on. At any rate, I wasn't able to trigger it without all conditions above being true. Initial investigations by facundominguez point to static pointer unpacking in distributed-closure as the culprit. Likely unpacked static pointers are no longer recognized as such by the FloatOut pass and therefore never floated to top-level, hence breaking a fundamental invariant about static pointers. This might explain why sometimes static pointers don't get added to the static pointer table (SPT), as in the above minimal example. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#12622: Unboxed static pointers lead to missing SPT entries -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundo.dominguez 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: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * owner: facundominguez => facundo.dominguez * cc: facundominguez (removed) * cc: facundo.dominguez, simonpj (added) Comment: One simple solution could be to redefine `StaticPtr` to something like {{{ data StaticPtr a = StaticPtr {-# NOUNPACK #-} !(StaticPtr' a) data StaticPtr' a = StaticPtr' Word# Word# StaticPtrInfo a }}} This would yield the `StaticPtr` data constructor from being eliminated due to unboxing. Another solution would be to tell the compiler never to unbox a field of type `StaticPtr`. Not sure how easy this would be. simonpj? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: new => patch * differential: => Phab:D2709 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Preventing StaticPtrs from being unpacked is not necessary. Turns out that there is a bug in the code that floats out static pointers. The identifier of the following binding is not exported and it should. {{{ 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) }}} Having the id as exported, prevents the simplifier from removing it, which is what we want. However, our minimal example still fails linting. The problem is this line in `Main.hs`: {{{ let T s = sg :: T (Bool -> Bool) }}} Which gets translated to {{{ s :: StaticPtr (Bool -> Bool) s = case sg of T dt_d2bM dt_d2bN dt_d2bO dt_d2bP -> GHC.StaticPtr.StaticPtr dt_d2bM dt_d2bN dt_d2bO dt_d2bP }}} which the linter rejects because it contains an occurrence of the StaticPtr data constructor which cannot be floated. Note that this occurrence is harmless, since it is not created by a `static` form and does not correspond to an entry in the Static Pointer Table. Nonetheless, the linter is confused, and I don't know yet how to help it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: |
-------------------------------------+-------------------------------------
Comment (by facundo.dominguez):
Fixed the id of the floated binding in master
{{{
commit 31d5b6efa24985d0a8be5354e6a9a38e016db0ff
Author: Facundo Domínguez

#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 -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * differential: Phab:D2709 => Phab:D2709 Phab:D2720 Comment: Found a fix for the linter. It introduces a twin data constructor StaticPtrInternal which is used exclusively when desugaring the static form. This avoids confusion when unpacking inserts occurrences of the StaticPtr constructor in the code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Facundo, your work has exposed some woolly thinking on my part, and I think we need to take a step back to revisit some of our earlier design decisions. I fear that we are now piling hack upon hack and accumulating technical debt that we will later regret. In particular, the desire to accomodate references to local closed defintitions (seee Trac #11656) has led to a raft of unexpected complexity: * We need the `tcg_static_wc` stuff anyway. * The `FloatOut` pass needs special extra stuff, and must always be run. * Similary the SPT construction needs to find all those top-level `StaticPtr` applications. * Now we discover that sometimes nested `StaticPtr` is fine, which leads to further complexity in your patch. All this sounds fragile. We see all the uses of `static` so it seems odd to have to rediscover them when we are constructing the SPT. How important is #11656, really? After all, you can always write those local closed defns at top level! If we recanted on that we could: * Do all the floating work in the type checker (we are doing it alrady with `tcg_static_wc`, prettty much) * And then we'd be done! This seems attractive to me. When in a hole, stop digging! There's always a tradeoff between compiler complexity and language expressiveness. Yes we ''can'' do everything. But life is short, and if we spend time doing X it means we don't have time to Y. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Simon, #11656 is needed for programming in the large, similarly to how local definitions avoid polluting the top-level namespace of a module with many functions that relate to its very internals, which would make it harder to maintain it. Of the points you raise, the first three are what we designed it to be from the start. But I agree that the mechanism for the linter to discern static forms is more involved than expected. We might review this mechanism, but I feel it would be excessive to disregard support for local definitions because of linting. As an example of how the namespace pollution prevented using static pointers, I offer a use case where StaticPtrs were used to persist and share the states of a state machine. If static forms did not support local definitions, then a module with many state machines with many states and events each would have to bear a lot of "internal" top-level functions. {{{ -- | This module defines state machines whose state can be serialized -- and execution can be resumed later. It uses the package distributed- closure -- to create the closures. {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE StaticPointers #-} {-# LANGUAGE TypeSynonymInstances #-} module Main where import Control.Distributed.Closure import Control.Monad import GHC.StaticPtr -- | A state can be final, in which case it yields a result, or it provides -- a computation which yields the next state. -- -- The Closure type is used to keep track of the current state, and it -- can be persisted or sent to other nodes for subsequent execution. -- -- In this implementation machines have a single push-button. Transitions are -- done at the user request. It would be possible to extend it to react to -- other events. newtype MState m a = MState (Closure (m (NextState m a))) type NextState m a = Either (MState m a) a -- | @anbncn@ is a state machine which recognizes words in the set -- @{ a^n b^n c^n | n <- [1..] }@. -- -- It yields the amount of repetitions @n@ found in the input. anbncn :: MState IO Int anbncn = MState $ mkClosure (static as) 0 where as :: Int -> IO (NextState IO Int) as an = do x <- getChar return $ case x of 'a' -> Left $ MState $ mkClosure (static as) (an + 1) 'b' | an > 0 -> Left $ MState $ mkClosure (static bs) (an, 1) _ -> Right 0 bs :: (Int, Int) -> IO (NextState IO Int) bs (an, bn) = do x <- getChar return $ case x of 'b' -> Left $ MState $ mkClosure (static bs) (an, bn + 1) 'c' | an == bn -> Left $ MState $ mkClosure (static cs) (an, 1) _ -> Right 0 cs :: (Int, Int) -> IO (NextState IO Int) cs (an, cn) = do x <- getChar return $ case x of 'c' | an == cn + 1 -> Right $ cn + 1 | otherwise -> Left $ MState $ mkClosure (static cs) (an, cn + 1) _ | an == cn -> Right cn | otherwise -> Right 0 -- Make one transition. pushButton :: MState m a -> m (NextState m a) pushButton (MState c) = unclosure c -- Make all transitions of the state machine. runStateMachine :: Monad m => MState m a -> m a runStateMachine = pushButton >=> either runStateMachine return main :: IO () main = do putStrLn "start typing a, b or c" n <- runStateMachine anbncn putStrLn $ "The amount of repetitions is " ++ show n -- | Produces a closure from a static pointer and a serializable value. mkClosure :: Static (Serializable a) => StaticPtr (a -> b) -> a -> Closure b mkClosure sp a = closure sp `cap` cpure closureDict a instance Static (Serializable Int) where closureDict = closure $ static Dict instance Static (Serializable (Int, Int)) where closureDict = closure $ static Dict }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Well, maybe. There is a complexity-budget cost that I remain anxious about. If you want to pursue the current line, let's not introduce a "twin" data constructor. Rather, how about this: * Make `(static e)` expand into the ordinary function call `makeStatic e` * Make the float-out pass spot those calls (instead of spotting the `StaticPtr` data constructor) and float them to the top. * Make the SPT construction spot those calls, gather them into a table, generate a GUID or whatever for each, and allocate a `StaticPtr` data consructor for each. That way all the magic of building `StaticPtr` constructors is in one place. Would that work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I infer that: * `makeStatic` should never be unfolded, * FloatOut needs to treat it specially when **deciding what to float** (unlike it does now with `StaticPtr`) * Besides keeping the floated bindings, the optimizations should never inline them, or the SPT construction pass wouldn't replace the inlined calls to `makeStatic`. * the SPT construction needs to do more work (which is replacing this call with a StaticPtr). It is probably doable, but how is it simpler than using the twin data constructor? Something that could be simpler is to stop relaying on the FloatOut pass. Instead: 1. As you suggest: Make `static e` expand into the ordinary function call `makeStatic e` 2. Make the SPT construction phase float all such calls and insert them in the SPT. Thus there is no need to worry about unfloated calls during linting and there will be no interference from optimizations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): I'm a bit lost reading comment:11. What is step (2)? Lots of stuff is crossed out. Yes `makeStatic` should not be unfolded. I'm not sure why `FloatOut` would need to treat `makeStatic` any more specially than it did `StaticPtr`. Yes, the top level binding `x = makeStatic y` should not be inlined; but I think that'll be the case anyway. Yes, some stuff (making a fingerprint, and `StaticPtr` value) is moved from the desugarer to the SPT construction -- that's a feature! It looks good to me. If you think another approach is better, by all means describe it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I've edited the comment to make it clear, I hope. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Yes, I think that a special-purpose float pass would also be OK, and I do agree that it'd be nicer to localise the magic. I bet that almost always the ordinary float-out stuff would move `(makeStatic e)` to top level anyway (if not, it would be good to explain why not) but not having that as a guaranteed invariant would be nicer. But before going there, let's just check that what we have is not almost OK anyway: * You say that `FloatOut` would have go treat `makeStatic` specially, when not currently treat `StaticPtr` specially. Why? * I'm betting that if we had a top-level binding `x = makeStatic e` then it would never get inlined anyway. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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):
I'm betting that if we had a top-level binding x = makeStatic e then it would never get inlined anyway.
Indeed, I would hope GHC has no incentive to inline it.
You say that FloatOut would have go treat makeStatic specially, when not currently treat StaticPtr specially. Why?
The SetLevels pass checks if a soon-to-be new top-level binding is a static pointer to determine what kind of Id to produce for the new binding (bindings of StaticPtrs need to be of //exported// kind). But so far the SetLevels pass decides on its own that the static pointer needs to be floated, because, I presume, most or all data constructor applications are treated like that. If we want SetLevels to float `makeStatic e`, we probably will have to modify the decision procedure to treat `makeStatic e` unlike other function applications and always float it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Interesting. In fact this "make it an exported Id" stuff can now be done later. The Grand Plan comment in `SimplCore` says {{{ The FloatOut pass is careful to produce an /exported/ Id for a floated 'StaticPtr', so the binding is not removed by the simplifier (see #12207). E.g. the code for `f` above might look like static_ptr = StaticPtr <fingerprint> k f x = ...(staticKey static_ptr)... which might correctly be simplified to f x = ...<fingerprint>... BUT the top-level binding for static_ptr must remain, so that it can be collected to populate the Static Pointer Table. }}} But if we generate `sp = makeStatic e)` not `sp = StaticPtr blah blah`, then `(staticKey sp)` won't simplify, but will still use `sp`. So no need for special treatment. Hooray. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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): I figured this one. GHC propagates strictness information from 'error' to 'makeStatic', and then from 'makeStatic' to the floated top-level binding which uses it. The only effective way I found to turned it off is to use {{{ {-# OPTIONS_GHC -fignore-interface-pragmas #-} }}} at the top of {{{GHC/StaticPtr/Internal.hs}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Phab:D2930 -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * differential: Phab:D2709 Phab:D2720 => Phab:D2709 Phab:D2720 Phab:D2930 Comment: I just submitted the implementation to phabricator. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Phab:D2930
-------------------------------------+-------------------------------------
Comment (by Facundo Domínguez

#12622: Unboxed static pointers lead to missing SPT entries -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundo.dominguez Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | 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 Phab:D2930 -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12622#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC