[GHC] #13016: SPECIALIZE INLINE doesn't necessarily inline specializations of a recursive function
GHC
ghc-devs at haskell.org
Wed Dec 21 00:52:01 UTC 2016
#13016: SPECIALIZE INLINE doesn't necessarily inline specializations of a recursive
function
-------------------------------------+-------------------------------------
Reporter: nfrisby | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime
Unknown/Multiple | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets: #13014
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
[https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html
#specialize-inline The user's guide] for `SPECIALIZE INLINE` states it
will do a "type-based unrolling" of a recursive function over GADTs. It
gives an example, which I've munged a bit to simplify and listed here.
{{{#!hs
{-# Language GADTs #-}
module C where
data Arr e where
ArrInt :: !Int -> Arr Int
ArrPair :: Arr e1 -> Arr e2 -> Arr (e1, e2)
(!:) :: Arr e -> Int -> e
{-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-}
{-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-}
(ArrInt ba) !: i = ba * i
(ArrPair a1 a2) !: i = (a1 !: i, a2 !: i)
}}}
{{{#!hs
module D where
import C
example = ArrPair (ArrInt 2) (ArrInt 3) !: 5
}}}
The specialize rule for pairs fires, but it does not get inlined. This is
because the specialization for pairs is marked as a loopbreaker.
This behavior contradicts the text from the users guide, emphasis mine:
Here, `(!:)` is a recursive function that indexes arrays of type `Arr
e`. Consider a call to `(!:)` at type `(Int,Int)`. The second
specialisation will fire, ''and the specialised function will be
inlined''. It has two calls to `(!:)`, both at type `Int`. Both these
calls fire the first specialisation, whose body is also inlined. The
result is a type-based unrolling of the indexing function.
If I move the `SPECIALIZE INLINE` pragma to the downstream module, then it
is not marked as a loopbreaker and we see the expected type-based
unrolling.
Two possible ways to resolve this ticket:
* `SPECIALIZE INLINE` should always achieve supercompilation even if
declared in the defining module; the specialization should not be marked
as a loopbreaker.
* The docs should be updated to say the pragma must be declared in a
separate module.
I suggest the former.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13016>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list