
#14440: Duplicate type family instances are permitted -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Type checker) | Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This threw me for a loop recently. To my surprise, GHC is quite happy to allow duplicate type family instances, provided that their RHSes are the same: {{{#!hs {-# LANGUAGE TypeFamilies #-} module Lib where type family Foo b }}} {{{#!hs {-# LANGUAGE TypeFamilies #-} module A where import Lib type instance Foo Bool = Bool }}} {{{#!hs {-# LANGUAGE TypeFamilies #-} module B where import Lib type instance Foo Bool = Bool }}} {{{#!hs module C where import A import B import Lib f :: Bool -> Foo Bool f x = not x }}} {{{ $ /opt/ghc/8.2.1/bin/ghci C.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 4] Compiling Lib ( Lib.hs, interpreted ) [2 of 4] Compiling B ( B.hs, interpreted ) [3 of 4] Compiling A ( A.hs, interpreted ) [4 of 4] Compiling C ( C.hs, interpreted ) Ok, 4 modules loaded. λ> :i Foo type family Foo b :: * -- Defined at Lib.hs:4:1 type instance Foo Bool = Bool -- Defined at A.hs:6:15 type instance Foo Bool = Bool -- Defined at B.hs:6:15 }}} Is this intended? My intuition screams "no", since if we offer //class// instance coherence, it seems like one ought to offer //type family// instance coherence as well. At the same time, I can't think of any threat to type soundness imposed by this (although it's quite strange to see two duplicate type family instances in the output of `:i` with two completely different provenances). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14440 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler