[Haskell-cafe] The Applicative Functor Monad

Martijn van Steenbergen martijn at van.steenbergen.nl
Wed Dec 24 11:04:18 EST 2008


mappend :: (Monoid a) => a -> a -> a
(<*>) :: (Applicative f) => f (a -> b) -> f a -> f b

mappend takes two arguments of the same type and produces a value of 
that same type. <*>'s arguments and result types are all different. 
Therefore, I don't think you can just glue applicative functors together 
with <*> like you can do with mappend.

Ryan Ingram wrote:
> I think that there's no solution for your problem as stated, besides
> going with something like type-indexed monads, which leads you down
> the no-implicit-prelude path.
> 
> But to see one obvious reason why this is the case: can you tell me
> what the type of "returnAF" is?
> 
> Also, one of the monad laws is
>    m >>= return   =   m
> 
> I don't see how this can possibly be the case with the definition of
> bindAF you have given.
> 
>   -- ryan
> 
> On Tue, Dec 23, 2008 at 5:50 PM, Jeremy Shaw <jeremy at n-heptane.com> wrote:
>> Hello,
>>
>> I want to make a Monad which is almost exactly like the Writer monad,
>> except instead of using mappend to glue Monoids together, it uses <*>
>> to glue applicative functors together.
>>
>> Here is the code:
>>
>> import Control.Applicative
>> import Data.Monoid
>>
>> -- * Sample Implementation of the Writer Monad
>>
>> data Writer w a = Writer { runWriter :: (w, a) }
>>
>> instance (Monoid w) => Monad (Writer w) where
>>    return a = Writer (mempty, a)
>>    (>>=) = bindWriter
>>
>> bindWriter :: (Monoid w) => Writer w a -> (a -> Writer w b) -> Writer w b
>> bindWriter (Writer (w,a)) f =
>>    let (Writer (w', b)) = f a
>>    in Writer (w `mappend` w', b)
>>
>> -- * Sample Implementation of the Applicative Functor Monad
>>
>> data AF af a = AF { runAF :: (af, a) }
>>
>> bindAF :: (Applicative f) => AF (f (a -> b)) x -> (x -> AF (f a) y) -> AF (f b) y
>> bindAF (AF (f, x)) g =
>>    let (AF (a, y)) = g x
>>    in AF (f <*> a, y)
>>
>> -- instance (Applicative f) => Monad (AF (f ...
>>
>> As you can see, the similarity is striking. Alas, AF and bindAF do not
>> quite have the right type signatures to be used for an instance of the
>> Monad class. Is there some clever work-around I missing? (Aside from,
>> -fno-implicit-prelude).
>>
>> Thanks!
>>
>> - jeremy
>> _______________________________________________
>> 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



More information about the Haskell-Cafe mailing list