Add Applicative instances for MTL types

Hello, In a project of mine I needed an Applicative instance for Identity and noticed it didn't exist. So I decided to add Applicative (and Alternative instances where possible) for all MTL types. When I was about to submit a library proposal I saw there already existed one. So I added my patch to that ticket. My patch I different in that my Applicative instances don't require a Monad constraint. This also means that most Functor instances now also depend on Applicative rather than on Monad. See the ticket for the details: http://hackage.haskell.org/trac/ghc/ticket/2316 Discussion period: 5 weeks (taking the holidays into account) This is the old thread about this proposal: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/9140/focus=9154 regards, Bas

On Sat, Dec 20, 2008 at 7:09 PM, Bas van Dijk
Hello,
In a project of mine I needed an Applicative instance for Identity and noticed it didn't exist. So I decided to add Applicative (and Alternative instances where possible) for all MTL types.
When I was about to submit a library proposal I saw there already existed one. So I added my patch to that ticket.
My patch I different in that my Applicative instances don't require a Monad constraint. This also means that most Functor instances now also depend on Applicative rather than on Monad.
See the ticket for the details:
http://hackage.haskell.org/trac/ghc/ticket/2316
Discussion period: 5 weeks (taking the holidays into account)
This is the old thread about this proposal:
http://thread.gmane.org/gmane.comp.lang.haskell.libraries/9140/focus=9154
regards,
Bas
getCurrentTime >>= \c -> print (realToFrac (diffUTCTime c (readTime defaultTimeLocale "%c" "Sat Dec 20 19:09:00 2008")) / 60 / 60 / 24 / 7) ~ 3.5 weeks ago I sended this previous message ;-) Can we have some discussion about my patch? As listed in the ticket I have these questions: * Does it make sense adding Applicative counterparts to the Monad* classes? For example: o class Applicative f => ApplicativeError e g | f -> e where ... o class Applicative f => ApplicativeState s f | f -> s where ... o class Applicative f => ApplicativeReader r f | f -> r where ... o class (Applicative f, Monoid w) => ApplicativeWriter w f | f -> w where ... o class (Monoid w, ApplicativeReader r f, ApplicativeWriter w f, ApplicatveState s f) => ApplicativeRWS r w s f | f -> r, f -> w, f -> s where ... o class (Applicative m) => ApplicativeCont m where ... o class ApplicativeTrans t where lift :: Applicative f => f a -> t f a * Can we get rid of the Monad and MonadPlus constraints in the Applicative and Alternative instances for StateT and RWST? Thanks, Bas

On Wed, 2009-01-14 at 13:54 +0100, Bas van Dijk wrote:
On Sat, Dec 20, 2008 at 7:09 PM, Bas van Dijk
wrote: Hello,
In a project of mine I needed an Applicative instance for Identity and noticed it didn't exist. So I decided to add Applicative (and Alternative instances where possible) for all MTL types.
When I was about to submit a library proposal I saw there already existed one. So I added my patch to that ticket.
My patch I different in that my Applicative instances don't require a Monad constraint. This also means that most Functor instances now also depend on Applicative rather than on Monad.
See the ticket for the details:
http://hackage.haskell.org/trac/ghc/ticket/2316
Discussion period: 5 weeks (taking the holidays into account)
This is the old thread about this proposal:
http://thread.gmane.org/gmane.comp.lang.haskell.libraries/9140/focus=9154
~ 3.5 weeks ago I sended this previous message ;-)
Can we have some discussion about my patch?
Yes please! I think we all want all the MTL monads to be instances of Applicative. I'm not sure if I am qualified to comment on the details of the patch however. If we don't get enough reviewers, we should try pinging people, like the original MTL authors, authors of similar mtl-esque packages etc.
As listed in the ticket I have these questions:
* Does it make sense adding Applicative counterparts to the Monad* classes? For example: o class Applicative f => ApplicativeError e g | f -> e where ... o class Applicative f => ApplicativeState s f | f -> s where ... o class Applicative f => ApplicativeReader r f | f -> r where ... o class (Applicative f, Monoid w) => ApplicativeWriter w f | f -> w where ... o class (Monoid w, ApplicativeReader r f, ApplicativeWriter w f, ApplicatveState s f) => ApplicativeRWS r w s f | f -> r, f -> w, f -> s where ... o class (Applicative m) => ApplicativeCont m where ... o class ApplicativeTrans t where lift :: Applicative f => f a -> t f a
That sounds like it wants to be an independent proposal. Duncan

