[GHC] #11774: Regression on GHC 8 branch (vs 7.10.3) when using the GHC API to parse code that uses TH

GHC ghc-devs at haskell.org
Wed Mar 30 16:06:21 UTC 2016


#11774: Regression on GHC 8 branch (vs 7.10.3) when using the GHC API to parse code
that uses TH
----------------------------------------+---------------------------------
           Reporter:  SimonHengel       |             Owner:
               Type:  bug               |            Status:  new
           Priority:  normal            |         Milestone:
          Component:  Compiler          |           Version:  8.0.1-rc2
           Keywords:                    |  Operating System:  Linux
       Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
          Test Case:                    |        Blocked By:
           Blocking:                    |   Related Tickets:
Differential Rev(s):                    |         Wiki Page:
----------------------------------------+---------------------------------
 If you use the GHC API to parse code that uses TH, the code does not work
 after a {{{:reload}}} in {{{ghci}}} anymore.

 = Steps to reproduce

 Given the following three modules

 {{{#!hs
 module Extract where
 import Prelude hiding (mod)
 import Data.Generics
 import DynFlags
 import FastString
 import GHC
 import GHC.Paths
 import Control.Monad
 import Digraph (flattenSCCs)

 extractDocStrings :: IO [String]
 extractDocStrings = do
   concatMap (extract . pm_parsed_source . tm_parsed_module) <$> do
     runGhc (Just libdir) $ do
       _ <- getSessionDynFlags >>= setSessionDynFlags . setHaddockMode
       guessTarget "Foo.hs" Nothing >>= setTargets . return
       mods <- depanal [] False >>= enableCompilation
       let sortedMods = flattenSCCs (topSortModuleGraph False mods Nothing)
       mapM (parseModule >=> typecheckModule >=> loadModule) sortedMods
   where
     setHaddockMode :: DynFlags -> DynFlags
     setHaddockMode dynflags = (gopt_set dynflags Opt_Haddock)

     extract :: ParsedSource -> [String]
     extract m = [unpackFS s | HsDocString s <- everything (++) ([] `mkQ`
 return) m]

 enableCompilation :: ModuleGraph -> Ghc ModuleGraph
 enableCompilation modGraph = do
   let enableComp d = let platform = targetPlatform d
                       in d { hscTarget = defaultObjectTarget platform }
   modifySessionDynFlags enableComp
   let upd m = m { ms_hspp_opts = enableComp (ms_hspp_opts m) }
   let modGraph' = map upd modGraph
   return modGraph'

 modifySessionDynFlags :: (DynFlags -> DynFlags) -> Ghc ()
 modifySessionDynFlags f = do
   dflags <- getSessionDynFlags
   let dflags' = case lookup "GHC Dynamic" (compilerInfo dflags) of
         Just "YES" -> gopt_set dflags Opt_BuildDynamicToo
         _          -> dflags
   _ <- setSessionDynFlags (f dflags')
   return ()
 }}}

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 module Foo where

 import Bar

 -- | some documentation
 foo :: Int
 foo = $(bar)
 }}}

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 module Bar where

 bar = [|23|]
 }}}


 == Expected (GHC 7.10.2 behavior)

 {{{
 $ ghci Extract.hs
 GHCi, version 7.10.2: http://www.haskell.org/ghc/  :? for help
 *Extract> extractDocStrings
 [" some documentation"]
 *Extract> :reload
 *Extract> extractDocStrings
 [" some documentation"]
 }}}

 == Actual (GHC 8.0.0.20160329 behavior)

 {{{
 $ ghci Extract.hs
 GHCi, version 8.0.0.20160329: http://www.haskell.org/ghc/  :? for help
 *Extract> extractDocStrings
 [" some documentation"]
 *Extract> :reload
 *Extract> extractDocStrings
 /tmp/ghc24970_1/libghc_7.so: file not recognized: File truncated
 collect2: error: ld returned 1 exit status
 *** Exception: `gcc' failed in phase `Linker'. (Exit code: 1)
 }}}

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


More information about the ghc-tickets mailing list