infix type constructors

Simon Peyton-Jones simonpj@microsoft.com
Thu, 16 May 2002 07:24:10 -0700


Chris

I'm slowly getting around to this.   Design questions:

(A) I think it would be a good compromise to declare that operators
like "+" are type *constructors* not type *variables*.  So=20
	S+T
would be a type.  That's slightly inconsistent with value variables,
but it's jolly useful.  So only alphabetic things would be type
variables.
It's very clunky having to write
	S :+: T

(B) One wants to declare fixities for type constructors, and that
gets them mixed up with their value counterparts.  My suggestion:
disamiguate with a compulsory 'type' keyword
	infix 6 type +
	infixl 9 type *

Or should it be 'data'?  Or should it depend how + and * are declared?

(C) The other place they can get mixed up is in import and export
lists.  I can think of several solutions

(i) 	module Foo( + ) where ...
    means export the type constructor (+); currently illegal in H98
	module Foo( (+) ) where ...
   means export the variable (+).

This seems a bit of a hack.

(ii) Use the 'type' keyword, rather like 'module':
	module Foo( type + ) where=20
		data a+b =3D A a | B b
or
	module Foo( type +(A,B) ) where
		data a+b =3D A a | B b

[I think 'type' is better than 'data' because we want to hide the=20
distinction in an export list.... or do you think we should use the=20
same keyword as the one in the defn?]

Similarly on import lists.


(D) I suppose one might want infix notation for type variables too:

	data T a =3D T (Int `a` Int)

but maybe that's going too far?

Simon

| -----Original Message-----
| From: Okasaki, C. DR EECS [mailto:Christopher.Okasaki@usma.edu]=20
| Sent: 03 May 2002 14:09
| To: 'glasgow-haskell-users@haskell.org'
| Subject: infix type constructors
|=20
|=20
| I'm not sure how long this has been implemented in GHC,
| but I just noticed that infix type constructors are allowed,
| as in
|=20
|   data a :- b =3D ...
|=20
| The syntactic asymmetry between type constructors and
| data contructors has bothered me for a while, so this
| is a welcome change!  However, this syntax seems to
| be supported for "data" and "newtype" declarations,
| but not for "type" declarations.  For example,
|=20
|   type a :- b =3D ...
|=20
| does not seem to be allowed.  Is there a reason for this?
| Or was it just an oversight?
|=20
| -- Chris
| _______________________________________________
| Glasgow-haskell-users mailing list=20
| Glasgow-haskell-users@haskell.org=20
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
|=20