Change from 7.10.3 to current master

Simon Peyton Jones simonpj at microsoft.com
Mon Dec 21 11:03:10 UTC 2015


|  type instance r1 :++: r2 :> a = (r1 :++: r2) :> a

What do you expect this to mean?  I suppose you could hope that GHC will unravel the fixity of :++: and :>, to determine whether you are giving an instance for :++: or for :>?

That sounds reasonable, but it's not trivial.

Currently the LHS of a 'type instance' decl is ultimately a TyFamEqn, and it looks like this:


data TyFamEqn name pats
  = TyFamEqn
       { tfe_tycon :: Located name
       , tfe_pats  :: pats
       , tfe_rhs   :: LHsType name }


So we've already decided (in the parser) what the type-function name is.  But we can't do that in this case, because the parser doesn't understand fixity.

To deal with this we'd need to change to

data TyFamEqn name pats
  = TyFamEqn
       { tfe_lhs  :: LHSType name
       , tfe_rhs   :: LHsType name }

so that the LHS was just a type.  Now the renamer can re-jiggle its fixities in the usual way, and only in the type checker will we need to decide exactly which type it's an instance of.  Easy!

This might be a good change to make! It's a bit like in ClsInstDecl, you'll see that the instance cid_poly_ty is just a LHsSigType, i.e. not decomposed into which class it is.


So: my instinct is that the above would be Fine Thing.  Make a ticket?  Add these comments to give context?  Excecute?

Thanks

Simon

|  -----Original Message-----
|  From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Alan
|  & Kim Zimmerman
|  Sent: 20 December 2015 18:55
|  To: ghc-devs at haskell.org
|  Subject: Change from 7.10.3 to current master
|  
|  I am in the process of updating ghc-exactprint for current GHC master.
|  
|  One of the tests has the following in it
|  
|  -----------------------------
|  {-# LANGUAGE TypeOperators #-}
|  
|  type family (r1 :++: r2); infixr 5 :++:
|  type instance r :++: Nil = r
|  type instance r1 :++: r2 :> a = (r1 :++: r2) :> a
|  ------------------------------
|  
|  Current GHC master rejects this with
|  
|  /tmp/Foo.hs:5:15: error:
|      Malformed head of type or class declaration: r1 :++: r2 :> a
|  
|  Is this expected, or a bug?
|  
|  Alan
|  _______________________________________________
|  ghc-devs mailing list
|  ghc-devs at haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h
|  askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
|  devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c17b33d7be13045d
|  d141308d3096f2bc5%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=LGroqdv
|  nYFSxydfZFQydhi2N6lltWwi%2b4tt%2bM3LH0P0%3d


More information about the ghc-devs mailing list