streamly-0.8.1.1: Dataflow programming and declarative concurrency
Copyright(c) 2021 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityreleased
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Data.Fold.Tee

Description

The Tee type is a newtype wrapper over the Fold type providing distributive Applicative, Semigroup, Monoid, Num, Floating and Fractional instances. The input received by the composed Tee is replicated and distributed to both the constituent Tees.

For example, to compute the average of numbers in a stream without going through the stream twice:

>>> import Streamly.Data.Fold.Tee (Tee(..))
>>> import qualified Streamly.Prelude as Stream
>>> import qualified Streamly.Data.Fold as Fold
>>> avg = (/) <$> (Tee Fold.sum) <*> (Tee $ fmap fromIntegral Fold.length)
>>> Stream.fold (toFold avg) $ Stream.fromList [1.0..100.0]
50.5

Similarly, the Semigroup and Monoid instances of Tee distribute the input to both the folds and combine the outputs using Monoid or Semigroup instances of the output types:

>>> import Data.Monoid (Sum(..))
>>> t = Tee Fold.head <> Tee Fold.last
>>> Stream.fold (toFold t) (fmap Sum $ Stream.enumerateFromTo 1.0 100.0)
Just (Sum {getSum = 101.0})

The Num, Floating, and Fractional instances work in the same way.

Synopsis

Documentation

newtype Tee m a b Source #

Tee is a newtype wrapper over the Fold type providing distributing Applicative, Semigroup, Monoid, Num, Floating and Fractional instances.

Since: 0.8.0

Constructors

Tee 

Fields

Instances

Instances details
Functor m => Functor (Tee m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

fmap :: (a0 -> b) -> Tee m a a0 -> Tee m a b #

(<$) :: a0 -> Tee m a b -> Tee m a a0 #

Monad m => Applicative (Tee m a) Source #

<*> distributes the input to both the argument Tees and combines their outputs using function application.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

pure :: a0 -> Tee m a a0 #

(<*>) :: Tee m a (a0 -> b) -> Tee m a a0 -> Tee m a b #

liftA2 :: (a0 -> b -> c) -> Tee m a a0 -> Tee m a b -> Tee m a c #

(*>) :: Tee m a a0 -> Tee m a b -> Tee m a b #

(<*) :: Tee m a a0 -> Tee m a b -> Tee m a a0 #

(Monad m, Floating b) => Floating (Tee m a b) Source #

Binary Floating operations distribute the input to both the argument Tees and combine their outputs using the Floating instance of the output type.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

pi :: Tee m a b #

exp :: Tee m a b -> Tee m a b #

log :: Tee m a b -> Tee m a b #

sqrt :: Tee m a b -> Tee m a b #

(**) :: Tee m a b -> Tee m a b -> Tee m a b #

logBase :: Tee m a b -> Tee m a b -> Tee m a b #

sin :: Tee m a b -> Tee m a b #

cos :: Tee m a b -> Tee m a b #

tan :: Tee m a b -> Tee m a b #

asin :: Tee m a b -> Tee m a b #

acos :: Tee m a b -> Tee m a b #

atan :: Tee m a b -> Tee m a b #

sinh :: Tee m a b -> Tee m a b #

cosh :: Tee m a b -> Tee m a b #

tanh :: Tee m a b -> Tee m a b #

asinh :: Tee m a b -> Tee m a b #

acosh :: Tee m a b -> Tee m a b #

atanh :: Tee m a b -> Tee m a b #

log1p :: Tee m a b -> Tee m a b #

expm1 :: Tee m a b -> Tee m a b #

log1pexp :: Tee m a b -> Tee m a b #

log1mexp :: Tee m a b -> Tee m a b #

(Monad m, Fractional b) => Fractional (Tee m a b) Source #

Binary Fractional operations distribute the input to both the argument Tees and combine their outputs using the Fractional instance of the output type.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

(/) :: Tee m a b -> Tee m a b -> Tee m a b #

recip :: Tee m a b -> Tee m a b #

fromRational :: Rational -> Tee m a b #

(Monad m, Num b) => Num (Tee m a b) Source #

Binary Num operations distribute the input to both the argument Tees and combine their outputs using the Num instance of the output type.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

(+) :: Tee m a b -> Tee m a b -> Tee m a b #

(-) :: Tee m a b -> Tee m a b -> Tee m a b #

(*) :: Tee m a b -> Tee m a b -> Tee m a b #

negate :: Tee m a b -> Tee m a b #

abs :: Tee m a b -> Tee m a b #

signum :: Tee m a b -> Tee m a b #

fromInteger :: Integer -> Tee m a b #

(Semigroup b, Monad m) => Semigroup (Tee m a b) Source #

<> distributes the input to both the argument Tees and combines their outputs using the Semigroup instance of the output type.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

(<>) :: Tee m a b -> Tee m a b -> Tee m a b #

sconcat :: NonEmpty (Tee m a b) -> Tee m a b #

stimes :: Integral b0 => b0 -> Tee m a b -> Tee m a b #

(Semigroup b, Monoid b, Monad m) => Monoid (Tee m a b) Source #

<> distributes the input to both the argument Tees and combines their outputs using the Monoid instance of the output type.

Instance details

Defined in Streamly.Internal.Data.Fold.Tee

Methods

mempty :: Tee m a b #

mappend :: Tee m a b -> Tee m a b -> Tee m a b #

mconcat :: [Tee m a b] -> Tee m a b #