[GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10

GHC ghc-devs at haskell.org
Fri Jul 31 14:45:49 UTC 2015


#10715: Possible regression in Coercible a (X a) between 7.8 and 7.10
-------------------------------------+-------------------------------------
        Reporter:  inaki             |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.10.1
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
 Type of failure:  GHC rejects       |  Unknown/Multiple
  valid program                      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by inaki):

 Replying to [comment:3 simonpj]:

 Thanks for the explanation! This makes it clear what happens. Just to
 state what I expected from reading the docs at
 https://hackage.haskell.org/package/base-4.8.1.0/docs/Data-Coerce.html,
 the following works:
 {{{#!hs
 {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances
 #-}
 -- import Data.Coerce (coerce, Coercible)

 data X a

 class Coercible a b where
     coerce :: a -> b

 newtype Y = Y (X Y)

 instance Coercible Y (X Y) where
     coerce (Y x) = x

 doCoerce :: Coercible a (X a) => a -> X a
 doCoerce = coerce

 test :: Y -> X Y
 test = doCoerce
 }}}
 which embodies what I understand the docs to be saying: because of the
 newtype, there is (morally) an instance of Coercible Y (X Y). But somehow
 the actual behavior of Coercible in 7.10 seems different.

 >  * It wouldn't help your use-case.  But do you have to use `Y` in this
 strange recursive way. Why not do this?
 > {{{
 > newtype FY = FY (ForeignPtr Y)
 > data Y
 > }}}
 With the recursive definition for every newtype we automatically know the
 type of the ForeignPtr inside, while these ForeignPtrs still have distinct
 types, which comes handy on a number of occasions. It is also the way c2hs
 defines newtypes, for example
 {{{
 {# pointer *GIBaseInfo as BaseInfo newtype #}
 }}}
 becomes
 {{{#!hs
 newtype BaseInfo = BaseInfo (Ptr (BaseInfo))
 }}}
 so it is a fairly common idiom in the wild.

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


More information about the ghc-tickets mailing list