[GHC] #5834: Allow both INLINE and INLINABLE for the same function

GHC ghc-devs at haskell.org
Wed Dec 30 13:23:39 UTC 2015


#5834: Allow both INLINE and INLINABLE for the same function
-------------------------------------+-------------------------------------
        Reporter:  rl                |                Owner:
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:  8.0.1
       Component:  Compiler          |              Version:  7.5
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by bgamari:

Old description:

> Sometimes you really want both. Here is a small example:
>
> {{{
> module T where
>
> foo :: Num a => a -> a -> a
> foo x y = x+y+1
> }}}
>
> {{{
> module U where
>
> import T
>
> appl :: (a -> b) -> a -> b
> {-# NOINLINE appl #-}
> appl f x = f x
>
> bar :: Int -> Int -> Int
> bar x y = appl foo x y
> }}}
>
> If I mark `foo` as `INLINE`, then GHC generates this code for `bar`:
>
> {{{
> bar1 :: Int -> Int -> Int
> bar1 = foo @ Int $fNumInt
>
> bar :: Int -> Int -> Int
> bar = \ (x_aa0 :: Int) (y_aa1 :: Int) -> appl @ Int @ (Int -> Int) bar1
> x_aa0 y_aa1
> }}}
>
> Whereas with `INLINABLE`, we get a nice specialisation but, of course,
> not guarantees with respect to inlining.
>
> In general, it seems that requiring a function to inline when it is
> saturated and requiring it two specialise when it isn't are two different
> things and shouldn't be mutually exclusive.

New description:

 Sometimes you really want both. Here is a small example:

 {{{#!hs
 module T where

 foo :: Num a => a -> a -> a
 foo x y = x+y+1
 }}}

 {{{#!hs
 module U where

 import T

 appl :: (a -> b) -> a -> b
 {-# NOINLINE appl #-}
 appl f x = f x

 bar :: Int -> Int -> Int
 bar x y = appl foo x y
 }}}

 If I mark `foo` as `INLINE`, then GHC generates this code for `bar`:

 {{{#!hs
 bar1 :: Int -> Int -> Int
 bar1 = foo @ Int $fNumInt

 bar :: Int -> Int -> Int
 bar = \ (x_aa0 :: Int) (y_aa1 :: Int) -> appl @ Int @ (Int -> Int) bar1
 x_aa0 y_aa1
 }}}

 Whereas with `INLINABLE`, we get a nice specialisation but, of course, not
 guarantees with respect to inlining.

 In general, it seems that requiring a function to inline when it is
 saturated and requiring it to specialise when it isn't are two different
 things and shouldn't be mutually exclusive.

--

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


More information about the ghc-tickets mailing list