[GHC] #13251: Must perform family consistency check on non-imported identifiers

GHC ghc-devs at haskell.org
Thu Feb 9 10:30:40 UTC 2017


#13251: Must perform family consistency check on non-imported identifiers
-------------------------------------+-------------------------------------
           Reporter:  ezyang         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
  (Type checker)                     |
           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:
-------------------------------------+-------------------------------------
 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.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13251>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list