[GHC] #15802: Inlining of constant fails when both cross-module and recursive

GHC ghc-devs at haskell.org
Thu Oct 25 00:01:08 UTC 2018


#15802: Inlining of constant fails when both cross-module and recursive
-------------------------------------+-------------------------------------
           Reporter:  j6carey        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.1
           Keywords:                 |  Operating System:  Linux
       Architecture:  x86_64         |   Type of failure:  Runtime
  (amd64)                            |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When an inline recursive function is applied to a constant, that
 application may reduce if it is in the same module, but will not reduce
 when in a different module.  (Naturally, this harms the ability to split a
 program into modules while retaining efficiency.)

 For example, consider the following files:

 T1.hs:
 {{{#!hs
 module T1 where

 data IntList = Nil | Cons Int IntList

 mapIntList :: (Int -> Int) -> IntList -> IntList
 mapIntList f Nil = Nil
 mapIntList f (Cons x xs) = Cons (f x) (mapIntList f xs)
 {-# INLINE mapIntList #-}

 mappedNil :: IntList
 mappedNil = mapIntList id Nil
 }}}

 T2.hs:
 {{{#!hs
 module T2 where

 data IntList = Nil | Cons Int IntList

 mapIntList :: (Int -> Int) -> IntList -> IntList
 mapIntList f Nil = Nil
 mapIntList f (Cons x xs) = Cons (f x) (mapIntList f xs)
 {-# INLINE mapIntList #-}
 }}}

 T3.hs:
 {{{#!hs
 module T3 where

 import T2

 mappedNil :: IntList
 mappedNil = mapIntList id Nil
 }}}

 The program built from T1.hs should be equivalent to the one built from
 T2.hs and T3.hs; however, the core output from GHC 8.6.1 with -O2 differs
 significantly.

 In the single-module case we obtain:

 {{{#!hs
 mappedNil = T1.Nil
 }}}

 Whereas in the two-module case we see:

 {{{#!hs
 mappedNil = mapIntList (id @ Int) T2.Nil
 }}}

 Recursion is relevant; the problem disappears if we make this change:
 {{{#!hs
 data IntList = Nil | Cons Int Int

 mapIntList :: (Int -> Int) -> IntList -> IntList
 mapIntList f Nil = Nil
 mapIntList f (Cons x xs) = Cons (f x) (f xs)
 {-# INLINE mapIntList #-}
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15802>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list