[GHC] #15143: Passing an IO value through several functions results in program hanging.
GHC
ghc-devs at haskell.org
Thu May 17 12:28:11 UTC 2018
#15143: Passing an IO value through several functions results in program hanging.
-------------------------------------+-------------------------------------
Reporter: Burtannia | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by danilo2):
Hi! I think I might get similar problem. However, no minimal example here
(unless you will need some). The code is pretty simple, I'm building a
"fold-like" function with type classes:
{{{
class Monad m => FoldableLayer t m layer where
buildLayerFold :: ∀ layout. Layer.Cons layer layout -> m (Result t) ->
m (Result t)
class Monad m => LayerFoldableBuilder__ (active :: Bool) t m layer where
buildLayerFold__ :: SomePtr -> m (Result t) -> m (Result t)
instance {-# OVERLAPPABLE #-} Monad m
=> LayerFoldableBuilder__ 'False t m layer where
buildLayerFold__ = \(!_) (!a) -> !a ; {-# INLINE buildLayerFold__ #-}
instance (Monad m, Layer.StorableLayer layer m, FoldableLayer t m layer)
=> LayerFoldableBuilder__ 'True t m layer where
buildLayerFold__ = \(!ptr) (!mr) -> do
!layer <- Layer.unsafePeekWrapped @layer ptr
!r <- mr -- | Performance
buildLayerFold @t @m @layer layer $! pure r
{-# INLINE buildLayerFold__ #-}
}}}
The problem is that if I change the last two lines to
{{{
buildLayerFold @t @m @layer layer mr -- mr instead of pure r
}}}
The performance is 2 times slower while evaluating it. The `m` is a
`State` over `IO`. Basically I am building here an action and this code
change should not affect anything - because this action is just a function
composition and will be evaluated eventually. I was initially thinking
this might be related to strictness on the result, but that is apparently
not the case. Even if I change the code to:
{{{
!_ <- mr
buildLayerFold @t @m @layer layer mr
}}}
I get the same slow results (2 times slower than the fast version). I
don't see any reason why would it happen and this bug could be related.
Thanks @iamrecursion for showing it to me!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15143#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list