On Wed, Jan 14, 2009 at 01:54:47PM +0100, Bas van Dijk wrote:
On Sat, Dec 20, 2008 at 7:09 PM, Bas van Dijk
wrote: In a project of mine I needed an Applicative instance for Identity and noticed it didn't exist. So I decided to add Applicative (and Alternative instances where possible) for all MTL types.
When I was about to submit a library proposal I saw there already existed one. So I added my patch to that ticket.
My patch I different in that my Applicative instances don't require a Monad constraint. This also means that most Functor instances now also depend on Applicative rather than on Monad.
See the ticket for the details:
The Functor instances could depend on Functor rather than Applicative. Even though Applicative is not a superclass of Monad, I think we ought to ensure that the instances are compatible. That is, if an Applicative is also a Monad, then we should have pure = return and (<*>) = ap. This fails for your ErrorT instance: ap runs the second computation only if the first succeeded, while (<*>) runs them both before checking for errors. It needs a Monad constraint (like StateT), though not an Error constraint.
* Can we get rid of the Monad and MonadPlus constraints in the Applicative and Alternative instances for StateT and RWST?
I don't think so: you need part of the value generated by the first computation, namely the state (inside the f), to construct the second one. You can do that in a Monad, but not in an Applicative. At Henning Thielemann's request, I've recently put up on hackage a restructuring of the mtl into three packages, to provide three different interfaces to the same monad transformers: transformers: a Haskell 98 package with the MonadTrans class, concrete monad transformers, operations and liftings. monads-fd: multi-parameter monad classes using functional dependencies, with instances for these transformers. (Almost backward-compatible with the mtl package.) monads-tf: monad classes using type families, with instances for these transformers. The first one includes Applicative instances like these.

Thanks for the reply.
On Wed, Jan 14, 2009 at 2:50 PM, Ross Paterson
The Functor instances could depend on Functor rather than Applicative.
Ok you mean like: instance Functor m => Functor (ErrorT e m) where fmap f = ErrorT . fmap (fmap f) . runErrorT instance Functor m => Functor (ListT m) where fmap f = ListT . fmap (fmap f) . runListT instance (Functor m) => Functor (ReaderT r m) where fmap f = ReaderT . fmap (fmap f) . runReaderT instance (Functor m, Monoid w) => Functor (WriterT w m) where fmap f = WriterT . fmap (\(x, w) -> (f x, w)) . runWriterT I could update the patch with this or I can create a separate ticket for it. What do you think? The latter instance indicates that WriterT should have its inner tuple reversed: newtype WriterT w m a = WriterT { runWriterT :: m (a, w) } --> newtype WriterT w m a = WriterT { runWriterT :: m (w, a) } Because then we can write the more consistent: instance (Functor m, Monoid w) => Functor (WriterT w m) where fmap f = WriterT . fmap (fmap f) . runWriterT But this is probably a ticket on it own.
Even though Applicative is not a superclass of Monad, I think we ought to ensure that the instances are compatible. That is, if an Applicative is also a Monad, then we should have pure = return and (<*>) = ap.
Yes, but what if an Applicative isn't a Monad? We can't have two instances because they overlap: instance Monad m => Applicative (ErrorT e m) where pure = return (<*>) = ap instance Applicative m => Applicative (ErrorT e m) where pure = ErrorT . pure . pure ef <*> ex = ErrorT $ liftA2 (<*>) (runErrorT ef) (runErrorT ex) I think the latter is more useful because there are more Applicatives than Monads out there.
This fails for your ErrorT instance: ap runs the second computation only if the first succeeded, while (<*>) runs them both before checking for errors. It needs a Monad constraint (like StateT), though not an Error constraint.
But isn't 'runErrorT ex' only evaluated when 'runErrorT ef' returns 'Right f' because of lazy evaluation?
* Can we get rid of the Monad and MonadPlus constraints in the Applicative and Alternative instances for StateT and RWST?
I don't think so: you need part of the value generated by the first computation, namely the state (inside the f), to construct the second one. You can do that in a Monad, but not in an Applicative.
Yes I thought so.
At Henning Thielemann's request, I've recently put up on hackage a restructuring of the mtl into three packages, to provide three different interfaces to the same monad transformers:
transformers: a Haskell 98 package with the MonadTrans class, concrete monad transformers, operations and liftings. monads-fd: multi-parameter monad classes using functional dependencies, with instances for these transformers. (Almost backward-compatible with the mtl package.) monads-tf: monad classes using type families, with instances for these transformers.
The first one includes Applicative instances like these.
Yes I saw it. Very nice! What is the long term goal of these libraries? Are they intended to replace mtl one day?

