[GHC] #13251: Must perform family consistency check on non-imported identifiers
GHC
ghc-devs at haskell.org
Thu Feb 9 10:44:39 UTC 2017
#13251: Must perform family consistency check on non-imported identifiers
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by ezyang:
@@ -54,0 +54,25 @@
+
+ A few things to note about how to fix this:
+
+ * Currently, type family instances are checked for consistency as we
+ process imports. Template Haskell splices can occur much later in a
+ Haskell file, so we must correspondingly do these checks later.
+
+ * If we refer to an identifier by synthesizing a name manually, it is as
+ if we imported it. This also means that a reference of this sort implies
+ an implicit import of the defining module (#13102) and we should consider
+ instances from it visible (at the moment, it's not considered visible.)
+ (Actually, with TH, this is a bit tricky, because if we take these
+ semantics, an instance might be visible below a top-level splice, but
+ invisible above it.)
+
+ * It is probably simplest if the type family compatibility check happens
+ at the end. So we should go ahead and revive idea (2) from
+ https://ghc.haskell.org/trac/ghc/ticket/11062#comment:9 ; if there are
+ overlapping families we should just not reduce the type family.
+
+ * For wired in things, it's pretty easy to find out if we have an implicit
+ import: if we bang on `checkWiredInTyCon`, that means we intended for the
+ instance to visible; so we should collect all of the TyCons we banged on
+ this way. For TH, this isn't exactly going to work, but maybe we can just
+ track when NameGs get synthesized.
New description:
Currently, the family consistency check checks pairs of *imported* modules
(and the modules they transitively import) for consistency. However, there
are a number of mechanisms by which we can refer to an identifier from a
module without explicitly importing it. Here is one example from Template
Haskell:
{{{
-- A.hs
{-# LANGUAGE TypeFamilies #-}
module A where
type family F a
-- B.hs
{-# LANGUAGE TypeFamilies #-}
module B where
import A
type instance F Bool = String
g :: F Bool
g = "af"
-- C.hs
{-# LANGUAGE TypeFamilies #-}
module C where
import A
type instance F Bool = Int
h :: F Bool -> IO ()
h = print
-- D.hs
{-# LANGUAGE TemplateHaskell #-}
import C
import Language.Haskell.TH.Syntax
main = h $( return (VarE (Name (OccName "g") (NameG VarName (PkgName
"main") (ModName "B")))) )
}}}
This does an unsafe coerce:
{{{
ezyang at sabre:~/Dev/labs/T13102$ ghc-head --make B.hs D.hs -fforce-recomp
[1 of 4] Compiling A ( A.hs, A.o )
[2 of 4] Compiling B ( B.hs, B.o )
[3 of 4] Compiling C ( C.hs, C.o )
[4 of 4] Compiling Main ( D.hs, D.o )
Linking D ...
ezyang at sabre:~/Dev/labs/T13102$ ./D
8070450533355229282
}}}
Clearly, checking consistency on imports is not enough: we must also check
up on original names that come by other mechanisms. (Other ways we can end
up with identifiers without imports include overloading, see #13102.
A few things to note about how to fix this:
* Currently, type family instances are checked for consistency as we
process imports. Template Haskell splices can occur much later in a
Haskell file, so we must correspondingly do these checks later.
* If we refer to an identifier by synthesizing a name manually, it is as
if we imported it. This also means that a reference of this sort implies
an implicit import of the defining module (#13102) and we should consider
instances from it visible (at the moment, it's not considered visible.)
(Actually, with TH, this is a bit tricky, because if we take these
semantics, an instance might be visible below a top-level splice, but
invisible above it.)
* It is probably simplest if the type family compatibility check happens
at the end. So we should go ahead and revive idea (2) from
https://ghc.haskell.org/trac/ghc/ticket/11062#comment:9 ; if there are
overlapping families we should just not reduce the type family.
* For wired in things, it's pretty easy to find out if we have an implicit
import: if we bang on `checkWiredInTyCon`, that means we intended for the
instance to visible; so we should collect all of the TyCons we banged on
this way. For TH, this isn't exactly going to work, but maybe we can just
track when NameGs get synthesized.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13251#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list