[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 02:52:16 UTC 2016
#12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit)
definitions as errors
-------------------------------------+-------------------------------------
Reporter: carter | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.0.1
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:
-------------------------------------+-------------------------------------
I was getting around to testing some of my maths code with ghc 8.0 and i
noticed that whereas in ghc 7.10 and earlier i could have an INLINE pragma
for a method of a type class method that has a default implementation
(whether this did anything or not is another question), in ghc 8.0 this
now gives an ERROR (with not even a warning in ghc 7.10)
is this a deliberate design change or an accident? I dont see it in the
release notes!
heres a small program that illustrates the differences (builds fine with
no mention of the INLINE pragma matter under -Wall for 7.10, errors during
build in 8.0)
{{{
{-# LANGUAGE NoImplicitPrelude #-}
module Main where
import Prelude (putStrLn)
import qualified Data.Functor as Fun
import qualified Data.Foldable as F
import Prelude hiding
(map,foldl,foldr,init,scanl,scanr,scanl1,scanr1,foldl1,foldr1)
newtype ListWrap a = ListWrap { unListWrap :: [a] } deriving (Eq, Show)
instance Foldable ListWrap where
{-# INLINE foldMap #-}
{-# INLINE foldr #-}
foldMap f (ListWrap ls)= (F.foldMap f ls )
main = putStrLn "hello"
}}}
this may be a *valid* design change, but i've not seen it documented
anywhere, such as the release notes in the RC or in
https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0 ... so i'm assuming
its a regression pending dicussion ;)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12027>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list