zipWithA, zipWithA_, mapAndUnzipA, filterA, replicateA, replicateA_

M Farkas-Dyck strake888 at gmail.com
Mon Mar 16 19:07:22 UTC 2015


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)


More information about the Libraries mailing list