
I am not sure whether to support your proposal, just want to point out that the original filterM can be generalized to Applicative, while you new filterM' seems to require a monad, since the result of checking the predicate on the first element influences the shape of the recursive call. import Control.Applicative consIf a b as = if b then a:as else as -- Applicative filter filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] filterM p [] = pure [] filterM p (a:as) = consIf a <$> p a <*> filterM p as -- Monadic filter (D. Feuer) filterM' :: (Functor m, Monad m) => (a -> m Bool) -> [a] -> m [a] filterM' p xs = reverse <$> go [] xs where go acc [] = return acc go acc (a:as) = do b <- p a go (consIf a b acc) as Maybe to support your proposal you should add a compelling test case (i.e. crashes with filterM but succeeds with filterM'). Cheers, Andreas On 04.09.2014 04:05, David Feuer wrote:
I wrote filterM' rather wrong. Sorry, folks. Here's a fix:
filterM' :: (Monad m) => (a -> m Bool) -> [a] -> m [a] filterM' p = go [] where go acc [] = return (reverse acc) go acc (x:xs) = do flq <- p x if flq then go (x:acc) xs else go acc xs
Or with foldr:
filterM' :: (Monad m) => (a -> m Bool) -> [a] -> m [a] filterM' p xs = foldr go (return . reverse) xs [] where go x r = \acc -> do flq <- p x if flq then r (x:acc) else r acc
Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/