[Haskell-cafe] Applicative but not Monad

Job Vranish jvranish at gmail.com
Fri Oct 30 17:06:18 EDT 2009


If you use a monad instance for ZipLists as follows:

instance Monad ZipList where
  return x = ZipList $ repeat x
  ZipList [] >>= _ = ZipList []
  xs >>= f = diagonal $ fmap f xs

(where diagonal pulls out the diagonal elements of a ziplist of ziplists)

It will satisfy all the monad laws _except_ when the function f (in xs >>=
f) returns ziplists of different length depending on the value passed to it.
If f always returns lists of the same length, the monad laws should still
hold even if the lists are not infinite in length.


I have a fixed size list type (http://github.com/jvranish/FixedList) that
uses an instance like this and it always satisfies the monad laws since the
length of the list can be determined from the type so f is forced to always
return the same size of list.

I hope that helps things make sense :)

- Job



On Fri, Oct 30, 2009 at 1:33 PM, Yusaku Hashimoto <nonowarn at gmail.com>wrote:

> Thanks for fast replies! Examples you gave explain why all
> Applicatives are not Monads to me.
>
> And I tried to rewrite Bob's Monad instance for ZipList with (>>=).
>
> import Control.Applicative
>
> instance Monad ZipList where
>  return = ZipList . return
>  (ZipList []) >>= _ = ZipList []
>  (ZipList (a:as)) >>= f = zlHead (f a) `zlCons` (ZipList as >>= f)
>
> zlHead :: ZipList a -> a
> zlHead (ZipList (a:_)) = a
> zlCons :: a -> ZipList a -> ZipList a
> zlCons a (ZipList as) = ZipList $ a:as
> zlTail :: ZipList a -> ZipList a
> zlTail (ZipList (_:as)) = ZipList as
>
> I understand if this instance satisfies the laws, we can replace <$>
> with `liftM` and <*> and `ap`. And I found a counterexample (correct
> me if I'm wrong).
>
> *Main Control.Monad> getZipList $ (*) <$> ZipList [1,2] <*> ZipList [3,4,5]
> [3,8]
> *Main Control.Monad> getZipList $ (*) `liftM` ZipList [1,2] `ap` ZipList
> [3,4,5]
> [3,6]
>
> Cheers,
> -~nwn
>
> On Sat, Oct 31, 2009 at 2:06 AM, Tom Davie <tom.davie at gmail.com> wrote:
> > On Fri, Oct 30, 2009 at 5:59 PM, Luke Palmer <lrpalmer at gmail.com> wrote:
> >>
> >> On Fri, Oct 30, 2009 at 10:39 AM, Tom Davie <tom.davie at gmail.com>
> wrote:
> >> > Of note, there is a sensible monad instance for zip lists which I
> >> > *think*
> >> > agrees with the Applicative one, I don't know why they're not monads:
> >> > instance Monad (ZipList a) where
> >> >   return = Ziplist . return
> >> >   join (ZipList []) = ZipList []
> >> >   join (ZipList (a:as)) = zlHead a `zlCons` join (map zlTail as)
> >>
> >> IIRC, that doesn't satisfy the associativity law, particularly when
> >> you are joining a list of lists of different lengths.  2 minutes of
> >> experimenting failed to find me the counterexample though.
> >
> > Cool, thanks Luke, that explains why this is available in Stream, but not
> in
> > ZipList too.
> > Bob
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091030/a21584f9/attachment.html


More information about the Haskell-Cafe mailing list