[GHC] #14220: GeneralizedNewtypeDeriving and polymorphic arguments don't play nicely together

GHC ghc-devs at haskell.org
Tue Sep 12 04:53:52 UTC 2017


#14220: GeneralizedNewtypeDeriving and polymorphic arguments don't play nicely
together
--------------------------------------+---------------------------------
           Reporter:  ivanm           |             Owner:  (none)
               Type:  bug             |            Status:  new
           Priority:  normal          |         Milestone:
          Component:  Compiler        |           Version:  8.0.2
           Keywords:                  |  Operating System:  MacOS X
       Architecture:  x86_64 (amd64)  |   Type of failure:  None/Unknown
          Test Case:                  |        Blocked By:
           Blocking:                  |   Related Tickets:
Differential Rev(s):                  |         Wiki Page:
--------------------------------------+---------------------------------
 I'm not sure if this is a bug per se, but ghci says to report it so here
 it is:

 test.hs:
 {{{#!hs
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}

 class NameOf a where
   nameOf :: proxy a -> String

 instance NameOf Int where
   nameOf _ = "Int"

 newtype MyInt = MyInt Int
   deriving (NameOf)
 }}}

 {{{
 $ ghci test.hs
 GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( test.hs, interpreted )

 test.hs:10:13: warning: [-Wdeferred-type-errors]
     • Couldn't match representation of type ‘proxy1 Int’
                                with that of ‘proxy1 MyInt’
         arising from a use of ‘GHC.Prim.coerce’
       NB: We cannot know what roles the parameters to ‘proxy1’ have;
         we must assume that the role is nominal
     • In the expression:
         GHC.Prim.coerce
           @(forall (proxy :: TYPE GHC.Types.PtrRepLifted
                              -> TYPE GHC.Types.PtrRepLifted).
             proxy Int -> String)
           @(forall (proxy :: TYPE GHC.Types.PtrRepLifted
                              -> TYPE GHC.Types.PtrRepLifted).
             proxy MyInt -> String)
           nameOf
       In an equation for ‘nameOf’:
           nameOf
             = GHC.Prim.coerce
                 @(forall (proxy :: TYPE GHC.Types.PtrRepLifted
                                    -> TYPE GHC.Types.PtrRepLifted).
                   proxy Int -> String)
                 @(forall (proxy :: TYPE GHC.Types.PtrRepLifted
                                    -> TYPE GHC.Types.PtrRepLifted).
                   proxy MyInt -> String)
                 nameOf
       When typechecking the code for ‘nameOf’
         in a derived instance for ‘NameOf MyInt’:
         To see the code I am typechecking, use -ddump-deriv
       In the instance declaration for ‘NameOf MyInt’
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.2 for x86_64-apple-darwin):
         opt_univ fell into a hole {a15j}

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

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


More information about the ghc-tickets mailing list