Make worker-wrapper unbox data families
I noticed that the worker-wrapper optimization doesn't unbox arguments whose type is a data family instance. For example in this module:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE BangPatterns #-}
module Foo where
data family Foo a
data instance Foo Int = FooInt Int Int
foo :: Foo Int -> Int
foo (FooInt a b) = loop a b
where
loop 0 y = length $ replicate y b
loop x !y = loop (mod y x) x
foo1 :: (Int, Int) -> Int
foo1 (a, b) = loop a b
where
loop 0 y = length $ replicate y b
loop x !y = loop (mod y x) x
foo and foo1 both get worker-wrapper applied, with worker functions of the following types:
$wfoo :: Foo Int -> Int#
$wfoo1 :: Int# -> Int# -> Int#
It would be nice if $wfoo could get the same type as $wfoo1.
This issue happened in real life with unboxed vectors from the vector package, resulting in a lot of boxing with unboxed vector constructors immediately followed by unboxing.
Trac metadata
Trac field | Value |
---|---|
Version | 7.7 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |