[GHC] #10482: Not enough unboxing happens on data-family function argument

#10482: Not enough unboxing happens on data-family function argument -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In the following code, `foo` and `foo'` have isomorphic types, but the worker-wrapper pass does less unboxing for `foo`: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE TypeFamilies #-} module Foo where data family Foo a data instance Foo (a, b) = FooPair !(Foo a) !(Foo b) newtype instance Foo Int = Foo Int foo :: Foo ((Int, Int), Int) -> Int -> Int foo !f k = if k == 0 then 0 else if even k then foo f (k-1) else case f of FooPair (FooPair (Foo n) _) _ -> n data Foo0 a b c = Foo0 !(Foo1 a b) !c data Foo1 a b = Foo1 !a !b foo' :: Foo0 Int Int Int -> Int -> Int foo' !f k = if k == 0 then 0 else if even k then foo' f (k-1) else case f of Foo0 (Foo1 n _) _ -> n }}} The core generated by `ghc -ddump-simpl -O2 ww.hs` contains the following functions: {{{ Foo.foo_$s$wfoo [Occ=LoopBreaker] :: Foo Int -> Foo Int -> Foo.R:Foo(,) Int Int ~R# Foo (Int, Int) -> Foo Int -> GHC.Prim.Int# -> Int Foo.$wfoo [InlPrag=[0]] :: Foo (Int, Int) -> Foo Int -> GHC.Prim.Int# -> Int Foo.$wfoo' [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> Int -> Int -> GHC.Prim.Int# -> Int }}} The first argument of `Foo.foo_$s$wfoo` could be `Int#`, but it takes a boxed value. In practice this happens with unboxed vectors from the `vector` package. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10482 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10482: Not enough unboxing happens on data-family function argument -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by maoe): * cc: maoe@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10482#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10482: Not enough unboxing happens on data-family function argument
-------------------------------------+-------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10482: Not enough unboxing happens on data-family function argument
-------------------------------------+-------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10482: Not enough unboxing happens on data-family function argument -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The patch in comment:2 fixes the original bug report but gives perf failures on {{{
haddock.Cabal haddock.compiler
}}} Joachim says: I can confirm this, if you look at https://perf.haskell.org/ghc/ you see that that commit is the only in red Here is the report for that commit: https://perf.haskell.org/ghc/#revision/0b7e538a09bc958474ec704063eaa08836e92... and you can fetch the numbers from there, or from the full build log at https://raw.githubusercontent.com/nomeata/ghc-speed- logs/master/0b7e538a09bc958474ec704063eaa08836e9270e.log It looks very reproducible as well: https://perf.haskell.org/ghc/#graph/tests/alloc/haddock.Cabal;hl=0b7e538a09b... So we have to discover why this is happening. Sigh. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10482#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10482: Not enough unboxing happens on data-family function argument
-------------------------------------+-------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10482: Not enough unboxing happens on data-family function argument -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, I want this ticket to stay open because it seems likely that the main commit caused the around 7% regression in allocation numbers for these two Haddock tests. I found that surprising and want to investigate. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10482#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC