
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.