[GHC] #13729: ghc does not pick up TH changes across package boundaries
GHC
ghc-devs at haskell.org
Fri May 19 14:12:13 UTC 2017
#13729: ghc does not pick up TH changes across package boundaries
-------------------------------------+-------------------------------------
Reporter: Feuerbach | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I have the following three modules:
{{{#!hs
module Types where
data Foo = Bar
}}}
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Types
th_string = lift . show =<< reify ''Foo
}}}
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Main where
import TH
main = putStrLn $(th_string)
}}}
The goal is to make Main recompile if the definition of Types.Foo changes.
If I simply put the three files in the same directory and compile with
ghc, it works.
However, if I put Types and TH in package A and Main in package B, then
ghc doesn't recompile B.Main if I change the definition of A.Types.Foo and
reinstall the package A.
I tried this with both stack and cabal-install. In both cases I compiled
B.Main directly with ghc, so it's not Cabal that's hiding the changes. If
I pass -fforce-recomp to ghc, Main recompiles as expected.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13729>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list