[Haskell-beginners] return IO () vs. ()

Neil Jensen neilcjensen at gmail.com
Sat May 28 23:35:11 CEST 2011


I've been attempting to refactor some working code and running into
confusion about returning IO values.

The basic sequence is to query a database, calculate some values, and then
store the results back in the database.

The function which does the querying of the db and calculating results has
the following type signature:
calcCUVs :: AccountId -> IO [((ISODateInt, ISODateInt), CUV)]

This function stores the results back into the database
saveCUVs :: AccountId -> [((ISODateInt, ISODateInt), CUV)] -> IO ()
saveCUVs account cuvs = do
            r' <- mapM (\x -> storeCUV (snd $ fst x) account (snd x)) cuvs
            return ()


I had a working variation of the below using 'do' notation, but for some
reason when I moved to using bind, I'm getting messed up with return values.

processAccountCUVs :: AccountId -> ISODateInt -> ISODateInt -> IO ()
processAccountCUVs account prevMonthEnd monthEnd = -- do
                   if (prevMonthEnd == 0 && monthEnd == 0)
                       then calcCUVs account >>=  (\cuvs -> saveCUVs account
cuvs) >>= return ()
                       else calcCUVs account prevMonthEnd monthEnd >>=
(\cuvs -> saveCUVs account cuvs) >>= return ()


The compiler gives the following error message:

Couldn't match expected type `IO ()' against inferred type `()'
    In the first argument of `return', namely `()'
    In the second argument of `(>>=)', namely `return ()'
    In the expression:
            calcCUVs account >>= (\ cuvs -> saveCUVs account cuvs)   >>=
return ()


I thought the last return () would correctly return us IO () as we are in
the IO monad... what am I missing?

Thanks for any input you can provide.
Neil
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110528/7691c607/attachment.htm>


More information about the Beginners mailing list