The Applicative Functor Monad

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

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Dec 24, 2008 at 8:04 AM, Martijn van Steenbergen
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.
That's true, but it's not that hard to make a variant where you *can* glue things together. You just need to play with the types a tiny bit:
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
So, lets say the first argument to (<*>) has already been given. Now you need an (f a) for the second argument, and you want to be able to repeat this process. Well, something that is quite similar to having a value of type a is having a function that needs some additional value to give you a value of type a:
(<.>) :: Applicative f => f (a -> b) -> f (x -> a) -> f (x -> b) (<.>) = liftA2 (.)
It's now possible to define return and bind; first I am going to redefine AF slightly for reasons which will be clear soon.
newtype AF f x y a = AF { runAF :: (f (y -> x), a) }
returnAF :: Applicative f => a -> AF f x x a returnAF a = AF (pure id, a)
bindAF :: Applicative f => AF f z y a -> (a -> AF f y x b) -> AF f z x b bindAF m f = let (yz, a) = runAF m (xy, b) = runAF (f a) in AF (yz <.> xy, b)
Now, this type still isn't a monad; its type changes during bind. But it can be made into something close, a type-indexed monad:
class IndexedMonad m where ret :: a -> m x x a bind :: m x y a -> (a -> m y z b) -> m x z b
Given an indexed monad m, the remaining type arguments: m pre post val represent a precondition on the value, a post condition, and the held value. This class is very useful for threading *type-level* effects through a computation, just as regular monads are useful for threading value-level effects. (See Oleg's articles at http://okmij.org/ftp/Computation/monads.html#param-monad, or my implementation at http://hackage.haskell.org/packages/archive/Coroutine/0.1.0.0/doc/html/src/C...; there's a use of it in Control.Coroutine) AF is trivially an instance of this type:
instance Applicative f => IndexedMonad (AF f) where ret = returnAF bind = bindAF
You can then come up with some simple observation functions:
evalAF :: Applicative f => AF f x () a -> (f x, a) evalAF = runAF >>> first (($ ()) <$>)
The dual is also potentially useful, where you use (flip (<.>)) instead. I'm not sure if this is useful for Jeremy's goal, but it's an interesting direction to explore. -- ryan
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Jeremy Shaw
-
Martijn van Steenbergen
-
Ryan Ingram