[GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors
GHC
ghc-devs at haskell.org
Sat May 7 06:15:15 UTC 2016
#12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit)
definitions as errors
-------------------------------------+-------------------------------------
Reporter: carter | Owner:
Type: bug | Status: closed
Priority: high | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: invalid | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by bgamari):
* status: new => closed
* resolution: => invalid
Comment:
Right, because, just as the error says, that INLINE doesn't correspond to
any particular in-scope binding. However, you should not need an INLINE
here; instead just place one on the default definition. You can test this
yourself with the following,
{{{#!hs
module Class where
class AClass a where
aList :: a -> [Int]
aList _ = [1,2,3]
{-# INLINE aList #-}
}}}
{{{#!hs
module Instance where
import Class
instance AClass Int where
}}}
{{{#!hs
module Use where
import Class
import Instance
n :: Int
n = 42
main :: IO ()
main = print (aList n)
}}}
If you build `Use` with `-O -ddump-simpl` you will see that the RHS of
`aList` has been inlined.
I suspect the real bug here is the fact that this wasn't warned about
previously. I'll try to draw attention to this change in the release
notes.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12027#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list