
#8678: Derivin `Functor` complains about existential type ------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- When deriving a functor with !DataKinds enabled {{{ {-# LANGUAGE DataKinds, DeriveFunctor, FlexibleInstances, GADTs, KindSignatures, StandaloneDeriving #-} data {- kind -} Nat = Z | S Nat data NonStandard :: Nat -> * -> * where Standard :: a -> NonStandard (S n) a Non :: NonStandard n a -> a -> NonStandard (S n) a deriving instance Show a => Show (NonStandard n a) deriving instance Functor (NonStandard n) }}} I get following error message {{{ NonStandard.hs:10:1: Can't make a derived instance of ‛Functor (NonStandard n)’: Constructor ‛Standard’ must not have existential arguments In the stand-alone deriving instance for ‛Functor (NonStandard n)’ }}} But the `Standard` constructor is not at all existential in the last type argument! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8678 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler