
Hello! In a CGI application I was gathering SQL statements I wanted to run in the final transaction. Because I use haskelldb, it was most convenient to use (Database -> IO ()) as the type of the statement or a group of statements. In this representation concatenating two statement groups so they are executed in sequence can be done with: concatStmts s1 s2 = \db -> s1 db >> s2 db My mistake was that I forgot about db and wrote: concatStmts s1 s2 = s1 >> s2 And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)! Of course it doesn't do the right thing - s1 is simply ignored. Fortunately I noticed it quite quickly, but I think a similar bug can cause someone a big headache. Perhaps we could move this instance to some separate module, so people won't import it if they don't want it or even don't know about its existence? Best regards Tomek

Tomasz Zielonka wrote:
My mistake was that I forgot about db and wrote:
concatStmts s1 s2 = s1 >> s2
And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)!
The danger in overloading is that you are relying on the compiler to infer which instance you mean. This is perhaps most visible with Monad which has so many common instances ([], (r ->), Maybe, etc). When writing monadic expressions in large projects, I recommend annotating them with the types you really want. Jules

On Tue, May 15, 2007 at 11:15:20AM +0100, Jules Bean wrote:
Tomasz Zielonka wrote:
My mistake was that I forgot about db and wrote:
concatStmts s1 s2 = s1 >> s2
And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)!
The danger in overloading is that you are relying on the compiler to infer which instance you mean. This is perhaps most visible with Monad which has so many common instances ([], (r ->), Maybe, etc).
So it seems a good idea not to import the instances you don't want to decrease the number of typechecking combinations. Unfortunately, the way class instances are implicitly exported and imported in Haskell makes it difficult.
When writing monadic expressions in large projects, I recommend annotating them with the types you really want.
You mean I should write the type signature for concatStmts? That's a good advice, however, in my code there was no concatStmts - it would be used only in one place, so I inlined it. Best regards Tomek

Hi Tomek!
In a CGI application I was gathering SQL statements I wanted to run in the final transaction. Because I use haskelldb, it was most convenient to use (Database -> IO ()) as the type of the statement or a group of statements. In this representation concatenating two statement groups so they are executed in sequence can be done with:
concatStmts s1 s2 = \db -> s1 db >> s2 db
My mistake was that I forgot about db and wrote:
concatStmts s1 s2 = s1 >> s2
And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)!
Have you considered changing the statements to have type 'ReaderT Database IO ()'? Then (>>) actually does what you want. Pozdrawiam, Arie -- Always go along with the group, or someone may drop a sixteen-ton safe on you. - The Buddy Bears

On Tue, May 15, 2007 at 02:27:13PM +0200, Arie Peterson wrote:
Hi Tomek!
Hi!
Have you considered changing the statements to have type 'ReaderT Database IO ()'? Then (>>) actually does what you want.
I tried it and it made the code simpler, more readable and of course more immune to this type of bugs. Thanks! Pozdrawiam Tomek

