pipes-fluid-0.6.0.0: Reactively combines Producers so that a value is yielded as soon as possible.

Safe HaskellSafe
LanguageHaskell2010

Pipes.Fluid.Merge

Synopsis

Documentation

data Source Source #

Differentiates whether a value from either or both producers. In the case of one producer, additional identify if the other producer is live or dead.

Instances

Eq Source Source # 

Methods

(==) :: Source -> Source -> Bool #

(/=) :: Source -> Source -> Bool #

Ord Source Source # 
Show Source Source # 
Generic Source Source # 

Associated Types

type Rep Source :: * -> * #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

type Rep Source Source # 
type Rep Source = D1 (MetaData "Source" "Pipes.Fluid.Merge" "pipes-fluid-0.6.0.0-CCIcZQo3sQtBpRbWWcJis" False) ((:+:) (C1 (MetaCons "FromBoth" PrefixI False) U1) ((:+:) (C1 (MetaCons "FromLeft" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OtherStatus))) (C1 (MetaCons "FromRight" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OtherStatus)))))

data OtherStatus Source #

The other producer can be live (still yielding values), or dead

Constructors

OtherLive 
OtherDead 

data Merged a b Source #

Differentiates when only one side is available (due to initial merge values of Nothing) or if two values (one of which may be a previous values) are availabe.

Instances

(Eq b, Eq a) => Eq (Merged a b) Source # 

Methods

(==) :: Merged a b -> Merged a b -> Bool #

(/=) :: Merged a b -> Merged a b -> Bool #

(Ord b, Ord a) => Ord (Merged a b) Source # 

Methods

compare :: Merged a b -> Merged a b -> Ordering #

(<) :: Merged a b -> Merged a b -> Bool #

(<=) :: Merged a b -> Merged a b -> Bool #

(>) :: Merged a b -> Merged a b -> Bool #

(>=) :: Merged a b -> Merged a b -> Bool #

max :: Merged a b -> Merged a b -> Merged a b #

min :: Merged a b -> Merged a b -> Merged a b #

(Show b, Show a) => Show (Merged a b) Source # 

Methods

showsPrec :: Int -> Merged a b -> ShowS #

show :: Merged a b -> String #

showList :: [Merged a b] -> ShowS #

Generic (Merged a b) Source # 

Associated Types

type Rep (Merged a b) :: * -> * #

Methods

from :: Merged a b -> Rep (Merged a b) x #

to :: Rep (Merged a b) x -> Merged a b #

type Rep (Merged a b) Source # 

isBothLive :: Merged x y -> Bool Source #

This can be used with takeWhile

isLeftLive :: Merged x y -> Bool Source #

This can be used with takeWhile

isRightLive :: Merged x y -> Bool Source #

This can be used with takeWhile

isRightDead :: Merged x y -> Bool Source #

This can be used with takeWhile

isLeftDead :: Merged x y -> Bool Source #

This can be used with takeWhile

class Merge f where Source #

Minimal complete definition

merge'

Methods

merge' :: Maybe x -> Maybe y -> f x -> f y -> f (Merged x y) Source #

Instances

(MonadBaseControl IO m, Forall * (Pure m)) => Merge (ImpulseIO m) Source #

Reactively combines two producers, given initial values to use when the produce hasn't produced anything yet Combine two signals, and returns a signal that emits Either bothfired (Either (leftFired, previousRight) (previousLeft, rightFired)). This creates two threads each time this combinator is used. Warning: This means that the monadic effects are run in isolation from each other so if the monad is something like (StateT s IO), then the state will alternate between the two input producers, which is most likely not what you want. This will be detect as a compile error due to use of Control.Concurrent.Async.Lifted.Safe

Methods

merge' :: Maybe x -> Maybe y -> ImpulseIO m x -> ImpulseIO m y -> ImpulseIO m (Merged x y) Source #

(Alternative m, Monad m) => Merge (Impulse m) Source #

Impulseively combines two producers, given initial values to use when the produce hasn't produced anything yet Combine two signals, and returns a signal that emits Either bothfired (Either (leftFired, previousRight) (previousLeft, rightFired)). This only works for Alternative m where failure means there was no effects, eg. STM, or MonadTrans t => t STM. Be careful of monad transformers ExceptT that hides the STM Alternative instance.

Methods

merge' :: Maybe x -> Maybe y -> Impulse m x -> Impulse m y -> Impulse m (Merged x y) Source #

merge :: Merge f => f x -> f y -> f (Merged x y) Source #

discreteLeft :: Merged x y -> Maybe x Source #

Keep only the values originated from the left, replacing other yields with Nothing. This is useful when React is based on STM, since filtering with Producer STM results in larger STM transactions which may result in blocking.

discreteRight :: Merged x y -> Maybe y Source #

Keep only the values originated from the right, replacing other yields with Nothing. This is useful when React is based on STM, since filtering with Producer STM results in larger STM transactions which may result in blocking.

discreteBoth :: Merged x y -> Maybe (x, y) Source #

Keep only the values originated from both, replacing other yields with Nothing. This is useful when React is based on STM, since filtering with Producer STM results in larger STM transactions which may result in blocking.

discrete' :: Merged x x -> NonEmpty x Source #

Keep only the "new" values

discrete :: Semigroup x => Merged x x -> x Source #

Keep only the "new" values (using semigroup <> when both values were active)

mergeDiscrete' :: (Merge f, Functor f) => f x -> f x -> f (NonEmpty x) Source #

merge two producers of the same type together.

mergeDiscrete :: (Semigroup x, Merge f, Functor f) => f x -> f x -> f x Source #

merge two producers of the same type together (using semigroup <> when both values were active)