
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
On Fri, Oct 30, 2009 at 5:59 PM, Luke Palmer
wrote: On Fri, Oct 30, 2009 at 10:39 AM, Tom Davie
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe