type families not advertised for 6.8

Simon Peyton-Jones simonpj at microsoft.com
Wed Oct 24 05:56:23 EDT 2007


Yes, GHC also uses `cast` to express the coercion for a newtype.  A type class with just one method is represented by a newtype.  Nothing to do with FDs; this is two source-language constructs using the same intermediate-language encoding.   (Though using casts for newtype did give rise to an unexpected interaction that I have yet to sort out!  http://hackage.haskell.org/trac/ghc/ticket/1496)

Simon

| -----Original Message-----
| From: Remi Turk [mailto:rturk at science.uva.nl]
| Sent: 20 October 2007 21:25
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users at haskell.org; Jean-Philippe Bernardy
| Subject: Re: type families not advertised for 6.8
|
| On Fri, Oct 19, 2007 at 08:25:22AM +0100, Simon Peyton-Jones wrote:
| > | What does this imply for 6.8 support for FD's, as they now use
| > | the same type-coercions?
| >
| > Actually FDs do not use type coercions, in GHC at least.  As Mark
|
| Excuse me, it turns out I didn't look carefully enough: It's not
| functional dependencies, it's classes-with-only-one-method:
|
| module Bar where
|
| bar = fmap id []
|
| Compiles to the following Core with 6.8.0.20071002:
|
| Bar.bar :: forall a_a5M. [a_a5M]
| [GlobalId]
| []
| Bar.bar =
|   \ (@ a_a5M) ->
|     (GHC.Base.$f8
|      `cast` ((GHC.Base.:Co:TFunctor) []
|              :: (GHC.Base.:TFunctor) []
|                   ~
|                 forall a_a5G b_a5H. (a_a5G -> b_a5H) -> [a_a5G] -> [b_a5H]))
|       @ a_a5M @ a_a5M (GHC.Base.id @ a_a5M) (GHC.Base.[] @ a_a5M)
|
|
| Or does this simply mean that only type-functions (the type/axiom
| stuff) is not supported in 6.8, but type coercions (~ and cast) are supported
| (although perhaps not at the source level)?


More information about the Glasgow-haskell-users mailing list