<p dir="ltr">I like your idea, but not your proposed name. I think the Bool/Maybe matter should not be determined by whether it's filterA or filterM. Generalize filterM and give your version a different name. I also have a minor concern about your version. When it doesn't work magic to improve `fmap (fmap f) . filterM g`, and when there isn't enough inlining, those Just constructors could increase allocation.</p>
<div class="gmail_quot<blockquote class=" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">should <span style="font-size:12.8000001907349px">filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a]</span><div><span style="font-size:12.8000001907349px">perhaps be </span><span style="font-size:12.8000001907349px">filterA :: (Applicative p) => (a -> p (Maybe be)) -> [a] -> p [b]</span></div><div><span style="font-size:12.8000001907349px">?</span></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Mon, Mar 16, 2015 at 3:34 PM, Edward Kmett <span dir="ltr"><<a href="mailto:ekmett@gmail.com" target="_blank">ekmett@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">We've been simply generalizing the types of existing combinators (and leaving them in their existing homes) rather than taking an army of new names and leaving a ghetto of old, less useful combinators that we'd have to clean up later or leave as landmines to trip up newcomers to the language.<div><br></div><div>I have no objection to generalizing the types of these combinators, however.</div><span><font color="#888888"><div><br></div><div>-Edward</div></font></span></div><div><div><div class="gmail_extra"><br><div class="gmail_quote">On Mon, Mar 16, 2015 at 3:07 PM, M Farkas-Dyck <span dir="ltr"><<a href="mailto:strake888@gmail.com" target="_blank">strake888@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Analogs of monadic functions, which likely ought to be in base as part of AMP.<br>
<br>
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.<br>
<br>
-- | 'filterA' generalizes the list-based 'filter' function.<br>
{-# INLINE filterA #-}<br>
filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a]<br>
filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure [])<br>
  where<br>
    bool True  x = const x<br>
    bool False _ = id<br>
<br>
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists.<br>
{-# INLINE mapAndUnzipA #-}<br>
mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c])<br>
mapAndUnzipA f xs = unzip <$> traverse f xs<br>
<br>
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors.<br>
{-# INLINE zipWithA #-}<br>
zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c]<br>
zipWithA f x y = sequenceA (zipWith f x y)<br>
<br>
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result.<br>
{-# INLINE zipWithA_ #-}<br>
zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p ()<br>
zipWithA_ f x y = sequenceA_ (zipWith f x y)<br>
<br>
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results.<br>
{-# INLINEABLE replicateA #-}<br>
{-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-}<br>
{-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-}<br>
replicateA :: (Applicative p) => Int -> p a -> p [a]<br>
replicateA n x = sequenceA (replicate n x)<br>
<br>
-- | 'replicateA_' is like 'replicateA', but discards the result.<br>
{-# INLINEABLE replicateA_ #-}<br>
{-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-}<br>
{-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-}<br>
replicateA_ :: (Applicative p) => Int -> p a -> p ()<br>
replicateA_ n x = sequenceA_ (replicate n x)<br>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div><br></div>
</div></div><br>_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
<br></blockquote></div><br></div>
<br>_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
<br></div>