[GHC] #14115: GHC segfaults trying to use TH code when ghc is compiled as DYNAMIC_GHC_PROGRAMS=NO
GHC
ghc-devs at haskell.org
Tue Aug 15 09:48:48 UTC 2017
#14115: GHC segfaults trying to use TH code when ghc is compiled as
DYNAMIC_GHC_PROGRAMS=NO
-------------------------------------+-------------------------------------
Reporter: pacak | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
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:
-------------------------------------+-------------------------------------
When ghc 8.2.1 compiled using DYNAMIC_GHC_PROGRAMS=NO attemps at using TH
results in all sorts
of exciting errors:
source files:
{{{
% cat A.hs
{-# LANGUAGE TemplateHaskell #-}
module Numeric.Sum where
import B
b
}}}
this file makes little sense, but it was segfaulting when it had more code
as well
{{{
% cat B.hs
{-# LANGUAGE TemplateHaskellQuotes #-}
module B where
import Language.Haskell.TH
b :: DecsQ
b = return [ InstanceD Nothing [] (ConT ''Show `AppT` undefined) [] ]
}}}
Let's try running it a few times - note illegal hardware instruction
{{{
% ghc -O2 A.hs
[1 of 2] Compiling B ( B.hs, B.o )
[2 of 2] Compiling Numeric.Sum ( A.hs, A.o )
zsh: segmentation fault ghc -O2 A.hs
% ghc -O2 A.hs
[2 of 2] Compiling Numeric.Sum ( A.hs, A.o )
zsh: segmentation fault ghc -O2 A.hs
% ghc -O2 A.hs
[2 of 2] Compiling Numeric.Sum ( A.hs, A.o )
zsh: illegal hardware instruction ghc -O2 A.hs
% ghc -O2 A.hs
[2 of 2] Compiling Numeric.Sum ( A.hs, A.o )
zsh: segmentation fault ghc -O2 A.hs
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14115>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list