pipes-3.3.0: Compositional pipelines

Safe HaskellSafe-Inferred

Control.Proxy.Prelude

Contents

Description

General purpose proxies

Synopsis

I/O

stdinS :: Proxy p => () -> Producer p String IO rSource

A Producer that sends lines from stdin downstream

 stdinS = hGetLineS stdin

stdoutD :: Proxy p => x -> p x String x String IO rSource

putStrLns all values flowing 'D'ownstream to stdout

 stdoutD = hPutStrLnD stdout

readLnS :: (Read b, Proxy p) => () -> Producer p b IO rSource

read input from stdin one line at a time and send 'D'ownstream

hGetLineS :: Proxy p => Handle -> () -> Producer p String IO ()Source

A Producer that sends lines from a handle downstream

hPutStrLnD :: Proxy p => Handle -> x -> p x String x String IO rSource

putStrLns all values flowing 'D'ownstream to a Handle

printD :: (Show a, Proxy p) => x -> p x a x a IO rSource

prints all values flowing 'D'ownstream to stdout

printU :: (Show a', Proxy p) => a' -> p a' x a' x IO rSource

prints all values flowing 'U'pstream to stdout

printB :: (Show a', Show a, Proxy p) => a' -> p a' a a' a IO rSource

prints all values flowing through it to stdout

Prefixes upstream values with "U: " and downstream values with "D: "

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 = pull

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 = pull

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 = pull

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 = pull

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 ()) = pull

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 ()) = pull

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 ()) = pull

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 ()) = pull

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 = pull

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 = pull

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 = pull

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 = pull

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 = pull

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 = pull

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 = pull

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 = pull

Lists and Enumerations

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

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

Producer version of enumFrom

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

Producer version of enumFromTo

eachS :: (Monad m, Proxy 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

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

Non-deterministically choose from all values in the given range

Folds

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

Strict fold over values flowing 'D'ownstream.

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

 foldD mempty = idPull

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

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

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

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

allD_ terminates on the first value that fails the predicate

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

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

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

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

anyD_ terminates on the first value that satisfies the predicate

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

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

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

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

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

Count how many values flow 'D'ownstream

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

Retrieve the first value going 'D'ownstream

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

Retrieve the first value going 'D'ownstream

headD_ terminates on the first value it receives

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

Retrieve the last value going 'D'ownstream

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

Fold the values flowing 'D'ownstream into a list

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

Fold equivalent to foldr

To see why, consider this isomorphic type for foldr:

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

ArrowChoice

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

leftD :: (Monad m, Proxy 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, Proxy 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

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

Kleisli utilities

foreverK :: Monad m => (a -> m a) -> a -> m bSource

Compose a 'K'leisli arrow with itself forever

Use foreverK to abstract away the following common recursion pattern:

 p a = do
     ...
     a' <- respond b
     p a'

Using foreverK, you can instead write:

 p = foreverK $ \a -> do
     ...
     respond b

Re-exports

Deprecated

To be removed in version 4.0.0

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

Deprecated: Combine mapD and mapU instead

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

Deprecated: Combine mapMD and mapMU instead

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

Deprecated: Combined useD and useU instead

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

Deprecated: Combine execD and execU instead

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

Deprecated: Use 'turn . fromListS xs' instead

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

Deprecated: Use 'turn . enumFromS n' instead

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

Deprecated: Use 'turn . enumFromToS n1 n2' instead

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

Deprecated: Use 'RequestT $ turn $ fromListS xs ()' instead

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

Deprecated: Use 'RequestT $ turn $ enumFromToS n1 n2 ()' instead

getLineS :: Proxy p => () -> Producer p String IO rSource

Deprecated: Use stdinS instead

getLineC :: Proxy p => () -> CoProducer p String IO rSource

Deprecated: Use 'turn . stdinS' instead

readLnC :: (Read a', Proxy p) => () -> CoProducer p a' IO rSource

Deprecated: Use 'turn . readLnC' instead

putStrLnD :: Proxy p => x -> p x String x String IO rSource

Deprecated: Use stdoutD instead

putStrLnU :: Proxy p => String -> p String x String x IO rSource

Deprecated: Use 'execU putStrLn' instead

putStrLnB :: Proxy p => String -> p String String String String IO rSource

Deprecated: Not that useful

hGetLineC :: Proxy p => Handle -> () -> CoProducer p String IO ()Source

Deprecated: Use 'turn . hGetLineS h'

hPutStrLnU :: Proxy p => Handle -> String -> p String x String x IO rSource

Deprecated: Not that useful

hPutStrLnB :: Proxy p => Handle -> String -> p String String String String IO rSource

Deprecated: Not that useful

hPrintD :: (Show a, Proxy p) => Handle -> x -> p x a x a IO rSource

Deprecated: Not that useful

prints all values flowing 'D'ownstream to a Handle

hPrintU :: (Show a', Proxy p) => Handle -> a' -> p a' x a' x IO rSource

Deprecated: Not that useful

prints all values flowing 'U'pstream to a Handle

hPrintB :: (Show a, Show a', Proxy p) => Handle -> a' -> p a' a a' a IO rSource

Deprecated: Not that useful

replicateK :: Monad m => Int -> (a -> m a) -> a -> m aSource

Deprecated: Not very useful

liftK :: (Monad m, MonadTrans t) => (a -> m b) -> a -> t m bSource

Deprecated: Use '(lift .)' instead

hoistKSource

Arguments

:: (Monad m, MFunctor t) 
=> (forall a. m a -> n a)

Monad morphism

-> (b' -> t m b)

Kleisli arrow

-> b' -> t n b 

Deprecated: Use '(hoist f .)' instead

raise :: (Monad m, MFunctor t1, MonadTrans t2) => t1 m r -> t1 (t2 m) rSource

Deprecated: Use 'hoist lift' instead

raiseK :: (Monad m, MFunctor t1, MonadTrans t2) => (q -> t1 m r) -> q -> t1 (t2 m) rSource

Deprecated: Use '(hoist lift .)' instead

hoistPKSource

Arguments

:: (Monad m, Proxy p1, PFunctor t) 
=> (forall _a' _a _b' _b _r. p1 _a' _a _b' _b m _r -> p2 _a' _a _b' _b n _r)

Proxy morphism

-> (q -> t p1 a' a b' b m r)

Proxy Kleisli arrow

-> q -> t p2 a' a b' b n r 

Deprecated: Use '(hoistP f .)' instead

raisePSource

Arguments

:: (Monad m, Proxy p, PFunctor t1, ProxyTrans t2) 
=> t1 p a' a b' b m r

Proxy

-> t1 (t2 p) a' a b' b m r 

Deprecated: Use 'hoistP liftP' instead

raisePKSource

Arguments

:: (Monad m, Proxy p, PFunctor t1, ProxyTrans t2) 
=> (q -> t1 p a' a b' b m r)

Proxy Kleisli arrow

-> q -> t1 (t2 p) a' a b' b m r 

Deprecated: Use '(hoistP liftP .)' instead