[GHC] #15191: Deriving via DeriveAnyClass not behaving the same as an emply instance declaration
GHC
ghc-devs at haskell.org
Mon May 28 12:48:32 UTC 2018
#15191: Deriving via DeriveAnyClass not behaving the same as an emply instance
declaration
-------------------------------------+-------------------------------------
Reporter: Darwin226 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Darwin226:
Old description:
> I've opened [https://stackoverflow.com/questions/50557019/deriving-via-
> deriveanyclass-not-behaving-the-same-as-an-emply-instance-declarati a
> question on StackOverflow] describing the issue. I'll copy it here:
>
> ----
>
> I have the following code
>
> {{{#!hs
> {-# LANGUAGE PolyKinds, DefaultSignatures, FlexibleContexts,
> DeriveAnyClass, DeriveGeneric #-}
> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,
> UndecidableInstances #-}
> module DeriveTest where
>
> import GHC.Generics
>
> class GenericClass a m where
> instance GenericClass f m => GenericClass (M1 i c f) m
> instance Condition a m => GenericClass (K1 i a) m
>
> class Condition (a :: k) (m :: * -> *) where
> instance (Condition a m, Condition b m) => Condition (a b) m
> instance {-# OVERLAPPABLE #-} Condition (a :: k) m
>
> class Class (e :: (* -> *) -> *) where
> classF :: e m -> ()
> default classF :: GenericClass (Rep (e m)) m => e m -> ()
> classF = undefined
> }}}
>
> It defines the class Class of types that have a higher-kinded type as a
> parameter. It also defines a generic way to derive an instance of that
> class. Now if I declare a new datatype like this, and try to derive an
> instance of Class
>
> {{{#!hs
> data T a m = T
> { field :: a }
> deriving (Generic, Class)
> }}}
>
> I get the following error:
>
> {{{
> * Overlapping instances for Condition a m
> arising from the 'deriving' clause of a data type declaration
> Matching instances:
> instance [overlappable] forall k (a :: k) (m :: * -> *).
> Condition a m
> instance forall k1 k2 (a :: k1 -> k2) (m :: * -> *) (b :: k1).
> (Condition a m, Condition b m) =>
> Condition (a b) m
> (The choice depends on the instantiation of `a, m'
> To pick the first instance above, use IncoherentInstances
> when compiling the other instance declarations)
> * When deriving the instance for (Class (T a))
> |
> 22 | deriving (Generic, Class)
> |
> ^^^^^
> }}}
>
> The error sort of makes sense because I guess. The instance really does
> depend on the instantiation of a. However, if I just write an empty
> instance like this:
>
> {{{#!hs
> data T a m = T
> { field :: a }
> deriving (Generic)
> instance Class (T a) -- works
> }}}
>
> It works. Why? And how can I make it behave the same with the deriving
> statement?
>
> ----
>
> Ryan Scott suggested I open a ticket and that the issue probably isn't
> with the deriving mechanisms. Still, I chose to keep the title because
> that's what the original problem was and I've seen
> [https://github.com/GetShopTV/swagger2/issues/144 similar issues] before
New description:
I've opened [https://stackoverflow.com/questions/50557019/deriving-via-
deriveanyclass-not-behaving-the-same-as-an-emply-instance-declarati a
question on StackOverflow] describing the issue. I'll copy it here:
----
I have the following code
{{{#!hs
{-# LANGUAGE PolyKinds, DefaultSignatures, FlexibleContexts,
DeriveAnyClass, DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,
UndecidableInstances #-}
module DeriveTest where
import GHC.Generics
class GenericClass a m where
instance GenericClass f m => GenericClass (M1 i c f) m
instance Condition a m => GenericClass (K1 i a) m
class Condition (a :: k) (m :: * -> *) where
instance (Condition a m, Condition b m) => Condition (a b) m
instance {-# OVERLAPPABLE #-} Condition (a :: k) m
class Class (e :: (* -> *) -> *) where
classF :: e m -> ()
default classF :: GenericClass (Rep (e m)) m => e m -> ()
classF = undefined
}}}
It defines the class Class of types that have a higher-kinded type as a
parameter. It also defines a generic way to derive an instance of that
class. Now if I declare a new datatype like this, and try to derive an
instance of Class
{{{#!hs
data T a m = T
{ field :: a }
deriving (Generic, Class)
}}}
I get the following error:
{{{
* Overlapping instances for Condition a m
arising from the 'deriving' clause of a data type declaration
Matching instances:
instance [overlappable] forall k (a :: k) (m :: * -> *).
Condition a m
instance forall k1 k2 (a :: k1 -> k2) (m :: * -> *) (b :: k1).
(Condition a m, Condition b m) =>
Condition (a b) m
(The choice depends on the instantiation of `a, m'
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
* When deriving the instance for (Class (T a))
|
22 | deriving (Generic, Class)
| ^^^^^
}}}
The error sort of makes sense I guess. The instance really does depend on
the instantiation of a. However, if I just write an empty instance like
this:
{{{#!hs
data T a m = T
{ field :: a }
deriving (Generic)
instance Class (T a) -- works
}}}
It works. Why? And how can I make it behave the same with the deriving
statement?
----
Ryan Scott suggested I open a ticket and that the issue probably isn't
with the deriving mechanisms. Still, I chose to keep the title because
that's what the original problem was and I've seen
[https://github.com/GetShopTV/swagger2/issues/144 similar issues] before
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15191#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list