[GHC] #13731: DeriveFunctor and friends don't understand type families

GHC ghc-devs at haskell.org
Sat May 20 02:20:25 UTC 2017


#13731: DeriveFunctor and friends don't understand type families
-------------------------------------+-------------------------------------
           Reporter:  spacekitteh    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1-rc2
           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:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE DeriveFunctor #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE TypeFamilies #-}

 data Test ext a where
   Foo :: a -> Test ext a
   Extend :: (ExtensionType ext a) -> Test ext a

 type family ExtensionType ext a
 data ListExtension
 type instance ExtensionType ListExtension a = [a]

 deriving instance Functor (Test ListExtension)

 {-

 a.hs:15:1: error:
     • Can't make a derived instance of ‘Functor (Test ListExtension)’:
         Constructor ‘Extend’ must use the type variable only as the last
 argument of a data type
     • In the stand-alone deriving instance for
         ‘Functor (Test ListExtension)’
    |
 15 | deriving instance Functor (Test ListExtension)
    | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 Failed, modules loaded: none.
 -}
 }}}

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


More information about the ghc-tickets mailing list