zipWithA, zipWithA_, mapAndUnzipA, filterA, replicateA, replicateA_

Edward Kmett ekmett at gmail.com
Tue Mar 17 03:36:57 UTC 2015


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 at 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 <ekmett at gmail.com> 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 <strake888 at gmail.com>
>> 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 at haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>
>>
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20150316/39b17655/attachment.html>


More information about the Libraries mailing list