
Hi all, I am trying to write the simplest possible database program in a monadic style. The aim of the program is to connect to the database, run a query, then print the results. My approach is - use the Reader monad to pass around the connection handle (lda) to the database - use the Writer monad to store the result set (rs) on its way back out - converted into [String] (one String per row) My code is: module Main where import Control.Monad.Reader import Control.Monad.Writer import Database.HDBC import Database.HDBC.Sqlite3 runDbApp lda f = do (a, rs) <- runWriterT (runReaderT f lda) return rs doQuery::MonadIO m => ReaderT Connection (WriterT [String] m) () doQuery = do lda <- ask -- get the database handle from the Reader rs <- quickQuery lda "select datetime ('now')" [] let rs' = map convRow rs mapM_ tell rs' -- store the results in the Writer where convRow [x] = (fromSql x)::String main = handleSqlError $ do lda <- connectSqlite3 "test.db" rs <- runDbApp lda $ doQuery mapM_ putStrLn rs -- end of file And the error is home/gaius/Projects/MonadDb/MonadDb.hs:15:2: Couldn't match expected type `IO [[SqlValue]]' against inferred type `ReaderT Connection (WriterT [String] m) [[SqlValue]]' In a stmt of a 'do' expression: rs <- quickQuery lda "select datetime ('now')" [] Why does it think that that is the final expression of the function? Any advice greatly appreciated. I have been struggling with this since lunchtime! Thanks, G

On Saturday 18 September 2010 20:40:58, Gaius Hammond wrote:
Hi all,
I am trying to write the simplest possible database program in a monadic style. The aim of the program is to connect to the database, run a query, then print the results. My approach is
- use the Reader monad to pass around the connection handle (lda) to the database - use the Writer monad to store the result set (rs) on its way back out - converted into [String] (one String per row)
My code is:
module Main where
import Control.Monad.Reader import Control.Monad.Writer import Database.HDBC import Database.HDBC.Sqlite3
runDbApp lda f = do (a, rs) <- runWriterT (runReaderT f lda) return rs
doQuery::MonadIO m => ReaderT Connection (WriterT [String] m) () doQuery = do lda <- ask -- get the database handle from the Reader rs <- quickQuery lda "select datetime ('now')" []
let rs' = map convRow rs mapM_ tell rs' -- store the results in the Writer
where convRow [x] = (fromSql x)::String
main = handleSqlError $ do lda <- connectSqlite3 "test.db" rs <- runDbApp lda $ doQuery
mapM_ putStrLn rs
-- end of file
And the error is
home/gaius/Projects/MonadDb/MonadDb.hs:15:2: Couldn't match expected type `IO [[SqlValue]]' against inferred type `ReaderT Connection (WriterT [String] m) [[SqlValue]]' In a stmt of a 'do' expression: rs <- quickQuery lda "select datetime ('now')" []
Why does it think that that is the final expression of the function?
It doesn't, but you said the do-expression had type ReaderT Connection (WriterT [String] m) () while quickQuery :: IConnection conn => conn -> String -> [SqlValue] -> IO [[SqlValue]] The types don't match, hence the error. But you have a MonadIO constraint, so rs <- liftIO $ quickQuery ... should fix it.
Any advice greatly appreciated. I have been struggling with this since lunchtime!
Hopefully it didn't stop you from eating. Cheers, Daniel

On 18 Sep 2010, at 21:03, Daniel Fischer wrote:
Why does it think that that is the final expression of the function?
It doesn't, but you said the do-expression had type ReaderT Connection (WriterT [String] m) () while
quickQuery :: IConnection conn => conn -> String -> [SqlValue] -> IO [[SqlValue]]
The types don't match, hence the error. But you have a MonadIO constraint, so
rs <- liftIO $ quickQuery ...
should fix it.
Aha! It does indeed, thanks :-) I had assumed that with the rs <- quickQuery I was getting the [[SqlValue]] "out" of the IO Monad - but I have to lift it into the IO Monad first, since I am in a monadic context? This would be the non- monadic version module Main where import Database.HDBC import Database.HDBC.Sqlite3 main:: IO () main = do lda <- connectSqlite3 "test.db" rs <- quickQuery lda "select datetime ('now')" [] mapM_ putStrLn (map convRow rs) where convRow [x] = (fromSql x)::String -- EOF Oh, but I am already in the IO monad there aren't I.... And doQuery *isn't* but I have declared that it *should be* (e.g. an instance of typeclass MonadIO). Is that accurate?
Any advice greatly appreciated. I have been struggling with this since lunchtime!
Hopefully it didn't stop you from eating.
Nothing could do that :-) Cheers, G

On Saturday 18 September 2010 22:30:46, Gaius Hammond wrote:
On 18 Sep 2010, at 21:03, Daniel Fischer wrote:
Why does it think that that is the final expression of the function?
It doesn't, but you said the do-expression had type ReaderT Connection (WriterT [String] m) () while
quickQuery :: IConnection conn => conn -> String -> [SqlValue] -> IO [[SqlValue]]
The types don't match, hence the error. But you have a MonadIO constraint, so
rs <- liftIO $ quickQuery ...
should fix it.
Aha! It does indeed, thanks :-)
I had assumed that with the rs <- quickQuery I was getting the [[SqlValue]] "out" of the IO Monad
Sort of, but only in a do-block of type IO something, you had it in a do- block of type ReaderT Connection (WriterT [String] m) something There it doesn't type-check. Remember, do a <- act otherAct a is syntactic sugar for act >>= otherAct The type of (>>=) says the monads on both sides must be the same.
- but I have to lift it into the IO Monad first, since I am in a monadic context?
No, you have to lift the IO-action (quickQuery args) into the MonadIO ReaderT Connection (WriterT [String] m), liftIO :: MonadIO m => IO a -> m a lifts IO-actions to another monad.
This would be the non- monadic version
module Main where
import Database.HDBC import Database.HDBC.Sqlite3
main:: IO () main = do lda <- connectSqlite3 "test.db" rs <- quickQuery lda "select datetime ('now')" []
mapM_ putStrLn (map convRow rs) where convRow [x] = (fromSql x)::String
-- EOF
Oh, but I am already in the IO monad there aren't I.
Yup, in main, you're in IO.
... And doQuery *isn't* but I have declared that it *should be* (e.g. an instance of typeclass MonadIO). Is that accurate?
No, MonadIO says, you can run IO-actions from inside that monad, but you have to lift them in order to run them (except the MonadIO you use is IO itself). You said that you wanted to be able to do that, but forgot the lifting.
Any advice greatly appreciated. I have been struggling with this since lunchtime!
Hopefully it didn't stop you from eating.
Nothing could do that :-)
Glad to read that.

On 18 Sep 2010, at 21:49, Daniel Fischer wrote:
Hopefully it didn't stop you from eating.
Nothing could do that :-)
Glad to read that.
I've written all this up in my blog now, hopefully it will be of some use to the next person :-) http://gaiustech.wordpress.com/2010/09/19/scope-in-database-code-2/ Cheers, G

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 9/18/10 16:30 , Gaius Hammond wrote:
Oh, but I am already in the IO monad there aren't I.... And doQuery *isn't* but I have declared that it *should be* (e.g. an instance of typeclass MonadIO). Is that accurate?
You're in ReaderT at that point. If you "lift" a monadic expression from there, it will be run in WriterT. Since IO must always be at the base(*) of any stack of monad transformers it is used in, the MonadIO class provides a convenience function liftIO that lifts its argument directly to the IO monad without having to step through any intermediates. _______ * we call it "lifting" but we also claim IO is at the base of the stack, and I at least usually expect a base to be at the bottom. Nice and confusing :) - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkyWopIACgkQIn7hlCsL25VRAwCfSLR1M++NqB1wPFbI8LQoD1Lk GS4Anitq5B3KDectcCF18HGDb5XqRxIo =tBJU -----END PGP SIGNATURE-----

On Sun, Sep 19, 2010 at 07:53:54PM -0400, Brandon S Allbery KF8NH wrote:
Since IO must always be at the base(*) of any stack of monad transformers it is used in, the MonadIO class provides a convenience function liftIO that lifts its argument directly to the IO monad without having to step through any intermediates.
_______ * we call it "lifting" but we also claim IO is at the base of the stack, and I at least usually expect a base to be at the bottom. Nice and confusing :)
I think of liftIO as lifting its argument *from* the IO monad (at the bottom of the stack) into a monad higher up the stack. liftIO :: (MonadIO m) => IO a -> m a So I don't find it confusing/backwards at all. -Brent
participants (4)
-
Brandon S Allbery KF8NH
-
Brent Yorgey
-
Daniel Fischer
-
Gaius Hammond