Lifting IO actions into Applicatives

I'm wondering if anyone's run into this problem before, and if there's a common solution. In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time: data Blog = Blog Title UTCTime Contents myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm The question is: what goes in something? Its type has to be: something :: Form UTCTime Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as: something = lift $ liftIO getCurrentTime This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are: 1. Has anyone else run into this issue? 2. Is there an existing solution out there? Michael [1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T...

It's not a solution per se, but it seems to me that there's no need for the
Monad superclass constraint on MonadIO. If that were removed, we could
just have
class LiftIO t where
liftIO :: IO a -> t a
and it would Just Work.
On Tue, Oct 1, 2013 at 1:58 AM, Michael Snoyman
I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are:
1. Has anyone else run into this issue? 2. Is there an existing solution out there?
Michael
[1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, 1 Oct 2013 02:21:13 -0500, John Lato
It's not a solution per se, but it seems to me that there's no need for the Monad superclass constraint on MonadIO. If that were removed, we could just have
class LiftIO t where liftIO :: IO a -> t a
and it would Just Work.
One concern with this is that it's not exactly clear what the semantics are on LiftIO (is liftIO a >> liftIO b equal to liftIO (a >> b) or not?) and the interaction between LiftIO and Applicative/Monad would have to be some sort of ugly ad-hoc law like we have with Bounded/Enum etc. Furthermore, you might end up specifying a lot of ‘redundant’ constraints like (Monad m, LiftIO m) that way, just a thing to keep in mind.

On Tue, Oct 01, 2013 at 09:29:00AM +0200, Niklas Haas wrote:
On Tue, 1 Oct 2013 02:21:13 -0500, John Lato
wrote: It's not a solution per se, but it seems to me that there's no need for the Monad superclass constraint on MonadIO. If that were removed, we could just have
class LiftIO t where liftIO :: IO a -> t a
and it would Just Work.
One concern with this is that it's not exactly clear what the semantics are on LiftIO (is liftIO a >> liftIO b equal to liftIO (a >> b) or not?) and the interaction between LiftIO and Applicative/Monad would have to be some sort of ugly ad-hoc law like we have with Bounded/Enum etc.
What is this 'ad-hoc law' you are talking about ?
Furthermore, you might end up specifying a lot of ‘redundant’ constraints like (Monad m, LiftIO m) that way, just a thing to keep in mind. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Jose Antonio Lopes Ganeti Engineering Google Germany GmbH Dienerstr. 12, 80331, München Registergericht und -nummer: Hamburg, HRB 86891 Sitz der Gesellschaft: Hamburg Geschäftsführer: Graham Law, Christine Elizabeth Flores Steuernummer: 48/725/00206 Umsatzsteueridentifikationsnummer: DE813741370

On Tue, Oct 01, 2013 at 09:29:00AM +0200, Niklas Haas wrote:
On Tue, 1 Oct 2013 02:21:13 -0500, John Lato
wrote: It's not a solution per se, but it seems to me that there's no need for the Monad superclass constraint on MonadIO. If that were removed, we could just have
class LiftIO t where liftIO :: IO a -> t a
and it would Just Work.
One concern with this is that it's not exactly clear what the semantics are on LiftIO (is liftIO a >> liftIO b equal to liftIO (a >> b) or not?) and the interaction between LiftIO and Applicative/Monad would have to be some sort of ugly ad-hoc law like we have with Bounded/Enum etc.
Shouldn't it be an *Applicative* constraint? class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a and require that liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter. Tom

* Tom Ellis
On Tue, Oct 01, 2013 at 09:29:00AM +0200, Niklas Haas wrote:
On Tue, 1 Oct 2013 02:21:13 -0500, John Lato
wrote: It's not a solution per se, but it seems to me that there's no need for the Monad superclass constraint on MonadIO. If that were removed, we could just have
class LiftIO t where liftIO :: IO a -> t a
and it would Just Work.
One concern with this is that it's not exactly clear what the semantics are on LiftIO (is liftIO a >> liftIO b equal to liftIO (a >> b) or not?) and the interaction between LiftIO and Applicative/Monad would have to be some sort of ugly ad-hoc law like we have with Bounded/Enum etc.
Shouldn't it be an *Applicative* constraint?
class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a
and require that
liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x
Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter.
Agreed, this makes perfect sense. It simply says that liftIO is an applicative homomorphism. Roman

On Tue, Oct 01, 2013 at 12:11:23PM +0300, Roman Cheplyaka wrote:
Shouldn't it be an *Applicative* constraint?
class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a
and require that
liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x
Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter.
Agreed, this makes perfect sense. It simply says that liftIO is an applicative homomorphism.
Indeed. A related question is whether, when m and m' are monads, an applicative homomorphism between m and m' is automatically a monad homomorphism. That seems important in determining if one typeclass is actually enough. In fact we could go crazy and define class Functor f => FunctorIO f where liftIO :: IO a -> f a and require that liftIO . fmap f = fmap f . liftIO i.e. essentially that liftIO is a natural transformation between IO and f. I don't know whether there are simpler sufficient conditions that allow one to determine that such an instance is also an applicative and monad morphism. Tom

From what you've said, it sounds like you can already write:
serverSide :: IO a -> Form a This seems elegant enough to me for your needs. Just encourage it as an idiom specific to Forms. myBlogForm = Blog <$> titleForm <*> serverSide getCurrentTime <*> contentsForm Could you abstract `serverSide` out into a typeclass, such as ApplicativeIO? Sure. but why bother? The point is, you've got the specialization you need already. -- Dan Burton On Tue, Oct 1, 2013 at 1:20 AM, Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Tue, Oct 01, 2013 at 09:29:00AM +0200, Niklas Haas wrote:
On Tue, 1 Oct 2013 02:21:13 -0500, John Lato
wrote: It's not a solution per se, but it seems to me that there's no need for the Monad superclass constraint on MonadIO. If that were removed, we could just have
class LiftIO t where liftIO :: IO a -> t a
and it would Just Work.
One concern with this is that it's not exactly clear what the semantics are on LiftIO (is liftIO a >> liftIO b equal to liftIO (a >> b) or not?) and the interaction between LiftIO and Applicative/Monad would have to be some sort of ugly ad-hoc law like we have with Bounded/Enum etc.
Shouldn't it be an *Applicative* constraint?
class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a
and require that
liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x
Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter.
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Burton wrote:
From what you've said, it sounds like you can already write:
serverSide :: IO a -> Form a
This seems elegant enough to me for your needs. Just encourage it as an idiom specific to Forms.
myBlogForm = Blog <$> titleForm <*> serverSide getCurrentTime <*> contentsForm
Could you abstract `serverSide` out into a typeclass, such as ApplicativeIO? Sure. but why bother? The point is, you've got the specialization you need already.
In my opinion, this is the nicest answer to the original question about yesod forms. But the more general question that it led to is an interesting and important one. -Yitz

On Tue, Oct 1, 2013 at 12:15 PM, Dan Burton
From what you've said, it sounds like you can already write:
serverSide :: IO a -> Form a
This seems elegant enough to me for your needs. Just encourage it as an idiom specific to Forms.
myBlogForm = Blog <$> titleForm <*> serverSide getCurrentTime <*> contentsForm
Could you abstract `serverSide` out into a typeclass, such as ApplicativeIO? Sure. but why bother? The point is, you've got the specialization you need already.
Yes, I agree that to simply solve the problem in yesod-form, this would be a great solution. But as to "why bother" with ApplicativeIO: my point in sending this email was to see if other people have been bothered by this, and if it's therefore worth coming up with a general purpose solution. If there's no real interest in it, I don't see a need to create such a general solution. On the other hand, if people think this is worth a general ApplicativeIO class, I'd be happy to use that instead of defining an ad-hoc function in yesod-form. Thanks to everyone for this great discussion, I'm thoroughly enjoying following it. Michael

Tom Ellis wrote:
Shouldn't it be an *Applicative* constraint?
class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a
and require that
liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x
Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter.
In fact, it even makes sense to define it as FunctorIO, with the only laws being that liftIO commutes with fmap and preserves id, i.e., that it is a natural transformation. (Those laws are also needed for ApplicativeIO and MonadIO.) Since Haskell is not dependently typed and we specify laws only as human-readable comments, should we define only FunctorIO and then just specify in the comments the additional laws that should be satisfied for Applicative and Monad? Or should we have equivalent definitions that differ only in the laws that are expected to be satisfied? Or should the different definitions have different superclass constraints? Let's get it right this time and not create yet another Functor/Applicative/Monad mess. Thanks, Yitz

On Tue, Oct 01, 2013 at 03:17:40PM +0300, Yitzchak Gale wrote:
Tom Ellis wrote:
Shouldn't it be an *Applicative* constraint?
class Applicative t => ApplicativeIO t where liftIO :: IO a -> t a
and require that
liftIO (pure x) = pure x liftIO (f <*> x) = liftIO f <*> liftIO x
Seems like ApplicativeIO makes more sense than MonadIO, which is unnecessarily restrictive. With planned Functor/Applicative/Monad shuffle, the former could completely replace the latter.
In fact, it even makes sense to define it as FunctorIO, with the only laws being that liftIO commutes with fmap and preserves id, i.e., that it is a natural transformation. (Those laws are also needed for ApplicativeIO and MonadIO.)
I think that law follows automatically from parametricity, doesn't it?
Since Haskell is not dependently typed and we specify laws only as human-readable comments, should we define only FunctorIO and then just specify in the comments the additional laws that should be satisfied for Applicative and Monad? Or should we have equivalent definitions that differ only in the laws that are expected to be satisfied? Or should the different definitions have different superclass constraints?
In tackling such questions I think it would be useful to know how many such instances there can be. Can there be more than one morphism between two monads? Between two applicatives? I would guess there are plenty of examples of functors with more than one functor morphism (natural transformation) between them. Perhaps these questions are easy, but I don't know how to approach them. Tom

Yitzchak Gale
writes:
In fact, it even makes sense to define it as FunctorIO, with the only laws being that liftIO commutes with fmap and preserves id, i.e., that it is a natural transformation. (Those laws are also needed for ApplicativeIO and MonadIO.)
Given that we are moving toward Applicative (and thus Functor) as a superclass of Monad, why not just solve the MonadIO problem and similar type classes with natural transformations? It requires 3 extensions, but these are extensions I believe should become part of Haskell anyway: {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} module NatTrans where import Control.Monad.IO.Class import Control.Monad.Trans.Maybe class (Functor s, Functor t) => NatTrans s t where nmap :: forall a. s a -> t a -- Such that: nmap . fmap f = fmap f . nmap -- In 7.10, this Functor constraint becomes redundant instance (Functor m, MonadIO m) => NatTrans IO m where nmap = liftIO main :: IO () main = void $ runMaybeT $ nmap $ print (10 :: Int) Now if I have a functor of one kind and need another, I reach for nmap in the same way that I reach for fmap to transform the mapped type. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Interesting. It's similar in spirit to basically a safe Coerce typeclass,
but for * -> * types.
class Coerce a b where
coerce :: a -> b
class Coerce1 f g where
coerce1 :: f a -> g a
-- Dan Burton
On Tue, Oct 1, 2013 at 11:00 AM, John Wiegley
Yitzchak Gale
writes: In fact, it even makes sense to define it as FunctorIO, with the only laws being that liftIO commutes with fmap and preserves id, i.e., that it is a natural transformation. (Those laws are also needed for ApplicativeIO and MonadIO.)
Given that we are moving toward Applicative (and thus Functor) as a superclass of Monad, why not just solve the MonadIO problem and similar type classes with natural transformations? It requires 3 extensions, but these are extensions I believe should become part of Haskell anyway:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-}
module NatTrans where
import Control.Monad.IO.Class import Control.Monad.Trans.Maybe
class (Functor s, Functor t) => NatTrans s t where nmap :: forall a. s a -> t a -- Such that: nmap . fmap f = fmap f . nmap
-- In 7.10, this Functor constraint becomes redundant instance (Functor m, MonadIO m) => NatTrans IO m where nmap = liftIO
main :: IO () main = void $ runMaybeT $ nmap $ print (10 :: Int)
Now if I have a functor of one kind and need another, I reach for nmap in the same way that I reach for fmap to transform the mapped type.
-- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Isn't it the case that there could be more than one natural transformation
between functors?
On Tue, Oct 1, 2013 at 10:00 PM, John Wiegley
Yitzchak Gale
writes: In fact, it even makes sense to define it as FunctorIO, with the only laws being that liftIO commutes with fmap and preserves id, i.e., that it is a natural transformation. (Those laws are also needed for ApplicativeIO and MonadIO.)
Given that we are moving toward Applicative (and thus Functor) as a superclass of Monad, why not just solve the MonadIO problem and similar type classes with natural transformations? It requires 3 extensions, but these are extensions I believe should become part of Haskell anyway:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-}
module NatTrans where
import Control.Monad.IO.Class import Control.Monad.Trans.Maybe
class (Functor s, Functor t) => NatTrans s t where nmap :: forall a. s a -> t a -- Such that: nmap . fmap f = fmap f . nmap
-- In 7.10, this Functor constraint becomes redundant instance (Functor m, MonadIO m) => NatTrans IO m where nmap = liftIO
main :: IO () main = void $ runMaybeT $ nmap $ print (10 :: Int)
Now if I have a functor of one kind and need another, I reach for nmap in the same way that I reach for fmap to transform the mapped type.
-- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sincerely yours, -- Daniil

