At 11:02 +0000 1999/05/03, Wolfram Kahl wrote:
>With respect to the new RULES mechanism presented by
>Simon Peyton Jones (Thu, 22 Apr 1999),
>Carsten Schultz <[EMAIL PROTECTED]> writes
> > [...]
> > > And what about algebraic simplification? Say,
> > The same applies to our beloved monads.
> > The compiler could be told about the monad laws.
>
>Somebody else (Olaf Chitil?) already remarked that most ``Monads'' aren't.
>
>So to be more consistent,
>how about changing the current class Monad into
>(motivation see signature ;-):
>
>> class HasMonadOps m where
>>   return :: a -> m a
>>   >>= :: m a -> (a -> m b) -> m b
>>   ...
>
>and introduce:
>
>> class (HasMonadOps m) => Monad m where
>> {-# RULES
>>      "Monad-rightId" forall f.    f >>= return    =  f
>>       "Monad-leftId"  forall f,x.  return x >>= f  =  f x
>>       ...
>>  #-}
>
>Even if some still will not like this, would it be within
>the scope of the current RULES mechanism?

For expressing algebraic relations, I think one can use universal algebra
by factoring through the free universal algebra of a particular set of
relations. For example, if one wants to state that a binary operator is
commutative, one can say that is should be defined on the symmetric set of
order two, that is the set of pairs (x, y) where (x, y) is equivalent to
(y, x). If one wants to say that an operator is associative (with
identity), then it factors through the free monoid, or list of the algebra
itself, so this amount to saying that it is defined on the set of lists.
And so on.

For monads, you might perhaps try doing the same thing, by introducing a
concept of "universal categories" and factorizing through them.

Otherwise, I think that Haskell need a better way to more exactly describe
what the object are. For example, a group G is formally a quadruple (G, e,
*, -1; R), where e is an identity, * multiplication, -1 an inverse, and R
some relations. Those details are wholly inexpressible in Haskell as
matters now stand. The same thing applies to monads, which are also known
as triples (plus relations). It is not possible to express in Haskell the
fact even that monads are triples, even less that they have some additional
monad relations to fulfill.

  Hans Aberg
                  * Email: Hans Aberg <mailto:[EMAIL PROTECTED]>
                  * Home Page: <http://www.matematik.su.se/~haberg/>
                  * AMS member listing: <http://www.ams.org/cml/>




Reply via email to