zipWithA, zipWithA_, mapAndUnzipA, filterA, replicateA, replicateA_

Analogs of monadic functions, which likely ought to be in base as part of AMP. I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import. -- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id -- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs -- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y) -- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y) -- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x) -- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x)

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.
I have no objection to generalizing the types of these combinators, however.
-Edward
On Mon, Mar 16, 2015 at 3:07 PM, M Farkas-Dyck
Analogs of monadic functions, which likely ought to be in base as part of AMP.
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.
-- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y)
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y)
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x)
-- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x) _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

should filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a]
perhaps be filterA :: (Applicative p) => (a -> p (Maybe be)) -> [a] -> p [b]
?
On Mon, Mar 16, 2015 at 3:34 PM, Edward Kmett
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.
I have no objection to generalizing the types of these combinators, however.
-Edward
On Mon, Mar 16, 2015 at 3:07 PM, M Farkas-Dyck
wrote: Analogs of monadic functions, which likely ought to be in base as part of AMP.
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.
-- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y)
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y)
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x)
-- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x) _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

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.
should filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a]
perhaps be filterA :: (Applicative p) => (a -> p (Maybe be)) -> [a] -> p [b]
?
On Mon, Mar 16, 2015 at 3:34 PM, Edward Kmett
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.
I have no objection to generalizing the types of these combinators, however.
-Edward
On Mon, Mar 16, 2015 at 3:07 PM, M Farkas-Dyck
wrote: Analogs of monadic functions, which likely ought to be in base as part of AMP.
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.
-- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y)
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y)
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x)
-- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x) _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Usually that second op is given a different name. e.g. filterMapM or something. On Mon, Mar 16, 2015 at 6:29 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
should filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] perhaps be filterA :: (Applicative p) => (a -> p (Maybe be)) -> [a] -> p [b] ?
On Mon, Mar 16, 2015 at 3:34 PM, Edward Kmett
wrote: 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.
I have no objection to generalizing the types of these combinators, however.
-Edward
On Mon, Mar 16, 2015 at 3:07 PM, M Farkas-Dyck
wrote: Analogs of monadic functions, which likely ought to be in base as part of AMP.
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.
-- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y)
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y)
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x)
-- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x) _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That sounds about right. Data.Maybe is out of the way enough few would object if we extending it to include that function. I'm pretty much +/- 0 on it. -Edward On Tue, Mar 17, 2015 at 4:09 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 16 Mar 2015, Edward Kmett wrote:
Usually that second op is given a different name. e.g. filterMapM or
something.
If it is a mapMaybe, why not mapMaybeA or mapMaybeM?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yes, that's a better name imo
Tom
El Mar 17, 2015, a las 4:09, Henning Thielemann
On Mon, 16 Mar 2015, Edward Kmett wrote:
Usually that second op is given a different name. e.g. filterMapM or something.
If it is a mapMaybe, why not mapMaybeA or mapMaybeM? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

+1
I feel the awkwardness of the current combinators at times.
2015-03-17 4:07 GMT+09:00 M Farkas-Dyck
Analogs of monadic functions, which likely ought to be in base as part of AMP.
I send no patch yet, for I not know which way to do the Data.Traversable <-> Control.Applicative cyclic import.
-- | 'filterA' generalizes the list-based 'filter' function. {-# INLINE filterA #-} filterA :: (Applicative p) => (a -> p Bool) -> [a] -> p [a] filterA p = foldr (\ x -> liftA2 (\ flg -> bool flg (x:) id) (p x)) (pure []) where bool True x = const x bool False _ = id
-- | 'mapAndUnzipA' maps its first argument over a list, returning the result as a pair of lists. {-# INLINE mapAndUnzipA #-} mapAndUnzipA :: (Applicative p) => (a -> p (b, c)) -> [a] -> p ([b], [c]) mapAndUnzipA f xs = unzip <$> traverse f xs
-- | 'zipWithA' generalizes 'zipWith' to arbitrary applicative functors. {-# INLINE zipWithA #-} zipWithA :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p [c] zipWithA f x y = sequenceA (zipWith f x y)
-- | 'zipWithA_' is the extension of 'zipWithA' which ignores the final result. {-# INLINE zipWithA_ #-} zipWithA_ :: (Applicative p) => (a -> b -> p c) -> [a] -> [b] -> p () zipWithA_ f x y = sequenceA_ (zipWith f x y)
-- | @'replicateA' n x@ does @x@ @n@ times, gathering the results. {-# INLINEABLE replicateA #-} {-# SPECIALIZE replicateA :: Int -> IO a -> IO [a] #-} {-# SPECIALIZE replicateA :: Int -> Maybe a -> Maybe [a] #-} replicateA :: (Applicative p) => Int -> p a -> p [a] replicateA n x = sequenceA (replicate n x)
-- | 'replicateA_' is like 'replicateA', but discards the result. {-# INLINEABLE replicateA_ #-} {-# SPECIALIZE replicateA_ :: Int -> IO a -> IO () #-} {-# SPECIALIZE replicateA_ :: Int -> Maybe a -> Maybe () #-} replicateA_ :: (Applicative p) => Int -> p a -> p () replicateA_ n x = sequenceA_ (replicate n x) _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (7)
-
amindfv@gmail.com
-
Carter Schonwald
-
David Feuer
-
Edward Kmett
-
Fumiaki Kinoshita
-
Henning Thielemann
-
M Farkas-Dyck