On Mon, Oct 07, 2013 at 07:57:23PM +0400, Daniil Frumin wrote:
Isn't it the case that there could be more than one natural transformation between functors?
Definitely. In addition rwbarton responded to my challenge by finding two different applicative morphisms between the same applicative, one which extends to a monad morphism and one which does not: http://www.reddit.com/r/haskell/comments/1ni8r6/should_it_be_monadio_applica... Tom

Daniil Frumin
writes:
Isn't it the case that there could be more than one natural transformation between functors?
Yes, I imagine there would have to be some newtype wrappers to distinguish in those cases. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Maybe this is needed new typeclass ApplicativeTrans?
2013/10/1 Michael Snoyman
I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are:
1. Has anyone else run into this issue? 2. Is there an existing solution out there?
Michael
[1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Oct 1, 2013 at 10:24 AM, Alexey Uimanov
Maybe this is needed new typeclass ApplicativeTrans?
There's actually no problem with defining a MonadTrans instance for non-monads. Obviously this can't follow the laws directly (since they're defined in terms of monadic bind and return), but I think we could probably state Applicative versions of those laws (assuming I haven't made a stupid mistake): lift . pure = pure lift (x <*> y) = lift x <*> lift y Michael
2013/10/1 Michael Snoyman
I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are:
1. Has anyone else run into this issue? 2. Is there an existing solution out there?
Michael
[1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T...
_______________________________________________ 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

In MFow there is a Monad instance for formlets that make a lot of sense.
Apart from using liftIO inside an applicative formlets
it can do it that way also:
myBlogForm = do
t <- liftIO getTime
Blog <$> titleForm <*> return t <*> contentsForm
Which may look contrived, but instead of using return t, we can display for
the user something interesting in that place.
There are other dynamic things, like asking different questions depending
on previous responses thanks to the monad instance :
http://haskell-web.blogspot.com.es/2013/06/the-promising-land-of-monadic-for...
2013/10/1 Michael Snoyman
On Tue, Oct 1, 2013 at 10:24 AM, Alexey Uimanov
wrote: Maybe this is needed new typeclass ApplicativeTrans?
There's actually no problem with defining a MonadTrans instance for non-monads. Obviously this can't follow the laws directly (since they're defined in terms of monadic bind and return), but I think we could probably state Applicative versions of those laws (assuming I haven't made a stupid mistake):
lift . pure = pure lift (x <*> y) = lift x <*> lift y
Michael
2013/10/1 Michael Snoyman
I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are:
1. Has anyone else run into this issue? 2. Is there an existing solution out there?
Michael
[1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T...
_______________________________________________ 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

What about (Compose Form IO) Blog type? Form is Applicative, IO — the same, their composition should be Applicative as well (one good thing about Applicatives — they really compose). Take a look at Control.Compose module. Отправлено с iPad
01 окт. 2013 г., в 10:58, Michael Snoyman
написал(а): I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
This works, but is unintuitive. One solution would be to have an ApplicativeIO typeclass and then use liftIOA. My questions here are:
1. Has anyone else run into this issue? 2. Is there an existing solution out there?
Michael
[1] Full crazy definition is at: http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-T... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 10/01/2013 07:58 AM, Michael Snoyman wrote:
I'm wondering if anyone's run into this problem before, and if there's a common solution.
In Yesod, we have applicative forms (based originally on formlets). These forms are instances of Applicative, but not of Monad. Let's consider a situation where we want to get some user input to fill out a blog post datatype, which includes the current time:
data Blog = Blog Title UTCTime Contents
myBlogForm :: Form Blog myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
The question is: what goes in something? Its type has to be:
something :: Form UTCTime
Ideally, I'd call getCurrentTime. The question is: how do I lift that into a Form? Since Form is only an Applicative, not a Monad, I can't create a MonadIO instance. However, Form is in fact built on top of IO[1]. And it's possible to create a MonadTrans instance for Form, since it's entirely possible to lift actions from the underlying functor/monad into Form. So something can be written as:
something = lift $ liftIO getCurrentTime
Is it really necessary to have a type class to do this? You can always just introduce 'io :: IO a -> Form a' to lift IO actions into a form. Then you just have: myBlogForm = Blog <$> titleForm <*> io getCurrentTime <*> contentsForm In digestive-functors, we have the base monad in the type of the form itself, so we provide 'monadic' which goes from m (Form m a) -> Form m a (hand-waving as there are actually other type constraints). You might get more power by following in those steps, and having the aforementioned 'io' function actually be: io :: IO (Form a) -> Form a - ocharles
participants (15)
-
Alberto G. Corona
-
Alexander Solla
-
Alexey Uimanov
-
Dan Burton
-
Daniil Frumin
-
John Lato
-
John Wiegley
-
Jose A. Lopes
-
Michael Snoyman
-
MigMit
-
Niklas Haas
-
Oliver Charles
-
Roman Cheplyaka
-
Tom Ellis
-
Yitzchak Gale