On May 15, 2007, at 14:52 , Tomasz Zielonka wrote:
On Tue, May 15, 2007 at 02:27:13PM +0200, Arie Peterson wrote:
Hi Tomek!
Hi!
Have you considered changing the statements to have type 'ReaderT Database IO ()'? Then (>>) actually does what you want.
I tried it and it made the code simpler, more readable and of course more immune to this type of bugs. Thanks!
I use the same idea in Hope (http://hope.bringert.net/), with a newtype DatabaseT, and a typeclass MonadDatabase, and lifted versions of the HaskellDB database operations. The code is in the first part of this module: http://www.cs.chalmers.se/~bringert/darcs/hope/Hope/ DatabaseT.hs Perhaps this should be added to HaskellDB? /Björn

You could also use mappend instead of concatStmts and keep the Database ->
IO () representation. - Conal
On 5/15/07, Arie Peterson
Hi Tomek!
In a CGI application I was gathering SQL statements I wanted to run in the final transaction. Because I use haskelldb, it was most convenient to use (Database -> IO ()) as the type of the statement or a group of statements. In this representation concatenating two statement groups so they are executed in sequence can be done with:
concatStmts s1 s2 = \db -> s1 db >> s2 db
My mistake was that I forgot about db and wrote:
concatStmts s1 s2 = s1 >> s2
And it was accepted because I had the Monad instance for ((->) r) in scope (from Control.Monad.Trans I guess)!
Have you considered changing the statements to have type 'ReaderT Database IO ()'? Then (>>) actually does what you want.
Pozdrawiam,
Arie
--
Always go along with the group, or someone may drop a sixteen-ton safe on you. - The Buddy Bears
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote:
You could also use mappend instead of concatStmts and keep the Database -> IO () representation. - Conal
You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that. Pozdrawiam Tomek

Tomasz Zielonka wrote:
On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote:
You could also use mappend instead of concatStmts and keep the Database -> IO () representation. - Conal
You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that.
Indeed, all Monads are Monoids (that is, if m :: * -> * is a Monad, then m a :: * is a Monoid, for any fixed type a) by using >>. MonadPlusses have a Monoid structure at each particular fixed type, using mplus, but it's not the same one in all but the most trivial case. E.g: Prelude System.IO Control.Monad> Just 3 >> Nothing Nothing Prelude System.IO Control.Monad> Just 3 `mplus` Nothing Just 3 The general point here is that an awful lot of things are Monoids, often in more than one way. There isn't a really elegant way to choose which instance you want, though. newtype hackery is one way to partition them, although it might be nicer (?) to have a more general notion of 'naming instances'. Jules

On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote:
Tomasz Zielonka wrote:
You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that.
Indeed, all Monads are Monoids (that is, if m :: * -> * is a Monad, then m a :: * is a Monoid, for any fixed type a) by using >>.
Are you sure that (IO Int) is a monoid with mappend = (>>)? How do you define mempty, so it is an identity for mappend? It would help if type a was a Monoid, then: mempty = return mempty mappend mx my = do x <- mx y <- my return (x `mappend` y) It's easier if a = (). Regards Tomek

Tomasz Zielonka wrote:
On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote:
Tomasz Zielonka wrote:
You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that.
Indeed, all Monads are Monoids (that is, if m :: * -> * is a Monad, then m a :: * is a Monoid, for any fixed type a) by using >>.
Are you sure that (IO Int) is a monoid with mappend = (>>)? How do you define mempty, so it is an identity for mappend?
It would help if type a was a Monoid, then:
mempty = return mempty mappend mx my = do x <- mx y <- my return (x `mappend` y)
It's easier if a = ().
Oops, you're right. I spoke too fast. It's only a monoid for (). Otherwise you can't hope to have a right identity. Jules

Oops -- I wasn't watching this thread. I like Jules's definition, though
I'd write it as follows.
-- Standard instance: monad applied to monoid
instance Monoid a => Monoid (IO a) where
mempty = return mempty
mappend = liftM2 mappend
You can replace "IO" with any monad at all, to make similar instances.
Here's the instance i use. It's in Control.Instances in the TypeCompose
library. See http://www.haskell.org/haskellwiki/TypeCompose.
-- Standard instance: applicative functor applied to monoid
instance Monoid a => Monoid (IO a) where
mempty = pure mempty
mappend = (*>)
On second thought, I don't really like (*>), since it's easy to accidentally
discard a useful value. (I dislike (>>) for the same reason.) Generalizing
the "monad applied to monoid" instance above:
-- Standard instance: applicative functor applied to monoid
instance Monoid a => Monoid (IO a) where
mempty = pure mempty
mappend = liftA2 mappend
That will be the definition in the next TypeCompose release.
All of these instances agree for a = (). The first & third are more
compelling to me than the second, since they make full use of the Monoid a
constraint.
Cheers, - Conal
On 5/16/07, Jules Bean
On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote:
Tomasz Zielonka wrote:
You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that.
Indeed, all Monads are Monoids (that is, if m :: * -> * is a Monad,
Tomasz Zielonka wrote: then
m a :: * is a Monoid, for any fixed type a) by using >>.
Are you sure that (IO Int) is a monoid with mappend = (>>)? How do you define mempty, so it is an identity for mappend?
It would help if type a was a Monoid, then:
mempty = return mempty mappend mx my = do x <- mx y <- my return (x `mappend` y)
It's easier if a = ().
Oops, you're right. I spoke too fast.
It's only a monoid for (). Otherwise you can't hope to have a right identity.
Jules

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Conal Elliott wrote:
-- Standard instance: applicative functor applied to monoid instance Monoid a => Monoid (IO a) where mempty = pure mempty mappend = (*>)
On second thought, I don't really like (*>), since it's easy to accidentally discard a useful value. (I dislike (>>) for the same reason.)
Exactly; because they don't make monoids, because (x `mappend` mempty) isn't (x), so mempty isn't a right-identity of mappend, so the instance doesn't follow the monoid laws. Isaac -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGV2hZHgcxvIWYTTURAjlsAJ0fyUrqYAx09neVi2/FN+sUQobEUACfWAph 2WJwISDe/11pg41lcV80uik= =SYQB -----END PGP SIGNATURE-----
participants (6)
-
Arie Peterson
-
Bjorn Bringert
-
Conal Elliott
-
Isaac Dupree
-
Jules Bean
-
Tomasz Zielonka