[Haskell] Proposal: unification of style of function/data/type/class definitions

Bulat Ziganshin bulat.ziganshin at gmail.com
Sun Sep 10 02:08:22 EDT 2006


Hello haskell,

we can consider functions as value-to-value mappings,
'type' definitions as type-to-type mappings,
'data' and 'class' as type-to-value mappings

but their syntax are different. functions has the most convenient syntax:

f patterns_for_parameters | guards = result

we can improve readability of various declarations by using the same
scheme:

class Monad m | Functor m, Monoid m where ...

instance Monad (WriterT m) | Monad m where ...

data EncodedStream m h | Monad m, Stream m h = ...

sequence :: [m a] -> m [a] | Monad m

By moving "guards" to the right side we will get more readable
definitions where most important information (type/class name and
shape of parameters) are written first and less important after


Even more unification can be applied to GADT-style definitions and
definitions of type/data families. The following is a well-known GADT
example rewritten in "functional" style:

data Expr t           = If (Expr Bool) (Expr t) (Expr t)
     Expr Int         = Lit Int
     Expr Bool | Eq t = Eq (Expr t) (Expr t)

And next is the example of type function which selects optimal array
representation depending on type of its elements:

type Arr Bool           = BitVector
     Arr u | Unboxed u  = UArray u
     Arr (a,b)          = (Arr a, Arr b)
     Arr a              = Array a

where Unboxed is a class whose instances are unboxable types.

We can also allow to use as guards partial type functions, i.e.
functions that defined only for subset of type parameters:

type SeqElem [a]          = a
     SeqElem (Sequence a) = a
     SeqElem (Array a)    = a

data Collection c | SeqElem c  = Coll c


     
In general, any type-level computation can use:

* in patterns - any type constructors declared in 'data' statements
                and their saturated synonyms
* in guards - classes (and partial type functions)
* at the right side - any type constructors and type functions
                      declared with data/type statements, including
                      associated types/type synonyms

Please note that ordinal functions dispatch (via pattern-matching) on
the data constructors which appear at the right side of 'data'
definitions while type-level computations dispatch (again via
pattern-matching) on type constructors which appears on left side of
the same 'data' definitions


ps: although this idea seems more appropriate for haskell' committee, i
propose to use it just now, starting from implementation of different
syntax for GADTs


-- 
Best regards,
 Bulat                          mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell mailing list