
#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