[GHC] #14577: Internal error when linker is initialized with -fexternal-interpreter set when compiling TH code with profiling

GHC ghc-devs at haskell.org
Wed Dec 13 07:38:41 UTC 2017


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

 {{{#!hs
 import GHC
 import Control.Monad.IO.Class
 import GHC.Paths ( libdir )
 import DynFlags
 import Linker

 main = runGhc (Just libdir) $ do
         env <- getSession
         dflags <- getSessionDynFlags
         liftIO $ initDynLinker env
         setSessionDynFlags (setGeneralFlag' Opt_ExternalInterpreter
 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:
 {{{
 Access violation in generated code when writing 0000000000000024
 }}}

 Probably I'm misusing the API in this example, but the way it crashes is
 suspicious.

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


More information about the ghc-tickets mailing list