
#5916: runST isn't free -------------------------------------+------------------------------------ Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.6.2 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): Using {{{#!haskell {-# INLINE runSTRep #-} runSTRep :: (forall s. STRep s a) -> a runSTRep st_rep = case st_rep (stWorld# st_rep) of (# _, r #) -> r {-# NOINLINE stWorld# #-} stWorld# :: a -> State# RealWorld stWorld# _ = realWorld# }}} it validates. But do we actually have a test for this? Here would be one: {{{#!haskell import Control.Monad.ST import Data.STRef main = let f n = runST $ do ref <- newSTRef 0 modifySTRef ref (+n) readSTRef ref in print (f 1 + f 2) }}} returns 3 in master, returns 4 if I inline `runSTRep`, and returns 3 with the `stWorld#`-trick. So unless someone says that this is not worth it (which would be strange, given that this bug is about an unexpected real-world performance issue), I suggest to give `runSTRep` a custom unfolding in `MkId` that replaces `runSTRep e` by `case e (stWorld# $(all free local variables of e)) of (# _, r #) -> r`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/5916#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler