
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