[GHC] #11307: Regresssion: parsing type operators

GHC ghc-devs at haskell.org
Mon Dec 28 18:58:29 UTC 2015


#11307: Regresssion: parsing type operators
-------------------------------------+-------------------------------------
           Reporter:  alanz          |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.0.1
          Component:  Compiler       |           Version:  7.11
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 GHC 7.10.3 will parse (but not type-check) the following

 {{{#!hs
 {-# LANGUAGE TypeOperators #-}

 type family (r1 :++: r2); infixr 5 :++:
 type instance r :++: Nil = r
 type instance r1 :++: r2 :> a = (r1 :++: r2) :> a
 }}}

 Current master (c7830bdb14e0a85a78617314156d101155fdf7aa) fails with

 {{{#!hs
 /tmp/Foo.hs:5:15: error:
     Malformed head of type or class declaration: r1 :++: r2 :> a
 }}}

 @simonpj comment on ghc-devs mailing list

 > `|  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:
 >
 > {{{#!hs
 > 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
 >
 > {{{#!hs
 > 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.
 >

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


More information about the ghc-tickets mailing list