Hi -

Part 1 of 2 - Monoid versus MonadPlus
===========================

I've just run into a troublesome question when trying to design a sequence class:

   class ISeq c a | c -> a where
        empty :: c
        single :: a -> c
        append :: c -> c -> c

However I've noticed that people sometimes separate the empty and append operations out as sequences with these ops form a Monoid therefore:

    class Monoid c => ISeq c a | c -> a where
        single :: a -> c

    -- now outside the class
    append :: ISeq c a => c -> c -> c
    append = mappend

    empty :: ISeq c a => c
    empty = mempty

Another option, is the Edison library which uses:

    class (Functor s, MonadPlus s) => Sequence s where

so here MonadPlus is used instead of Monoid to provide empty and append.
So I've got three main questions:

1) Did Edison choose MonadPlus just because this fitted in with the lack of multi-parameter typeclasses in H98?

2) Are there any reasons to prefer the Edison design over the MPTC design (apart from H98 compatibility) or vice versa?

3) Is it worth bothering to derive ISeq from Monoid (with the possible extra inefficiency of the indirection through the definitions for append = mappend etc or does the compiler completely optimize this out)?

and a fourth more long term question:

4) Would it be worth reconsidering the rules for top level names so that class methods could always be local to their class (ditto for value constructors and field names being local to their type constructor). For example it would be nice imho to be able to write:

     class Monoid c => ISeq c a | c -> a where
         length :: c -> Int


     f x y = Monoid/append x y -- or ISeq/append x y
     g x  = ISeq/length x

instead of having all names collide in the top level of a module, since at the moment it is difficult to think of method names that don't collide with the Prelude, and it's not nice to have to write "mempty" in place of "empty".

Part 2 of 2 - Monad versus Ancillary result type
================================

Another issue relates to left and right views of a sequence. If a sequence is non-empty, the left view is just the leftmost element and the rest of the sequence. The problem arises when the sequence is empty. In the Edison library, this is solved by returning a monadic value ie:

    lview :: Monad m => s a -> m (a, s a)

whereas from the paper "Finger trees: a simple general purpose data structure" by Ralf Hinze and Ross Paterson they use an ancillary data type to store the result of a view:

   data ViewL s a = NilL | ConsL a (s a)

   viewL :: FingerTree a -> ViewL FingerTree a

So my question here is: what's the best choice? I can see that the monadic version has the advantage that it could be used in do notation in cases where you expect the sequence to be non-empty, but has the disadvantage that it treats the empty sequence as something special (resulting in Monad/fail) and an extra indirection to find the components when the sequence is non-empty.

Anyway these are my main questions for now - any feedback appreciated ;-)

Thanks, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to