pipes-3.2.0: Compositional pipelines

Safe HaskellSafe-Inferred

Control.Proxy.Prelude.Base

Contents

Description

General purpose proxies

Synopsis

Maps

mapD :: (Monad m, Proxy p) => (a -> b) -> x -> p x a x b m rSource

(mapD f) applies f to all values going 'D'ownstream.

 mapD f1 >-> mapD f2 = mapD (f2 . f1)

 mapD id = idT

mapU :: (Monad m, Proxy p) => (b' -> a') -> b' -> p a' x b' x m rSource

(mapU g) applies g to all values going 'U'pstream.

 mapU g1 >-> mapU g2 = mapU (g1 . g2)

 mapU id = idT

mapB :: (Monad m, Proxy p) => (a -> b) -> (b' -> a') -> b' -> p a' a b' b m rSource

(mapB f g) applies f to all values going downstream and g to all values going upstream.

Mnemonic: map 'B'idirectional

 mapB f1 g1 >-> mapB f2 g2 = mapB (f2 . f1) (g1 . g2)

 mapB id id = idT

mapMD :: (Monad m, Proxy p) => (a -> m b) -> x -> p x a x b m rSource

(mapMD f) applies the monadic function f to all values going downstream

 mapMD f1 >-> mapMD f2 = mapMD (f1 >=> f2)

 mapMD return = idT

mapMU :: (Monad m, Proxy p) => (b' -> m a') -> b' -> p a' x b' x m rSource

(mapMU g) applies the monadic function g to all values going upstream

 mapMU g1 >-> mapMU g2 = mapMU (g2 >=> g1)

 mapMU return = idT

mapMB :: (Monad m, Proxy p) => (a -> m b) -> (b' -> m a') -> b' -> p a' a b' b m rSource

(mapMB f g) applies the monadic function f to all values going downstream and the monadic function g to all values going upstream.

 mapMB f1 g1 >-> mapMB f2 g2 = mapMB (f1 >=> f2) (g2 >=> g1)

 mapMB return return = idT

useD :: (Monad m, Proxy p) => (a -> m r1) -> x -> p x a x a m rSource

(useD f) executes the monadic function f on all values flowing 'D'ownstream

 useD f1 >-> useD f2 = useD (\a -> f1 a >> f2 a)

 useD (\_ -> return ()) = idT