On Wed, Jan 14, 2009 at 12:16 PM, Bas van Dijk
On Wed, Jan 14, 2009 at 2:50 PM, Ross Paterson
wrote: Even though Applicative is not a superclass of Monad, I think we ought to ensure that the instances are compatible. That is, if an Applicative is also a Monad, then we should have pure = return and (<*>) = ap.
Yes, but what if an Applicative isn't a Monad?
We can't have two instances because they overlap:
instance Monad m => Applicative (ErrorT e m) where pure = return (<*>) = ap
instance Applicative m => Applicative (ErrorT e m) where pure = ErrorT . pure . pure ef <*> ex = ErrorT $ liftA2 (<*>) (runErrorT ef) (runErrorT ex)
I think the latter is more useful because there are more Applicatives than Monads out there.
The latter is just normal composition of applicative functors, in this case "Comp m (Either e)". newtype Comp f g x = Comp { unComp :: f (g x) } instance (Functor f, Functor g) => Functor (Comp f g) where fmap f = Comp . fmap (fmap f) . unComp instance (Applicative f, Applicative g) => Applicative (Comp f g) where pure = Comp . pure . pure f <*> x = Comp $ liftA2 (<*>) (unComp f) (unComp x) Given how easy it is to combine different functors and applicative functors, there isn't very much need for (applicative) functor transformers. I agree with Ross, the functor and applicative instances for monad transformers should satisfy these laws: fmap = liftM pure = return (<*>) = ap
This fails for your ErrorT instance: ap runs the second computation only if the first succeeded, while (<*>) runs them both before checking for errors. It needs a Monad constraint (like StateT), though not an Error constraint.
But isn't 'runErrorT ex' only evaluated when 'runErrorT ef' returns 'Right f' because of lazy evaluation?
No, in your definition, the effects of the transformed applicative
functor are evaluated regardless of the error condition.
Try this code:
runState (runErrorT (throwError "!" <*> put False)) True
The first definition of <*> returns (Left "!", True). The second
returns (Left "!", False).
--
Dave Menendez

On Wed, Jan 14, 2009 at 7:56 PM, David Menendez
No, in your definition, the effects of the transformed applicative functor are evaluated regardless of the error condition.
Try this code:
runState (runErrorT (throwError "!" <*> put False)) True
The first definition of <*> returns (Left "!", True). The second returns (Left "!", False).
I see it now. Thanks for correcting me. Then we should consider the first patch by Spencer Janssen again which satisfies these laws: pure = return (<*>) = ap Thanks, Bas

When trying to perform some tests with StrictCheck, I found that the monads from the 'transformers' package don't have Data instances. Can they be provided while keeping 'transformers' Haskell 98 and avoiding orphan instances?

On Thu, Jan 15, 2009 at 10:46:46PM +0100, Henning Thielemann wrote:
When trying to perform some tests with StrictCheck, I found that the monads from the 'transformers' package don't have Data instances. Can they be provided while keeping 'transformers' Haskell 98 and avoiding orphan instances?
They could be provided for GHC only using ifdef'd deriving clauses.

On Thu, Jan 15, 2009 at 10:46:46PM +0100, Henning Thielemann wrote:
When trying to perform some tests with StrictCheck, I found that the monads from the 'transformers' package don't have Data instances. Can they be provided while keeping 'transformers' Haskell 98 and avoiding orphan instances?
The Typeable and Data instances will be non-trivial, as they can't be derived for higher-order type constructors.
participants (5)
-
Bas van Dijk
-
David Menendez
-
Duncan Coutts
-
Henning Thielemann
-
Ross Paterson