[GHC] #15191: Deriving via DeriveAnyClass not behaving the same as an emply instance declaration

GHC ghc-devs at haskell.org
Mon May 28 15:09:54 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:  Instances
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:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * keywords:   => Instances


Comment:

 As I mentioned in the Stack Overflow post, I think this has nothing to do
 with `deriving`, but rather the interaction between GHC's constraint
 solver and overlapping instances. Take this code:

 {{{#!hs
 {-# LANGUAGE DefaultSignatures #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE UndecidableInstances #-}
 module Bug 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 = classFDefault

 classFDefault :: forall (e :: (* -> *) -> *) (m :: * -> *).
                  GenericClass (Rep (e m)) m => e m -> ()
 classFDefault = undefined

 data T a m = T
     { field :: a }
     deriving (Generic)
 }}}

 And observe that this typechecks:

 {{{#!hs
 instance Class (T a) where
   classF = classFDefault
 }}}

 But this doesn't:

 {{{#!hs
 classFT :: forall a (m :: * -> *).
            T a m -> ()
 classFT = classFDefault
 }}}

 As it gives the same error as if you'd used a `deriving` clause:

 {{{
 $ /opt/ghc/8.4.2/bin/ghci Bug.hs
 GHCi, version 8.4.2: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )

 Bug.hs:36:11: error:
     • Overlapping instances for Condition a m
         arising from a use of ‘classFDefault’
       Matching instances:
         instance [overlappable] forall k (a :: k) (m :: * -> *).
                                 Condition a m
           -- Defined at Bug.hs:19:31
         instance forall k1 k2 (a :: k1 -> k2) (m :: * -> *) (b :: k1).
                  (Condition a m, Condition b m) =>
                  Condition (a b) m
           -- Defined at Bug.hs:18:10
       (The choice depends on the instantiation of ‘a, m’
        To pick the first instance above, use IncoherentInstances
        when compiling the other instance declarations)
     • In the expression: classFDefault
       In an equation for ‘classFT’: classFT = classFDefault
    |
 36 | classFT = classFDefault
    |           ^^^^^^^^^^^^^
 }}}

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


More information about the ghc-tickets mailing list