Add Streamly.Internal.Data.Fold.Tee

This commit is contained in:
Adithya Kumar 2021-01-22 07:22:15 +05:30 committed by Adithya Kumar
parent b9892e3119
commit bbfe463f0a
3 changed files with 54 additions and 0 deletions

View File

@ -84,6 +84,8 @@
* A bug was fixed in the conversion of MicroSecond64 and MilliSecond64
(commit e5119626)
* Bug fix: classifySessionsBy now flushes sessions at the end and terminates.
* `Streamly.Internal.Data.Fold.Tee` module added for folds with tee-like
applicative behaviour.
## 0.7.2

View File

@ -0,0 +1,51 @@
-- |
-- Module : Streamly.Internal.Data.Fold.Tee
-- Copyright : (c) 2020 Composewell Technologies
-- License : BSD-3-Clause
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
module Streamly.Internal.Data.Fold.Tee
( Tee(..)
, fromFold
, toFold
)
where
import Data.Coerce (coerce)
import Streamly.Internal.Data.Fold.Types (Fold)
import qualified Streamly.Internal.Data.Fold.Types as Fold
-- | The type @Tee m a b@ represents a left fold over an input stream of values
-- of type @a@ to a single value of type @b@ in 'Monad' @m@.
--
-- @Tee@ is a wrapper over 'Fold' that uses 'teeWith' to define the applicative
-- instance.
--
-- /Internal/
newtype Tee m a b =
Tee { runTee :: Fold m a b }
deriving (Functor)
-- | Convert a 'Tee' to 'Fold'.
{-# INLINE toFold #-}
toFold :: Tee m a b -> Fold m a b
toFold = coerce
-- | Convert a 'Fold' to 'Tee'.
{-# INLINE fromFold #-}
fromFold :: Fold m a b -> Tee m a b
fromFold = coerce
-- | The 'Tee' resulting from '<*>' distributes its input to both the argument
-- 'Tee's and combines their output using function application.
--
instance Monad m => Applicative (Tee m a) where
{-# INLINE pure #-}
pure a = fromFold (Fold.yield a)
{-# INLINE (<*>) #-}
(<*>) a b = fromFold (Fold.teeWith ($) (toFold a) (toFold b))

View File

@ -468,6 +468,7 @@ library
-- streamly-core
, Streamly.Internal.Data.Unfold
, Streamly.Internal.Data.Fold.Tee
, Streamly.Internal.Data.Fold
, Streamly.Internal.Data.Sink
, Streamly.Internal.Data.Parser