[GHC] #15970: Recompilation bug with default class methods
GHC
ghc-devs at haskell.org
Thu Nov 29 12:08:48 UTC 2018
#15970: Recompilation bug with default class methods
-------------------------------------+-------------------------------------
Reporter: simonmar | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.6.3
Component: Compiler | Version: 8.6.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Repro as follows.
A.hs:
{{{
{-# OPTIONS_GHC -fno-full-laziness #-}
module A (toTypedData, toTypedDataNoDef) where
toTypedData :: String -> IO Int
toTypedData s = wrapPrint "yoyo" $ toTypedDataNoDef s
wrapPrint :: String -> IO Int -> IO Int
wrapPrint s act = do
putStrLn s
act
toTypedDataNoDef :: String -> IO Int
toTypedDataNoDef s = return $ length s
}}}
B.hs:
{{{
module B ( TypeClass(..) ) where
import A
class Show a => TypeClass a where
getSize :: a -> IO Int
getSize a = toTypedData (show a)
printA :: a -> IO ()
}}}
C.hs:
{{{
module Main where
import B
data MyDataType = MyDataType String Int deriving Show
instance TypeClass MyDataType where
printA = putStrLn . show
main :: IO ()
main = do
let myValue = MyDataType "haha" 99
sz <- getSize myValue
putStrLn $ show sz
printA myValue
}}}
1. Comment out the `-fno-full-laziness` option in A.hs
2. `rm *.o *.hi; ghc -O2 C.hs`
3. Re-enable the `-fno-full-laziness` option in A.hs
4. `ghc -O2 C.hs`
Produces a linker error:
{{{
C.o:Main_main1_info: error: undefined reference to
'A_toTypedData2_closure'
C.o(.data.rel.ro+0x48): error: undefined reference to
'A_toTypedData2_closure'
collect2: error: ld returned 1 exit status
}}}
Reproduced in 8.0, 8.4 and master. Probably happens in all released
versions of GHC.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15970>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list