#5834: Allow both INLINE and INLINABLE for the same function
------------------------------+---------------------------------------------
 Reporter:  rl                |          Owner:                  
     Type:  feature request   |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.5               |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown      |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 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.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to