useU :: (Monad m, Proxy p) => (a' -> m r2) -> a' -> p a' x a' x m rSource

(useU g) executes the monadic function g on all values flowing 'U'pstream

 useU g1 >-> useU g2 = useU (\a' -> g2 a' >> g1 a')

 useU (\_ -> return ()) = idT

useB :: (Monad m, Proxy p) => (a -> m r1) -> (a' -> m r2) -> a' -> p a' a a' a m rSource

(useB f g) executes the monadic function f on all values flowing downstream and the monadic function g on all values flowing upstream

 useB f1 g1 >-> useB f2 g2 = useB (\a -> f1 a >> f2 a) (\a' -> g2 a' >> g1 a')

 useB (\_ -> return ()) (\_ -> return ()) = idT

execD :: (Monad m, Proxy p) => m r1 -> a' -> p a' a a' a m rSource

(execD md) executes md every time values flow downstream through it.

 execD md1 >-> execD md2 = execD (md1 >> md2)

 execD (return ()) = idT

execU :: (Monad m, Proxy p) => m r2 -> a' -> p a' a a' a m rSource

(execU mu) executes mu every time values flow upstream through it.

 execU mu1 >-> execU mu2 = execU (mu2 >> mu1)

 execU (return ()) = idT

execB :: (Monad m, Proxy p) => m r1 -> m r2 -> a' -> p a' a a' a m rSource

(execB md mu) executes mu every time values flow upstream through it, and executes md every time values flow downstream through it.

 execB md1 mu1 >-> execB md2 mu2 = execB (md1 >> md2) (mu2 >> mu1)

 execB (return ()) = idT

Filters

takeB :: (Monad m, Proxy p) => Int -> a' -> p a' a a' a m a'Source

(takeB n) allows n upstream/downstream roundtrips to pass through

 takeB n1 >=> takeB n2 = takeB (n1 + n2)  -- n1 >= 0 && n2 >= 0

 takeB 0 = return

takeB_ :: (Monad m, Proxy p) => Int -> a' -> p a' a a' a m ()Source

takeB_ is takeB with a () return value, convenient for composing

takeWhileD :: (Monad m, Proxy p) => (a -> Bool) -> a' -> p a' a a' a m ()Source

(takeWhileD p) allows values to pass downstream so long as they satisfy the predicate p.

 -- Using the "All" monoid over functions:
 mempty = \_ -> True
 (p1 <> p2) a = p1 a && p2 a

 takeWhileD p1 >-> takeWhileD p2 = takeWhileD (p1 <> p2)

 takeWhileD mempty = idT

takeWhileU :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> p a' a a' a m ()Source

(takeWhileU p) allows values to pass upstream so long as they satisfy the predicate p.

 takeWhileU p1 >-> takeWhileU p2 = takeWhileU (p1 <> p2)

 takeWhileD mempty = idT

dropD :: (Monad m, Proxy p) => Int -> () -> Pipe p a a m rSource

(dropD n) discards n values going downstream

 dropD n1 >-> dropD n2 = dropD (n1 + n2)  -- n2 >= 0 && n2 >= 0

 dropD 0 = idT

dropU :: (Monad m, Proxy p) => Int -> a' -> CoPipe p a' a' m rSource

(dropU n) discards n values going upstream

 dropU n1 >-> dropU n2 = dropU (n1 + n2)  -- n2 >= 0 && n2 >= 0

 dropU 0 = idT

dropWhileD :: (Monad m, Proxy p) => (a -> Bool) -> () -> Pipe p a a m rSource

(dropWhileD p) discards values going downstream until one violates the predicate p.

 -- Using the "Any" monoid over functions:
 mempty = \_ -> False
 (p1 <> p2) a = p1 a || p2 a

 dropWhileD p1 >-> dropWhileD p2 = dropWhileD (p1 <> p2)

 dropWhileD mempty = idT

dropWhileU :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> CoPipe p a' a' m rSource

(dropWhileU p) discards values going upstream until one violates the predicate p.

 dropWhileU p1 >-> dropWhileU p2 = dropWhileU (p1 <> p2)

 dropWhileU mempty = idT

filterD :: (Monad m, Proxy p) => (a -> Bool) -> () -> Pipe p a a m rSource

(filterD p) discards values going downstream if they fail the predicate p

 -- Using the "All" monoid over functions:
 mempty = \_ -> True
 (p1 <> p2) a = p1 a && p2 a

 filterD p1 >-> filterD p2 = filterD (p1 <> p2)

 filterD mempty = idT

filterU :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> CoPipe p a' a' m rSource

(filterU p) discards values going upstream if they fail the predicate p

 filterU p1 >-> filterU p2 = filterU (p1 <> p2)

 filterU mempty = idT

Lists

fromListS :: (Monad m, Proxy p) => [b] -> () -> Producer p b m ()Source

Convert a list into a Producer

 fromListS xs >=> fromListS ys = fromListS (xs ++ ys)

 fromListS [] = return

fromListC :: (Monad m, Proxy p) => [a'] -> () -> CoProducer p a' m ()Source

Convert a list into a CoProducer

 fromListC xs >=> fromListC ys = fromListC (xs ++ ys)

 fromListC [] = return

Enumerations

enumFromS :: (Enum b, Monad m, Proxy p) => b -> () -> Producer p b m rSource

Producer version of enumFrom

enumFromC :: (Enum a', Monad m, Proxy p) => a' -> () -> CoProducer p a' m rSource

CoProducer version of enumFrom

enumFromToS :: (Enum b, Ord b, Monad m, Proxy p) => b -> b -> () -> Producer p b m ()Source

Producer version of enumFromTo

enumFromToC :: (Enum a', Ord a', Monad m, Proxy p) => a' -> a' -> () -> CoProducer p a' m ()Source

ListT

eachS :: (Monad m, ListT p) => [b] -> ProduceT p m bSource

Non-deterministically choose from all values in the given list

 mappend <$> eachS xs <*> eachS ys = eachS (mappend <$> xs <*> ys)

 eachS (pure mempty) = pure mempty

eachC :: (Monad m, ListT p) => [a'] -> CoProduceT p m a'Source

Non-deterministically choose from all values in the given list

 mappend <$> eachC xs <*> eachC ys = eachC (mappend <$> xs <*> ys)

 eachC (pure mempty) = pure mempty

rangeS :: (Enum b, Ord b, Monad m, ListT p) => b -> b -> ProduceT p m bSource

Non-deterministically choose from all values in the given range

rangeC :: (Enum a', Ord a', Monad m, ListT p) => a' -> a' -> CoProduceT p m a'Source

Non-deterministically choose from all values in the given range

Folds

foldD :: (Monad m, Proxy p, Monoid w) => (a -> w) -> x -> p x a x a (WriterT w m) rSource

Fold values flowing 'D'ownstream

 foldD f >-> foldD g = foldD (f <> g)

 foldD mempty = idT

foldU :: (Monad m, Proxy p, Monoid w) => (a' -> w) -> a' -> p a' x a' x (WriterT w m) rSource

Fold values flowing 'U'pstream

 foldU f >-> foldU g = foldU (g <> f)

 foldU mempty = idT

allD :: (Monad m, Proxy p) => (a -> Bool) -> x -> p x a x a (WriterT All m) rSource

Fold that returns whether All values flowing 'D'ownstream satisfy the predicate

allU :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> p a' x a' x (WriterT All m) rSource

Fold that returns whether All values flowing 'U'pstream satisfy the predicate

allD_ :: (Monad m, Proxy p) => (a -> Bool) -> x -> p x a x a (WriterT All m) ()Source

Fold that returns whether All values flowing 'D'ownstream satisfy the predicate

allD_ terminates on the first value that fails the predicate

allU_ :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> p a' x a' x (WriterT All m) ()Source

Fold that returns whether All values flowing 'U'pstream satisfy the predicate

allU_ terminates on the first value that fails the predicate

anyD :: (Monad m, Proxy p) => (a -> Bool) -> x -> p x a x a (WriterT Any m) rSource

Fold that returns whether Any value flowing 'D'ownstream satisfies the predicate

anyU :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> p a' x a' x (WriterT Any m) rSource

Fold that returns whether Any value flowing 'U'pstream satisfies the predicate

anyD_ :: (Monad m, Proxy p) => (a -> Bool) -> x -> p x a x a (WriterT Any m) ()Source

Fold that returns whether Any value flowing 'D'ownstream satisfies the predicate

anyD_ terminates on the first value that satisfies the predicate

anyU_ :: (Monad m, Proxy p) => (a' -> Bool) -> a' -> p a' x a' x (WriterT Any m) ()Source

Fold that returns whether Any value flowing 'U'pstream satisfies the predicate

anyU_ terminates on the first value that satisfies the predicate

sumD :: (Monad m, Proxy p, Num a) => x -> p x a x a (WriterT (Sum a) m) rSource

Compute the Sum of all values that flow 'D'ownstream

sumU :: (Monad m, Proxy p, Num a') => a' -> p a' x a' x (WriterT (Sum a') m) rSource

Compute the Sum of all values that flow 'U'pstream

productD :: (Monad m, Proxy p, Num a) => x -> p x a x a (WriterT (Product a) m) rSource

Compute the Product of all values that flow 'D'ownstream

productU :: (Monad m, Proxy p, Num a') => a' -> p a' x a' x (WriterT (Product a') m) rSource

Compute the Product of all values that flow 'U'pstream

lengthD :: (Monad m, Proxy p) => x -> p x a x a (WriterT (Sum Int) m) rSource

Count how many values flow 'D'ownstream

lengthU :: (Monad m, Proxy p) => a' -> p a' x a' x (WriterT (Sum Int) m) rSource

Count how many values flow 'U'pstream

headD :: (Monad m, Proxy p) => x -> p x a x a (WriterT (First a) m) rSource

Retrieve the first value going 'D'ownstream

headD_ :: (Monad m, Proxy p) => x -> p x a x a (WriterT (First a) m) ()Source

Retrieve the first value going 'D'ownstream

headD_ terminates on the first value it receives

headU :: (Monad m, Proxy p) => a' -> p a' x a' x (WriterT (First a') m) rSource

Retrieve the first value going 'U'pstream

headU_ :: (Monad m, Proxy p) => a' -> p a' x a' x (WriterT (First a') m) ()Source

Retrieve the first value going 'U'pstream

headU_ terminates on the first value it receives

lastD :: (Monad m, Proxy p) => x -> p x a x a (WriterT (Last a) m) rSource

Retrieve the last value going 'D'ownstream

lastU :: (Monad m, Proxy p) => a' -> p a' x a' x (WriterT (Last a') m) rSource

Retrieve the last value going 'U'pstream

toListD :: (Monad m, Proxy p) => x -> p x a x a (WriterT [a] m) rSource

Fold the values flowing 'D'ownstream into a list

toListU :: (Monad m, Proxy p) => a' -> p a' x a' x (WriterT [a'] m) rSource

Fold the values flowing 'U'pstream into a list

foldrD :: (Monad m, Proxy p) => (a -> b -> b) -> x -> p x a x a (WriterT (Endo b) m) rSource

Fold equivalent to foldr

To see why, consider this isomorphic type for foldr:

 foldr :: (a -> b -> b) -> [a] -> Endo b

foldrU :: (Monad m, Proxy p) => (a' -> b -> b) -> a' -> p a' x a' x (WriterT (Endo b) m) rSource

Fold equivalent to foldr

foldlD' :: (Monad m, Proxy p) => (b -> a -> b) -> x -> p x a x a (StateT b m) rSource

Left strict fold over 'D'ownstream values

foldlU' :: (Monad m, Proxy p) => (b -> a' -> b) -> a' -> p a' x a' x (StateT b m) rSource

Left strict fold over 'U'pstream values

ArrowChoice

leftD and rightD satisfy the ArrowChoice laws using arr = mapD.

leftU and rightU satisfy the ArrowChoice laws using arr = mapU.

leftD :: (Monad m, ListT p) => (q -> p x a x b m r) -> q -> p x (Either a e) x (Either b e) m rSource

Lift a proxy to operate only on Left values flowing 'D'ownstream and forward Right values

rightD :: (Monad m, ListT p) => (q -> p x a x b m r) -> q -> p x (Either e a) x (Either e b) m rSource

Lift a proxy to operate only on Right values flowing 'D'ownstream and forward Left values

leftU :: (Monad m, ListT p) => (q -> p a' x b' x m r) -> q -> p (Either a' e) x (Either b' e) x m rSource

Lift a proxy to operate only on Left values flowing 'U'pstream and forward Right values

rightU :: (Monad m, ListT p) => (q -> p a' x b' x m r) -> q -> p (Either e a') x (Either e b') x m rSource

Lift a proxy to operate only on Right values flowing 'D'ownstream and forward Left values

Zips and Merges

zipD :: (Monad m, Proxy p1, Proxy p2, Proxy p3) => () -> Consumer p1 a (Consumer p2 b (Producer p3 (a, b) m)) rSource

Zip values flowing downstream

mergeD :: (Monad m, Proxy p1, Proxy p2, Proxy p3) => () -> Consumer p1 a (Consumer p2 a (Producer p3 a m)) rSource

Interleave values flowing downstream using simple alternation

Closed Adapters

Use the unit functions when you need to embed a proxy with a closed end within an open proxy. For example, the following code will not type-check because fromListS [1..] is a Producer and has a closed upstream end, which conflicts with the request statement preceding it:

 p () = do
     request ()
     fromList [1..] ()

You fix this by composing unitD upstream of it, which replaces its closed upstream end with an open polymorphic end:

 p () = do
     request ()
     (fromList [1..] <-< unitD) ()

unitD :: (Monad m, Proxy p) => q -> p x' x y' () m rSource

Compose unitD with a closed upstream end to create a polymorphic end

unitU :: (Monad m, Proxy p) => q -> p () x y' y m rSource

Compose unitU with a closed downstream end to create a polymorphic end

Modules

These modules help you build, run, and extract folds