[GHC] #14931: Segfault compiling file that uses Template Haskell with -prof (was: Segfault compiling files with -prof)
GHC
ghc-devs at haskell.org
Fri Mar 16 13:34:46 UTC 2018
#14931: Segfault compiling file that uses Template Haskell with -prof
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Profiling | Version: 8.4.1
Resolution: | 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: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I forgot that `mtl` is bundled with GHC now, so you can reproduce this
with a single file:
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Prelude (Int, IO, Bool(..), Num(..), Monad(..), not, print)
import qualified Language.Haskell.TH.Syntax as TH
import Control.Monad.State
wat :: IO ()
wat = print $(let playGame [] = do
(_, score) <- get
return score
playGame (x:xs) = do
(on, score) <- get
case x of
'a' | on -> put (on, score + 1)
'b' | on -> put (on, score - 1)
'c' -> put (not on, score)
_ -> put (on, score)
playGame xs
startState :: (Bool, Int)
startState = (False, 0)
in TH.lift (evalState (playGame "abcaaacbbcabbab")
startState) )
}}}
{{{
$ ~/Software/ghc-8.4.1/bin/ghc -O -prof -osuf p_o -hisuf p_hi Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.p_o )
Segmentation fault (core dumped)
}}}
Also, Template Haskell appears to be a key ingredient here, since removing
it makes the issue go away.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14931#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list