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

Daniel Fischer daniel.is.fischer at googlemail.com
Sun May 29 00:11:16 CEST 2011


On Saturday 28 May 2011 23:35:11, Neil Jensen wrote:
> 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 ()

You're not using the result of mapM, so you should use mapM_ here, if the 
list is long or the results of storeCUV are large, it's also more 
efficient.

saveCUVs account cuvs
    = mapM_ (\x -> storeCUV (snd $ fst x) account (snd x)) cuvs

or, avoiding the snd and fst by taking the argument apart via pattern-
matching,

saveCUVs account cuvs
    = mapM_ (\((_,date),cuv) -> storeCUV date account cuv) cuvs

> 
> 
> 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 ()

The second argument of (>>=) must be a function, here of type (a -> IO b),
... >> return () or ... >>= return would typecheck, but the latter doesn't 
make any sense, since 'action >>= return' is the same as plain 'action'.
The latter is only of use to finally get the right result type, which is 
what you're doing here.

>                        else calcCUVs account prevMonthEnd monthEnd >>=

No, that can't be. calcCUVs takes one argument and returns an IO [...], 
here you pass it three.

> (\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



More information about the Beginners mailing list