{-# LANGUAGE NoImplicitPrelude #-} module Precursor.Control.Applicative ( -- * Applicative functors Applicative , pure , (<*>) , (*>) , (<*) -- * Instances , Const(..) , WrappedArrow(..) , ZipList(..) -- * Utility functions , liftA2 , (<**>) , forever , when , unless , replicateA , replicateA_ , filterA ) where import Control.Applicative import Control.Monad import Precursor.Data.Bool import Precursor.Numeric.Num import qualified Prelude -- | @'replicateA' n act@ performs the action @n@ times, -- gathering the results. replicateA :: (Applicative f) => Prelude.Int -> f a -> f [a] {-# INLINEABLE replicateA #-} {-# SPECIALISE replicateA :: Prelude.Int -> Prelude.IO a -> Prelude.IO [a] #-} {-# SPECIALISE replicateA :: Prelude.Int -> Prelude.Maybe a -> Prelude.Maybe [a] #-} replicateA cnt0 f = loop cnt0 where loop cnt | cnt Prelude.<= 0 = pure [] | otherwise = liftA2 (:) f (loop (cnt Prelude.- 1)) -- | Like 'replicateA', but discards the result. replicateA_ :: (Applicative f) => Prelude.Int -> f a -> f () {-# INLINEABLE replicateA_ #-} {-# SPECIALISE replicateA_ :: Prelude.Int -> Prelude.IO a -> Prelude.IO () #-} {-# SPECIALISE replicateA_ :: Prelude.Int -> Prelude.Maybe a -> Prelude.Maybe () #-} replicateA_ cnt0 f = loop cnt0 where loop cnt | cnt Prelude.<= 0 = pure () | otherwise = f *> loop (cnt Prelude.- 1) -- | This generalizes the list-based 'Precursor.Data.List.filter' function. {-# INLINE filterA #-} filterA :: Applicative f => (a -> f Bool) -> [a] -> f [a] filterA = filterM