[GHC] #12731: Generic type class has type family; leads to big dep_finsts

GHC ghc-devs at haskell.org
Tue Oct 18 03:53:37 UTC 2016


#12731: Generic type class has type family; leads to big dep_finsts
-------------------------------------+-------------------------------------
           Reporter:  ezyang         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 While trying to determine a good explanation for simonpj's question in
 Phab:D2607, I noticed that `dep_finsts` was a lot larger than I would have
 ordinarily expected it to be: it included many modules that did not have
 the `TypeFamilies` extension enabled for them. For example, for one module
 in Cabal, here's "family instance modules":

 {{{
 family instance modules: Distribution.Compat.Semigroup
                          Distribution.Compiler Distribution.ModuleName
 Distribution.Package
                          Distribution.Simple.Compiler Distribution.System
                          Distribution.Utils.ShortText
 Distribution.Verbosity
                          Distribution.Version Language.Haskell.Extension
 Control.Applicative
                          Data.Complex Data.Either Data.Functor.Const
 Data.Functor.Identity
                          Data.List.NonEmpty Data.Monoid Data.Semigroup
 Data.Type.Equality
                          Data.Version Data.Void GHC.Exts GHC.Generics
 GHC.IO.Exception
                          GHC.TypeLits Data.IntMap.Base Data.IntSet.Base
 Data.Map.Base
                          Data.Sequence Data.Set.Base
 Text.PrettyPrint.Annotated.HughesPJ
                          Text.PrettyPrint.HughesPJ
 }}}

 Do we *really* have this many type family instances in base and Cabal? I
 was flummoxed, until I realized that the Generic type class defines a type
 family!

 {{{
 -- | Representable types of kind *.
 -- This class is derivable in GHC with the DeriveGeneric flag on.
 class Generic a where
   -- | Generic representation type
   type Rep a :: * -> *
   -- | Convert from the datatype to its representation
   from  :: a -> (Rep a) x
   -- | Convert from the representation to the datatype
   to    :: (Rep a) x -> a
 }}}

 The upshot is that if you derive Generic, you have agreed to a perpetual
 interface file size tax on every module which transitively depends on your
 module, as well as lots of fruitless pairwise consistency checking. Ick,
 especially considering that it's fairly common practice to slap a Generic
 on every data type you define.

 This is a case where we would gain a lot if we could put a local
 restriction on Generic instances so that individual instances are
 guaranteed not to overlap, e.g., like one of the rules that Rust uses
 (http://smallcultfollowing.com/babysteps/blog/2015/01/14/little-orphan-
 impls/) Then we'd avoid balling up a big transitive closure of all modules
 that wrote `deriving Generic`. Since non-overlapness is guaranteed by
 construction, we'd no longer need an eager check.

 Related #5224

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


More information about the ghc-tickets mailing list