[Haskell-cafe] Capped lists and |append|

Felipe Lessa felipe.lessa at gmail.com
Fri Jan 8 20:57:00 EST 2010


[Disclaimer: I didn't really read all the thread from which this
data structure originated on Cafè =).]

On Fri, Jan 08, 2010 at 03:38:15PM -0800, John Millikin wrote:
> Since uploading, there's been a big problem pointed out to me
> regarding this structure, namely the possible definitions of |append|.
> Because the list terminus is itself a value, but isn't / shouldn't be
> the same type as the elements, either obvious implementation will drop
> it.
>
>     append :: CappedList cap a -> CappedList cap a -> CappedList cap a
>     append (Cap 0) (Cap 1) = -- either (Cap 0) or (Cap 1), but
> information has been lost

I don't think there is an easy solution here.  In a first
approach, what I would do would be to provide

  -- Returning one of the caps out of list.
  appendL :: CappedList cap  a -> CappedList cap' a -> (cap', CappedList cap a)
  appendR :: CappedList cap' a -> CappedList cap  a -> (cap', CappedList cap a)

  -- Discarding one of the caps.
  appendL_ :: CappedList cap a -> CappedList discarded a -> CappedList cap a
  appendR_ :: CappedList discarded a -> CappedList cap a -> CappedList cap a

  -- 'mappend'ing the caps
  appendM :: Monoid cap => CappedList cap a -> CappedList cap a -> CappedList cap a

and then define

  mappend = appendM

If we used appendL_ then we would violate Monoid's law that says
that

  mappend mempty x = x

And if we used appendR_ we would violate

  mappend x mempty = x

Of course, you would have to change your 'empty' package to
include the following law:

  "For every data type implementing Empty and Monoid,
   empty should be mempty."

This way you will guarantee that when using appendM

  Cap empty `mappend` Cap c = Cap c




Also, you may want to have CappedList an instance of
Control.Functor.Bifunctor from category-extras:

  -- Hask is a synonym for (->).
  instance Bifunctor CappedList Hask Hask Hask where
    bimap f g = foldr (Next . f) (Cap . g)

And, of course,

  import Data.Monoid (First(..), Last(..))
  appendL_ = bimap id getFirst . appendM . bimap id First
  appendR_ = bimap id getLast  . appendM . bimap id Last


Cheers,

--
Felipe.


More information about the Haskell-Cafe mailing list