
#13092: family instance consistency checks are too pessimistic -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: rwbarton Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I managed to write `unsafeCoerce` in 8.0.1 without involving recompilation tricks. Compile these modules in order with `ghc -c -XTypeFamilies -fforce-recomp` (then you can do a final link with `ghc -o Main Main.hs -XTypeFamilies`): {{{#!hs module A where type family A a }}} {{{#!hs module B (A, X) where import A data X type instance A (X, b) = () }}} {{{#!hs {-# LANGUAGE RankNTypes #-} module C (x) where import Data.Proxy import B x :: Proxy b -> (forall t. Proxy t -> Bool -> A (t, b)) -> (Bool -> ()) x _ f = f (undefined :: Proxy X) }}} {{{#!hs module Main where import Data.Proxy import A import C data Y type instance A (a, Y) = Bool y :: Proxy a -> Bool -> A (a, Y) y _ = id z :: Bool -> () z = x (undefined :: Proxy Y) y main = print (z True) }}} `Main` has been rigged to not directly mention any names defined in `B`, by creating the intermediate module `C`. When `Main` is compiled the interface file for `B` is not read at all! There is a kind of off-by-one error in the check. The logic in the Note `[Checking family instance consistency]` correctly takes into account the fact that we do not check consistency of family instances in a module with those in its `dep_finsts`, and so if you try to import `Main` in another module (even one that is otherwise empty) GHC will report the overlap. But that still leaves a window of one module in which the overlap can be exploited. Even if not for this example I agree with
But regardless, I think it'd be better and more consistent to eagerly check consistency of all the new family instances in A with all those in modules it imports. Then instance lookup should never find more than one match.
I think it's even more efficient overall, since we currently do those checks in the importers of `A` instead, which usually will be at least one module. If we do them while compiling `A` then the optimization that this ticket was originally about will be sound and we can avoid the checks in the importers. I also figured out what my example involving recompilation was, I'll file a separate ticket for that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13092#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler