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

GHC ghc-devs at haskell.org
Thu Jun 4 09:26:38 UTC 2015


#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


More information about the ghc-tickets mailing list