
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

The thing that I see as weird is (>>= return ()), since the right argument
to (>>=) is supposed to be a function.
Maybe you want (>>)
On Sat, May 28, 2011 at 5:35 PM, Neil Jensen
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alex R

Hi Alex, thanks, I tried that, as well as removing the 'return' entirely,
but in both cases I ended up with the following:
Couldn't match expected type `ISODateInt -> ISODateInt -> IO a'
against inferred type `IO [((ISODateInt, ISODateInt), CUV)]'
In the first argument of `(>>=)', namely
`calcCUVs account prevMonthEnd monthEnd'
In the first argument of `(>>)', namely
`calcCUVs account prevMonthEnd monthEnd
>>=
(\ cuvs -> saveCUVs account cuvs)'
In the expression:
calcCUVs account prevMonthEnd monthEnd
>>=
(\ cuvs -> saveCUVs account cuvs)
>>
return ()
On Sat, May 28, 2011 at 2:50 PM, Alex Rozenshteyn
The thing that I see as weird is (>>= return ()), since the right argument to (>>=) is supposed to be a function.
Maybe you want (>>)
On Sat, May 28, 2011 at 5:35 PM, 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 ()
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alex R

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

Thanks Daniel, correcting the function call to calcCUVs did the trick. On Sat, May 28, 2011 at 3:11 PM, Daniel Fischer < daniel.is.fischer@googlemail.com> wrote:
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

On Sat, May 28, 2011 at 4:35 PM, Neil Jensen
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 ()
I think you might have your parenthesis in the wrong spot. Instead of
x >>= (\a -> y a) >> z
you probably want:
x >>= (\a -> y a >> z)
Does that make sense? Antoine

On Sun, May 29, 2011 at 3:33 AM, Antoine Latter
I think you might have your parenthesis in the wrong spot.
Instead of
x >>= (\a -> y a) >> z
you probably want:
x >>= (\a -> y a >> z)
Does that make sense?
No, that shouldn't change anything (except maybe performance, but not here), monads have a property close to associativity which means that changing the parenthesis shouldn't change the meaning of your code, you don't have to worry about that. -- Jedaï

On Sun, May 29, 2011 at 1:29 AM, Chaddaï Fouché
On Sun, May 29, 2011 at 3:33 AM, Antoine Latter
wrote: I think you might have your parenthesis in the wrong spot.
Instead of
x >>= (\a -> y a) >> z
you probably want:
x >>= (\a -> y a >> z)
Does that make sense?
No, that shouldn't change anything (except maybe performance, but not here), monads have a property close to associativity which means that changing the parenthesis shouldn't change the meaning of your code, you don't have to worry about that.
-- Jedaï
That's right Chaddaï, I was just able to do the following and it worked: calcCUVs account >>= (\cuvs -> saveCUVs account cuvs) Thanks. N.
participants (5)
-
Alex Rozenshteyn
-
Antoine Latter
-
Chaddaï Fouché
-
Daniel Fischer
-
Neil Jensen