[Haskell-beginners] IO action on a list of [IO a]
ugo pozo
ugopozo at gmail.com
Sun Oct 7 02:49:53 CEST 2012
Here is my try. It works for any monad (not just IO) and any foldable
(not just lists).
import Data.Foldable
myfor :: (Monad m, Foldable t) => (a -> m ()) -> t (m a) -> m ()
myfor f = foldlM (flip $ const (>>=f)) ()
--
~ ugo pozo
~ mailto:ugopozo at gmail.com
~ home://11.3266.2021
~ cell://11.8432.9252
On Sat, Oct 6, 2012 at 9:08 PM, Brent Yorgey <byorgey at seas.upenn.edu> wrote:
> On Sat, Oct 06, 2012 at 07:35:13PM +0200, Henk-Jan van Tuyl wrote:
>> On Sat, 06 Oct 2012 16:16:18 +0200, Manfred Lotz
>> <manfred.lotz at arcor.de> wrote:
>>
>> >myfor :: (a -> IO () ) -> [IO a] -> IO ()
>> >myfor _ [] = return ()
>> >myfor f (x:xs) = do
>> > x' <- x
>> > f x'
>> > myfor f xs
>> >
>> >
>> >Is there a library function doing just this?
>>
>> You could use this:
>> import Control.Monad
>> myfor :: (a -> IO () ) -> [IO a] -> IO ()
>> myfor f (x:xs) = mapM_ (liftM f) xs
>
> This should be
>
> myfor f xs = mapM_ (>>= f) xs
>
> using (liftM f) will result in the right type but it does the wrong
> thing, as Manfred observed:
>
> f :: a -> IO ()
> liftM f :: IO a -> IO (IO a)
>
> So mapping liftM f over a list of IO actions results in a list of IO
> actions with no effects, whose results are the IO actions you really
> wanted. Then mapM_ throws away those IO actions you really wanted,
> resulting in essentially (return () :: IO ()).
>
> -Brent
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list