[GHC] #15052: DeriveAnyClass instances may skip TypeError constraints

GHC ghc-devs at haskell.org
Wed Apr 18 00:00:34 UTC 2018


#15052: DeriveAnyClass instances may skip TypeError constraints
-------------------------------------+-------------------------------------
           Reporter:  jcpetruzza     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.2.2
           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:
-------------------------------------+-------------------------------------
 In the presence of `TypeError`, one can derive instances with
 `DeriveAnyClass` that would be rejected otherwise. A simplistic example
 would be:

 {{{#!haskell
 {-# LANGUAGE DeriveAnyClass       #-}
 {-# LANGUAGE DataKinds            #-}
 {-# LANGUAGE FlexibleContexts     #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE UndecidableSuperClasses #-}
 module T

 where

 import GHC.TypeLits(TypeError, ErrorMessage(..))


 class TypeError ('Text "BOOM") => C a where
     f :: a -> ()
     f _ = ()


 data T = T
   deriving(C)

 }}}

 Of course, any attempt to use the instance leads to a type-error. However,
 the instance is rejected right away using a normal instance declaration or
 StandaloneDeriving.

 While this is a toy example, it can actually happen when using `Generics`
 and default-signatures, where one would puts a `TypeError` in an instance
 head for one of the `Generics` constructors to give a better error
 message.

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


More information about the ghc-tickets mailing list