[GHC] #7672: boot file entities are sometimes invisible and are not (semantically) unified with corresponding entities in implementing module
GHC
cvs-ghc at haskell.org
Fri Feb 8 18:59:57 CET 2013
#7672: boot file entities are sometimes invisible and are not (semantically)
unified with corresponding entities in implementing module
--------------------------------------+-------------------------------------
Reporter: skilpat | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 7.4.2 | Keywords: recursive modules, boot files, double vision, double vision problem
Os: Linux | Architecture: x86_64 (amd64)
Failure: GHC rejects valid program | Blockedby:
Blocking: | Related:
--------------------------------------+-------------------------------------
Comment(by skilpat):
I must scale back my assessment of the problem somewhat: double vision is
indeed handled, to some extent, by GHC. In particular, a view of a type
from a boot file is treated ''as an equivalent type'' to a view of that
type from the implementation. That's good! But you still cannot
syntactically refer to both views in the same program. That's less good.
As a slight variation to my example with three modules, we make B expose a
function that mentions (the boot file's view of) T. Then in the A
implementation, we check that this function may be successfully applied to
a value of (the local view of) type T. Indeed, GHC accepts all this!
{{{
module A where
data T
}}}
{{{
module B(Decl.T, f) where
import {-# SOURCE #-} qualified A as Decl
f :: Decl.T -> Bool
f _ = True
}}}
{{{
module A where
import qualified B
data T = Z | S T
x = B.f Z
}}}
In the A implementation I'm not ever mentioning the boot file view of T,
B.T. If you try to do so, then GHC rejects the program with the same error
messages as mentioned in the original report. That is, the following
variation on A fails
{{{
module A where
import qualified B
data T = Z | S B.T
x = B.f Z :: B.T
}}}
with two independent errors, one for each reference to B.T:
{{{
A.hs:3:18:
Not in scope: type constructor or class `B.T'
Perhaps you meant `A.T' (line 3)
A.hs:4:16:
Not in scope: type constructor or class `B.T'
Perhaps you meant `A.T' (line 3)
}}}
In light of this example, I retract my statement that GHC fails to solve
the double vision problem! It's unclear, though, to what extent it does
so, as there's still some amount of wackiness.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7672#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list