[GHC] #7619: Make worker-wrapper unbox data families

#7619: Make worker-wrapper unbox data families -----------------------------+---------------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: type family Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- 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. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7619 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7619: Make worker-wrapper unbox data families ---------------------------------+------------------------------------------ Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: type family | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by simonpj): * difficulty: => Unknown Comment: Yes absolutely. The trick here is that * To get from `(Foo Int)` to the underlying data type involves generating a coercion. * So if `foo` wants to unbox its argument, the worker/wrapper code must include coercions. * Where do those coercions come from? You need the type-family instance environment, and even then it's a bit dodgy to be looking them up in the optimiser. * Or maybe we can gather them from the code itself during analysis, and keep them in the demand signature. Same thing happens in CPR I think -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7619#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7619: Make worker-wrapper unbox data families ---------------------------------+------------------------------------------ Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: type family | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by jwlato): * cc: jwlato@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7619#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7619: Make worker-wrapper unbox data families ---------------------------------+------------------------------------------ Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: type family | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by liyang): * cc: hackage.haskell.org@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7619#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7619: Make worker-wrapper unbox data families ---------------------------------+------------------------------------------ Reporter: akio | Owner: simonpj Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Keywords: type family | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by igloo): * owner: => simonpj * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7619#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC