[Haskell-cafe] Applicative but not Monad

David Menendez dave at zednenem.com
Fri Oct 30 13:32:59 EDT 2009


On Fri, Oct 30, 2009 at 12: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.

This works fine for infinite lists, since an infinite list is
equivalent to Nat -> a.

With finite lists, this implementation hits problems with calling head
on empty lists. If I rewrite it to avoid that problem, the
associativity law fails.

tail' [] = []
tail' (_:as) = as

diag ((a:_):bs) = a : diag (map tail' bs)
diag _ = []

bind :: [Int] -> (Int -> [Int]) -> [Int]  -- monomorphic for QuickCheck
bind m f = diag (map f m)

Prelude Test.QuickCheck Test.QuickCheck.Function> quickCheck $ \m
(Function _ f) (Function _ g) -> bind (bind m f) g == bind m (\x ->
bind (f x) g)
*** Failed! Falsifiable (after 16 tests and 23 shrinks):
[1,0]
{0 -> [-13,0], 1 -> [0]}
{-13 -> [], 0 -> [0,0]}

The left side is [0,0], the right side is [0].

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list