pipes-2.5.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell98

Control.Proxy.Prelude.Base

Contents

Description

General purpose proxies

Synopsis

Maps

mapB :: Monad m => (a -> b) -> (b' -> a') -> b' -> Proxy a' a b' b m r Source #

(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

mapD :: Monad m => (a -> b) -> x -> Proxy x a x b m r Source #

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

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

mapD id = idT

mapU :: Monad m => (b' -> a') -> b' -> Proxy a' x b' x m r Source #

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

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

mapU id = idT

mapMB :: Monad m => (a -> m b) -> (b' -> m a') -> b' -> Proxy a' a b' b m r Source #

(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

mapMD :: Monad m => (a -> m b) -> x -> Proxy x a x b m r Source #

(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 => (b' -> m a') -> b' -> Proxy a' x b' x m r Source #

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

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

mapMU return = idT

execB :: Monad m => m () -> m () -> a' -> Proxy a' a a' a m r Source #

(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

execD :: Monad m => m () -> a' -> Proxy a' a a' a m r Source #

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

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

execD (return ()) = idT

execU :: Monad m => m () -> a' -> Proxy a' a a' a m r Source #

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

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

execU (return ()) = idT

Filters

takeB :: Monad m => Int -> a' -> Proxy 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 => Int -> a' -> Proxy a' a a' a m () Source #

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

takeWhileD :: Monad m => (a -> Bool) -> a' -> Proxy 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 => (a' -> Bool) -> a' -> Proxy 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 => Int -> () -> Proxy () a () a m r Source #

(dropD n) discards n values going downstream

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

dropD 0 = idT

dropU :: Monad m => Int -> a' -> Proxy a' () a' () m r Source #

(dropU n) discards n values going upstream

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

dropU 0 = idT

dropWhileD :: Monad m => (a -> Bool) -> () -> Proxy () a () a m r Source #

(dropWhileD p) discards values going upstream 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 => (a' -> Bool) -> a' -> Proxy a' () a' () m r Source #

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

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

dropWhileU mempty = idT

filterD :: Monad m => (a -> Bool) -> () -> Proxy () a () a m r Source #

(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 => (a' -> Bool) -> a' -> Proxy a' () a' () m r Source #

(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 => [a] -> () -> Proxy x' x () a m () Source #

Convert a list into a Server

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

fromListS [] = return

fromListC :: Monad m => [a] -> () -> Proxy a x () y m () Source #

Convert a list into a Client

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

fromListC [] = return

Enumerations

enumFromS :: (Enum a, Monad m) => a -> y' -> Proxy x' x y' a m r Source #

Server version of enumFrom

enumFromC :: (Enum a, Monad m) => a -> y' -> Proxy a x y' y m r Source #

Client version of enumFrom

enumFromToS :: (Enum a, Ord a, Monad m) => a -> a -> y' -> Proxy x' x y' a m () Source #

Server version of enumFromTo

enumFromToC :: (Enum a, Ord a, Monad m) => a -> a -> y' -> Proxy a x y' y m () Source #

Client version of enumFromTo