#5243: ghc --make and ghci misses dependencies with explicit braces
---------------------------------+------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.2.1
Component: Compiler | Version: 7.0.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Karl Crary tripped over this deeply strange case:
{{{
Bar.hs
module Bar where
bar = True
Main.hs
{ import Bar; main = print bar }
}}}
Notice that `Main.hs` is missing its "`module Main where`" part, but has
explicit braces and semicolons. The BNF in the language standard says
that is fine.
If you compile them one at a time all is well:
{{{
ghc -c Bar.hs
ghc -c Main.hs
}}}
But if you use `--make` it breaks:
{{{
simonpj@cam-04-unx:~/tmp$ ghc --make Main -ddump-parsed -ddump-rn
[1 of 1] Compiling Main ( Main.hs, Main.o )
==================== Parser ====================
import Bar
main = print foo
Main.hs:1:29: Not in scope: `foo'
}}}
Bizarre, eh? This is ghc 7.0.3. It's as if `--make` somehow ignores the
import of `Bar`, even though it is parsed just fine.
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5243>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs