box-0.8.1: boxes
Safe HaskellNone
LanguageHaskell2010

Box.Connectors

Description

Various ways to connect things up.

Synopsis

Documentation

qList :: MonadConc m => [a] -> CoEmitter m a Source #

Queue a list.

>>> pushList <$|> qList [1,2,3]
[1,2,3]

popList :: Monad m => [a] -> Committer m a -> m () Source #

Directly supply a list to a committer action, via pop.

>>> popList [1..3] showStdout
1
2
3

pushList :: Monad m => Emitter m a -> m [a] Source #

Push an Emitter into a list, via push.

>>> pushList <$|> qList [1..3]
[1,2,3]

pushListN :: Monad m => Int -> Emitter m a -> m [a] Source #

Push an Emitter into a list, finitely.

>>> pushListN 2 <$|> qList [1..3]
[1,2]

sink :: MonadConc m => Int -> (a -> m ()) -> CoCommitter m a Source #

Create a finite Committer.

>>> glue <$> sink 2 print <*|> qList [1..3]
1
2

source :: MonadConc m => Int -> m a -> CoEmitter m a Source #

Create a finite Emitter.

>>> glue toStdout <$|> source 2 (pure "hi")
hi
hi

forkEmit :: Monad m => Emitter m a -> Committer m a -> Emitter m a Source #

Glues an emitter to a committer, then resupplies the emitter.

>>> (c1,l1) <- refCommitter :: IO (Committer IO Int, IO [Int])
>>> close $ toListM <$> (forkEmit <$> (qList [1..3]) <*> pure c1)
[1,2,3]
>>> l1
[1,2,3]

bufferCommitter :: MonadConc m => Committer m a -> CoCommitter m a Source #

Buffer a committer.

bufferEmitter :: MonadConc m => Emitter m a -> CoEmitter m a Source #

Buffer an emitter.

concurrentE :: MonadConc f => Queue a -> Emitter f a -> Emitter f a -> CoEmitter f a Source #

Concurrently run two emitters.

This differs to (<>), which is left-biased.

Note that functions such as toListM, which complete on the first Nothing emitted, will not work as expected.

>>> close $ (fmap toListM) (join $ concurrentE Single <$> qList [1..3] <*> qList [5..9])
[1,2,3]

In the code below, the ordering is non-deterministic.

(c,l) <- refCommitter :: IO (Committer IO Int, IO [Int])
close $ glue c <$> (join $ concurrentE Single <$> qList [1..30] <*> qList [40..60])

concurrentC :: MonadConc m => Queue a -> Committer m a -> Committer m a -> CoCommitter m a Source #

Concurrently run two committers.

>>> import Data.Functor.Contravariant
>>> import Data.Text (pack)
>>> cFast = witherC (\b -> pure (Just b)) . contramap ("fast: " <>) $ toStdout
>>> cSlow = witherC (\b -> sleep 0.1 >> pure (Just b)) . contramap ("slow: " <>) $ toStdout
>>> close $ (popList ((pack . show) <$> [1..3]) <$> (concurrentC Unbounded cFast cSlow)) <> pure (sleep 1)
fast: 1
fast: 2
fast: 3
slow: 1
slow: 2
slow: 3