[GHC] #8540: Template Haskell handling bug in ghc-7.7.20131115 ?
GHC
ghc-devs at haskell.org
Tue Nov 19 11:45:06 UTC 2013
#8540: Template Haskell handling bug in ghc-7.7.20131115 ?
-------------------------------------+------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by awson):
Here is the simplest test case:
Foo.hs
{{{
{-# LANGUAGE TemplateHaskell #-}
module Foo (foo) where
import Language.Haskell.TH
foo :: Q Exp
foo = [| bar |]
bar :: Int
bar = 5
}}}
Baz.hs
{{{
{-# LANGUAGE TemplateHaskell #-}
module Baz where
import Foo
baz :: Int
baz = $foo
}}}
Current GHC gives
{{{
Baz.hs:8:7:
Can't find interface-file declaration for variable Foo.bar
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
In the expression: Foo.bar
In an equation for `baz': baz = Foo.bar
}}}
when compiling Baz.hs.
But if I explicitly export bar from Foo.hs:
{{{
{-# LANGUAGE TemplateHaskell #-}
module Foo (foo, bar) where
import Language.Haskell.TH
foo :: Q Exp
foo = [| bar |]
bar :: Int
bar = 5
}}}
current GHC gets happy.
Older GHCs were able to live without this.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8540#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list