I have a couple of type constructors I would love to make instances of
the Monad class but which I can not.  I would like to know if I have
just missed something, if I am trying to do something silly, or if they
in fact suggest improvements on the existing class system.

The first example is the archetypical state monad State->(State,-).  I
can write (,) and (->) for the pair and function constructors but I do
not see any way to combine them.  Of course I could wrap
State->(State,_) in a newtype decleration:

  newtype StateMonad a = StateMonad(State->(State,a))

But this is cumbersome if I want to mix monadic style with
traditional style, ie. if I want finer control over the flow of the
state:

  f s = ...
        where
          (s1,n) = (do a<-...
                       b<-...
                       return ...) s
          (s2,m) = ... s

Some might consider mixing bad style, and I tend to agree when the
monads in question are of a more complex nature, but in the case of this
simple state monad it is conceptually easy to grasp what the monadic
operations do.

A way to make State->(State,-) an instance of the Monad class is to
allow type synonyms in instance declerations:

  type StateMonad a = State->(State,a)
  instance Monad StateMonad where
    ...

This is not possible in the current version of Haskell and in the
documentation of the Haskell extension by Simon Peyton Jones titled
Multi-parameter type classes in GHC

  <http://research.microsoft.com/Users/simonpj/Haskell/multi-param.html>

which allows type synonyms in instance declerations, it is mentioned
that "...type synonyms must be fully applied".  I think the above
example is a valid objection to this.

The other example of something that I want to declare as a monad, but
which 
I can not is this:  Consider a type of collection of some sort that
requires
the types of the elements to be instances of some specific class.  This
could be a hash-table that requires that the type of the elements is in
a class that has an operation associating a hash-value with the
elements.  My example, though, is a type of sorted lists:

  newtype Ord a=>SList a = SList[a]

This requires that the members are ordered.  This type supports a fast
and easy union operation:

  union :: Ord a=>SList a->SList a->SList a

and other such operations.  As SList is almost a list it would be nice
to make it a Monad-instance to allow monad-comprehensions, and indeed it
is possible to define the monadic operations for it:

  myreturn :: Ord a=>a->SList a
  myreturn a = SList[a]
  mybind :: (Ord a,Ord b)=>SList a->(a->SList b)->SList b
  mybind (SList a) f = foldr union (SList[]) (map f a)
 
except that they have type constraints.  This makes it impossible to
make SList an instance of Monad.  Still, I think it makes sense to
regard SList as a monad, but I am much more unsure of how this could be
obtained.  Maybe multi-parameter type classes can save the day (eg. a
class like MonadOver m a instead of Monad m).

Any comments on how to do what I want, why I should not be allowed to do
what I want, etc?

Oh, and another point.  Why has list comprehensions reverted to be list
comprehensions and not monad comprehensions in Haskell 98?  I think it
makes great sense when the monad in question is a collection of some
sort, but it can also be convenient for other kinds of monads as well.


Michael Florentin Nielsen ([EMAIL PROTECTED])

Reply via email to