Remove Applicative instance of Fold

This commit is contained in:
Adithya Kumar 2021-03-04 18:44:02 +05:30 committed by Adithya Kumar
parent d79dd95a13
commit 171907e2b3
6 changed files with 16 additions and 142 deletions

View File

@ -1,10 +1,5 @@
## Unreleased
### Notice
* In the next major release the behaviour of `<*>` for folds will be updated
from `teeWith` to `splitWith` to reflect it's similarity with parsers.
### Behavioral changes
* `Streamly.Prelude.fold` can now terminate early without consuming the entire
@ -31,6 +26,8 @@
require an additional `MonadAsync` constraint. Several other
functions that used these functions also now require the additional
constraint.
* Remove `Applicative` instance of folds. Please use `teeWith` or the `Tee` type
as an alternative to Fold applicative.
### Enhancements

View File

@ -70,7 +70,7 @@ takeLE value = IP.fold (FL.takeLE value FL.drain)
{-# INLINE sequence_ #-}
sequence_ :: Monad m => Int -> Fold m a ()
sequence_ value = foldr f (pure ()) (Prelude.replicate value (FL.takeLE 1 FL.drain))
sequence_ value = foldr f (FL.yield ()) (Prelude.replicate value (FL.takeLE 1 FL.drain))
where
@ -118,10 +118,14 @@ split_ value =
teeSumLength :: Monad m => SerialT m Int -> m (Int, Int)
teeSumLength = IP.fold (FL.teeWith (,) FL.sum FL.length)
{-# INLINE teeApplicative #-}
teeApplicative :: (Monad m, Ord a) => a -> SerialT m a -> m (Bool, Bool)
teeApplicative value =
IP.fold ((,) <$> FL.all (<= value) <*> FL.any (> value))
{-# INLINE teeAllAny #-}
teeAllAny :: (Monad m, Ord a) => a -> SerialT m a -> m (Bool, Bool)
teeAllAny value = IP.fold (FL.teeWith (,) all_ any_)
where
all_ = FL.all (<= value)
any_ = FL.any (> value)
{-# INLINE distribute #-}
distribute :: Monad m => SerialT m Int -> m [Int]
@ -272,8 +276,7 @@ o_1_space_serial_composition value =
[ bgroup
"composition"
[ benchIOSink value "splitWith (all, any)" $ splitAllAny value
, benchIOSink value "teeApplicative (all, any)"
$ teeApplicative value
, benchIOSink value "tee (all, any)" $ teeAllAny value
, benchIOSink value "many drain (takeLE 1)" many
, benchIOSink value "tee (sum, length)" teeSumLength
, benchIOSink value "distribute [sum, length]" distribute

View File

@ -199,7 +199,7 @@ module Streamly.Data.Fold
-- To compute the average of numbers in a stream without going through the
-- stream twice:
--
-- >>> let avg = (/) <$> Fold.sum <*> fmap fromIntegral Fold.length
-- >>> let avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
-- >>> Stream.fold avg (Stream.enumerateFromTo 1.0 100.0)
-- 50.5
--

View File

@ -602,7 +602,7 @@ variance = mkAccum step begin done
-- @since 0.7.0
{-# INLINABLE stdDev #-}
stdDev :: (Monad m, Floating a) => Fold m a a
stdDev = sqrt variance
stdDev = sqrt <$> variance
-- | Compute an 'Int' sized polynomial rolling hash
--

View File

@ -229,7 +229,6 @@ module Streamly.Internal.Data.Fold.Types
)
where
import Control.Applicative (liftA2)
import Control.Concurrent (threadDelay, forkIO, killThread)
import Control.Concurrent.MVar (MVar, newMVar, swapMVar, readMVar)
import Control.Exception (SomeException(..), catch, mask)
@ -573,26 +572,6 @@ data GenericRunner sL sR bL bR
| RunLeft !sL !bR
| RunRight !bL !sR
-- | The fold resulting from '<*>' distributes its input to both the argument
-- folds and combines their output using the supplied function.
--
-- __Note:__ The Applicative behaviour will change in the next major release.
--
instance Monad m => Applicative (Fold m a) where
{-# INLINE pure #-}
pure = yield
-- | __Notice:__ In the next major release the behaviour of @<*>@ for folds
-- will be updated from 'teeWith' to 'splitWith' to reflect it's similarity
-- with parsers.
{-# INLINE (<*>) #-}
(<*>) = teeWith ($)
#if MIN_VERSION_base(4,10,0)
{-# INLINE liftA2 #-}
liftA2 f x = (<*>) (fmap f x)
#endif
-- | @teeWith k f1 f2@ distributes its input to both @f1@ and @f2@ until both
-- of them terminate and combines their output using @k@.
--
@ -746,111 +725,6 @@ concatMap f (Fold stepa initiala extracta) = Fold stepc initialc extractc
Partial s -> e s
Done c -> return c
-- | Combines the outputs of the folds (the type @b@) using their 'Semigroup'
-- instances.
instance (Semigroup b, Monad m) => Semigroup (Fold m a b) where
{-# INLINE (<>) #-}
(<>) = liftA2 (<>)
-- | Combines the outputs of the folds (the type @b@) using their 'Monoid'
-- instances.
instance (Semigroup b, Monoid b, Monad m) => Monoid (Fold m a b) where
{-# INLINE mempty #-}
mempty = pure mempty
{-# INLINE mappend #-}
mappend = (<>)
-- | Combines the fold outputs (type @b@) using their 'Num' instances.
instance (Monad m, Num b) => Num (Fold m a b) where
{-# INLINE fromInteger #-}
fromInteger = pure . fromInteger
{-# INLINE negate #-}
negate = fmap negate
{-# INLINE abs #-}
abs = fmap abs
{-# INLINE signum #-}
signum = fmap signum
{-# INLINE (+) #-}
(+) = liftA2 (+)
{-# INLINE (*) #-}
(*) = liftA2 (*)
{-# INLINE (-) #-}
(-) = liftA2 (-)
-- | Combines the fold outputs (type @b@) using their 'Fractional' instances.
instance (Monad m, Fractional b) => Fractional (Fold m a b) where
{-# INLINE fromRational #-}
fromRational = pure . fromRational
{-# INLINE recip #-}
recip = fmap recip
{-# INLINE (/) #-}
(/) = liftA2 (/)
-- | Combines the fold outputs using their 'Floating' instances.
instance (Monad m, Floating b) => Floating (Fold m a b) where
{-# INLINE pi #-}
pi = pure pi
{-# INLINE exp #-}
exp = fmap exp
{-# INLINE sqrt #-}
sqrt = fmap sqrt
{-# INLINE log #-}
log = fmap log
{-# INLINE sin #-}
sin = fmap sin
{-# INLINE tan #-}
tan = fmap tan
{-# INLINE cos #-}
cos = fmap cos
{-# INLINE asin #-}
asin = fmap asin
{-# INLINE atan #-}
atan = fmap atan
{-# INLINE acos #-}
acos = fmap acos
{-# INLINE sinh #-}
sinh = fmap sinh
{-# INLINE tanh #-}
tanh = fmap tanh
{-# INLINE cosh #-}
cosh = fmap cosh
{-# INLINE asinh #-}
asinh = fmap asinh
{-# INLINE atanh #-}
atanh = fmap atanh
{-# INLINE acosh #-}
acosh = fmap acosh
{-# INLINE (**) #-}
(**) = liftA2 (**)
{-# INLINE logBase #-}
logBase = liftA2 logBase
------------------------------------------------------------------------------
-- Internal APIs
------------------------------------------------------------------------------

View File

@ -997,12 +997,12 @@ import Streamly.Internal.Data.Stream.IsStream
-- running average of elements is no more than 10:
--
-- >>> import Data.Maybe (fromJust)
-- >>> let avg = (/) <$> Fold.sum <*> fmap fromIntegral Fold.length
-- >>> let avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
-- >>> :{
-- Stream.toList
-- $ Stream.map (fromJust . fst)
-- $ Stream.takeWhile (\(_,x) -> x <= 10)
-- $ Stream.postscan ((,) <$> Fold.last <*> avg) (Stream.enumerateFromTo 1.0 100.0)
-- $ Stream.postscan (Fold.tee Fold.last avg) (Stream.enumerateFromTo 1.0 100.0)
-- :}
-- [1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
--