Bad Constructor used with deriving clause [GHC-16437]
The deriving mechanism expects constructors of a particular form. When the constructors do not comport to this form, this error is thrown:
• Can't make a derived instance of ‘Functor (T a)’:
Constructor ‘Mk’ is a GADT
• In the data declaration for ‘T’
Suggested fix: Use a standalone deriving declaration instead
Examples
Attempt at using deriving clause with GADT.
Deriving_gadt.hs
Before
module Deriving_gadt where
data T a b where
Mk :: Int -> b -> T Int b
deriving (Functor)
After
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
module Deriving_gadt where
data T a b where
Mk :: Int -> b -> T Int b
deriving instance Functor (T a)
Use of higher-rank types with a deriving clause.
Higher_rank.hs
Before
{-# LANGUAGE RankNTypes #-}
module Higher_rank where
data Bad = MkBad (forall a. a) deriving Eq
After
module Higher_rank where
-- unfortunately we just need a rank 1 type
data Bad a = MkBad a deriving Eq