Dear GHC users

As part of beefing up the kind system, we plan to implement the "Type 
operators" proposal for Haskell Prime
http://hackage.haskell.org/trac/haskell-prime/wiki/InfixTypeConstructors

GHC has had type operators for some kind, so you can say
        data a :+: b = Left a | Right b
but you can only do that for operators which start with ":".

As part of the above wiki page you can see the proposal to broaden this to ALL 
operators, allowing
        data a + b = Left a | Right b

Although this technically inconsistent the value page (as the wiki page 
discussed), I think the payoff is huge. (And "A foolish consistency is the 
hobgoblin of little minds", Emerson)


This email is (a) to highlight the plan, and (b) to ask about flags.  Our 
preferred approach is to *change* what -XTypeOperators does, to allow type 
operators that do not start with :.  But that will mean that *some* (strange) 
programs will stop working. The only example I have seen in tc192 of GHC's test 
suite
        {-# LANGUAGE TypeOperators #-}
        comp :: Arrow (~>) => (b~>c, c~>d)~>(b~>d)
      comp = arr (uncurry (>>>))        

Written more conventionally, the signature would look like
        comp :: Arrow arr => arr (arr b c, arr c d) (arr b d)
      comp = arr (uncurry (>>>))
or, in infix notation
        {-# LANGUAGE TypeOperators #-}
        comp :: Arrow arr => (b `arr` c, c `arr` d) `arr` (b `arr` d)
      comp = arr (uncurry (>>>))

But tc192 as it stands would become ILLEGAL, because (~>) would be a type 
*constructor* rather than (as now) a type *variable*.  Of course it's easily 
fixed, as above, but still a breakage is a breakage.

It would be possible to have two flags, so as to get
  - Haskell 98 behaviour
  - Current TypeOperator behaviuor
  - New TypeOperator behaviour
but it turns out to be Quite Tiresome to do so, and I would much rather not.  
Can you live with that? 


http://chrisdone.com/posts/2010-10-07-haskelldb-and-typeoperator-madness.html


_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to