[GHC] #14576: Internal error when compiling TH code with profiling on Windows

GHC ghc-devs at haskell.org
Wed Dec 13 07:30:21 UTC 2017


#14576: Internal error when compiling TH code with profiling on Windows
-------------------------------------+-------------------------------------
           Reporter:  lazac          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  GHC API        |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:  x86_64         |   Type of failure:  Compile-time
  (amd64)                            |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When using the GHC API with this minimal example, compiled with profiling
 enabled:

 {{{#!hs
 module Main where

 import GHC
 import GHC.Paths ( libdir )

 main = runGhc (Just libdir) $ do
         env <- getSession
         dflags <- getSessionDynFlags
         setSessionDynFlags dflags
         target <- guessTarget "A.hs" Nothing
         setTargets [target]
         load LoadAllTargets
 }}}

 Invoking the main executable:
 {{{
 testprof
 }}}

 While A.hs contains a TH splice:
 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 module A where

 $(return [])
 }}}

 The compiler crashes:
 {{{
 testprof.exe: internal error: IMAGE_REL_AMD64_ADDR32[NB]: High bits are
 set in 10e6109d0 for .text
     (GHC version 8.2.1 for x86_64_unknown_mingw32)
     Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug

 This application has requested the Runtime to terminate it in an unusual
 way.
 Please contact the application's support team for more information.
 }}}

 The walkaround is to use -fexternal-interpreter, in that case, the crash
 does not happen.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14576>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list