[GHC] #12768: 8.0.2 derives invalid code when class method is constrained by itself

GHC ghc-devs at haskell.org
Thu Oct 27 11:44:40 UTC 2016


#12768: 8.0.2 derives invalid code when class method is constrained by itself
-------------------------------------+-------------------------------------
           Reporter:  jophish        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
           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:
-------------------------------------+-------------------------------------
 GHC 8.0.1 is able to compile this without a problem and doesn't require
 FlexibleContexts.

 {{{#!hs
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE ConstrainedClassMethods #-}

 module A where

 class C m where
   foo :: C m => m ()

 newtype N m a = N (m a)
   deriving C
 }}}

 Compare the output of 8.0.1, 8.0.2 and 8.1. I turned on -fdefer-type-
 errors in order for -ddump-deriv to work.

 {{{
 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 8.0.1

 $ ghc -ddump-deriv A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )

 ==================== Derived instances ====================
 Derived instances:
   instance A.C m_aNK => A.C (A.N m_aNK) where
     A.foo = GHC.Prim.coerce (A.foo :: m_ap1 ()) :: A.N m_ap1 ()


 GHC.Generics representation types:
 }}}

 {{{

 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 8.0.2

 $ ghc A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )

 A.hs:10:12: error:
     • Couldn't match type ‘m’ with ‘N m’
         arising from the coercion of the method ‘foo’
           from type ‘C m => m ()’ to type ‘C (N m) => N m ()’
       ‘m’ is a rigid type variable bound by
         the deriving clause for ‘C (N m)’ at A.hs:10:12
     • When deriving the instance for (C (N m))

 $ ghc -ddump-deriv -fdefer-type-errors A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )

 ==================== Derived instances ====================
 Derived instances:
   instance A.C m_awm => A.C (A.N m_awm) where
     A.foo
       = GHC.Prim.coerce
           @(A.C m_ap0 => m_ap0 ()) @(A.C (A.N m_ap0) => A.N m_ap0 ())
 A.foo


 GHC.Generics representation types:



 A.hs:11:12: warning: [-Wdeferred-type-errors]
     • Couldn't match type ‘m’ with ‘N m’
         arising from a use of ‘GHC.Prim.coerce’
       ‘m’ is a rigid type variable bound by
         the instance declaration at A.hs:11:12
     • In the expression:
         GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo
       In an equation for ‘foo’:
           foo = GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo
       When typechecking the code for ‘foo’
         in a derived instance for ‘C (N m)’:
         To see the code I am typechecking, use -ddump-deriv
       In the instance declaration for ‘C (N m)’
     • Relevant bindings include foo :: N m () (bound at A.hs:11:12)
 }}}

 There's no '8.0.2' version to report this against so I've chosen 8.1. GHC
 8.1 gives very similar results:

 {{{
 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 8.1.20160930

 $ ghc A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )

 A.hs:11:12: error:
     • Couldn't match type ‘m’ with ‘N m’
         arising from the coercion of the method ‘foo’
           from type ‘C m => m ()’ to type ‘C (N m) => N m ()’
       ‘m’ is a rigid type variable bound by
         the deriving clause for ‘C (N m)’ at A.hs:11:12
     • When deriving the instance for (C (N m))

 $ ghc -ddump-deriv -fdefer-type-errors A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )

 ==================== Derived instances ====================
 Derived instances:
   instance A.C m_awK => A.C (A.N m_awK) where
     A.foo
       = GHC.Prim.coerce
           @(A.C m_app => m_app ()) @(A.C (A.N m_app) => A.N m_app ())
 A.foo


 GHC.Generics representation types:



 A.hs:11:12: warning: [-Wsimplifiable-class-constraints]
     The constraint ‘C (N m)’ matches an instance declaration
     instance C m => C (N m) -- Defined at A.hs:11:12
     This makes type inference for inner bindings fragile;
       either use MonoLocalBinds, or simplify it using the instance

 A.hs:11:12: warning: [-Wdeferred-type-errors]
     • Couldn't match type ‘m’ with ‘N m’
         arising from a use of ‘GHC.Prim.coerce’
       ‘m’ is a rigid type variable bound by
         the instance declaration at A.hs:11:12
     • In the expression:
         GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo
       In an equation for ‘foo’:
           foo = GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo
       When typechecking the code for ‘foo’
         in a derived instance for ‘C (N m)’:
         To see the code I am typechecking, use -ddump-deriv
       In the instance declaration for ‘C (N m)’
     • Relevant bindings include foo :: N m () (bound at A.hs:11:12)
 }}}

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


More information about the ghc-tickets mailing list