Control.Concatenative brings concatenative combinators in the style of factor (see http://docs.factorcode.org/content/article-dataflow-combinators.html) to haskell in a variety of interfaces, allowing a terse, pointfree style.
- bi :: (a -> b) -> (a -> c) -> (b -> c -> d) -> a -> d
- tri :: (a -> b) -> (a -> c) -> (a -> d) -> (b -> c -> d -> e) -> a -> e
- biSp :: (a -> c) -> (b -> d) -> (c -> d -> e) -> a -> b -> e
- triSp :: (a -> d) -> (b -> e) -> (c -> f) -> (d -> e -> f -> g) -> a -> b -> c -> g
- biAp :: (t -> t1) -> (t1 -> t1 -> t2) -> t -> t -> t2
- triAp :: (a -> b) -> (b -> b -> b -> c) -> a -> a -> a -> c
- ifte :: (a -> Bool) -> (a -> b) -> (a -> b) -> a -> b
- biM :: Monad m => (a -> m b) -> (a -> m c) -> (b -> c -> m d) -> a -> m d
- triM :: Monad m => (a -> m b) -> (a -> m c) -> (a -> m d) -> (b -> c -> d -> m e) -> a -> m e
- biSpM :: Monad m => (a -> m c) -> (b -> m d) -> (c -> d -> m e) -> a -> b -> m e
- triSpM :: Monad m => (a -> m d) -> (b -> m e) -> (c -> m f) -> (d -> e -> f -> m g) -> a -> b -> c -> m g
- biApM :: Monad m => (t -> m t1) -> (t1 -> t1 -> m t2) -> t -> t -> m t2
- triApM :: Monad m => (a -> m b) -> (b -> b -> b -> m c) -> a -> a -> a -> m c
- biM_ :: Monad m => (a -> m b) -> (a -> m c) -> a -> m ()
- triM_ :: Monad m => (a -> m b) -> (a -> m c) -> (a -> m d) -> a -> m ()
- biApM_ :: Monad m => (t -> m t1) -> t -> t -> m ()
- triApM_ :: Monad m => (a -> m b) -> a -> a -> a -> m ()
- (>>@) :: Arrow a => a b (x, y) -> (x -> y -> z) -> a b z
- dup :: Arrow a => a b (b, b)
- swap :: Arrow a => a (x, y) (y, x)
- both :: Arrow a => a b c -> a (b, b) (c, c)
- (>>.) :: Arrow a => a b c -> a c d -> a b d
- (&&.) :: Arrow a => a b c -> a b c' -> a b (c, c')
- (**.) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c')
- first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d)
- second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c)
- newtype Concatenative a b c d = Concatenative {
- with :: (b -> c) -> a -> d
- cat :: (a -> b) -> Concatenative a b c c
- (&.) :: (a -> b) -> (a -> e) -> Concatenative a b (e -> c) c
- (.&.) :: Concatenative a b c d -> (a -> e) -> Concatenative a b (e -> c) d
- (*.) :: (t -> b) -> (a -> b1) -> Concatenative a b (b1 -> c) (t -> c)
- (.*.) :: Concatenative a b c d -> (e -> f) -> Concatenative e b (f -> c) (a -> d)
- catM :: Monad m => (a -> m b) -> Concatenative a b (m c) (m c)
- clM :: Monad m => Concatenative a b c (m d) -> (a -> m e) -> Concatenative a b (e -> c) (m d)
- cl :: Monad m => (a -> m b) -> (a -> m e) -> Concatenative a b (e -> m d) (m d)
- spM :: Monad m => Concatenative a b c (m d) -> (e -> m f) -> Concatenative e b (f -> c) (a -> m d)
- sp :: Monad m => (a -> m b) -> (e -> m f) -> Concatenative e b (f -> m d) (a -> m d)
- apN :: Int -> Q Exp
- apM :: Int -> Q Exp
- apM_ :: Monad m => Int -> m a -> m ()
Postfix combinators
These concatenative combinators essentially apply multiple functions to one or more values before combining all the results using another function. Without concatenative combinators:
\x-> (x+1) + (subtract 1 x)
With concatenative combinators:
bi (+1) (subtract 1) (+)
bi :: (a -> b) -> (a -> c) -> (b -> c -> d) -> a -> dSource
Apply both arguments to a and combine the results
tri :: (a -> b) -> (a -> c) -> (a -> d) -> (b -> c -> d -> e) -> a -> eSource
Apply each of three arguments to a and combine the results
biSp :: (a -> c) -> (b -> d) -> (c -> d -> e) -> a -> b -> eSource
Apply the first argument to a, the second to b, and combine the results
triSp :: (a -> d) -> (b -> e) -> (c -> f) -> (d -> e -> f -> g) -> a -> b -> c -> gSource
Apply the first argument to a, the second to b, and the third to c, combining the results
biAp :: (t -> t1) -> (t1 -> t1 -> t2) -> t -> t -> t2Source
Apply a function to two values and combine the results
triAp :: (a -> b) -> (b -> b -> b -> c) -> a -> a -> a -> cSource
Apply a function to three values and combine the results
:: (a -> Bool) | A predicate |
-> (a -> b) | Applied if the predicate yields True |
-> (a -> b) | Applied if the predicate yields False |
-> a | |
-> b |
biM :: Monad m => (a -> m b) -> (a -> m c) -> (b -> c -> m d) -> a -> m dSource
Like bi
, but functions can return monadic values
triM :: Monad m => (a -> m b) -> (a -> m c) -> (a -> m d) -> (b -> c -> d -> m e) -> a -> m eSource
Like tri
, but functions can return monadic values
biSpM :: Monad m => (a -> m c) -> (b -> m d) -> (c -> d -> m e) -> a -> b -> m eSource
Like biSp
, but functions can return monadic values
triSpM :: Monad m => (a -> m d) -> (b -> m e) -> (c -> m f) -> (d -> e -> f -> m g) -> a -> b -> c -> m gSource
Like triSp
, but functions can return monadic values
biApM :: Monad m => (t -> m t1) -> (t1 -> t1 -> m t2) -> t -> t -> m t2Source
Like biAp
, but functions can return monadic values
triApM :: Monad m => (a -> m b) -> (b -> b -> b -> m c) -> a -> a -> a -> m cSource
Like triAp
, but functions can return monadic values
biM_ :: Monad m => (a -> m b) -> (a -> m c) -> a -> m ()Source
Like biM
, but throws away the end result
triM_ :: Monad m => (a -> m b) -> (a -> m c) -> (a -> m d) -> a -> m ()Source
Like triM
, but throws away the end result
triApM_ :: Monad m => (a -> m b) -> a -> a -> a -> m ()Source
Like triApM
, but throws away the end result
Postfix arrows
The arrow functions &&.
and **.
are equivalent to bi
and biSp
.
Combining here must be done seperately, through the >>@
function.
first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d)
Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.
second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c)
A mirror image of first
.
The default definition may be overridden with a more efficient version if desired.
Generalized Datatypes
The Concatenative datatype can be used to cleave, spread, or
apply any number of functions and values.
Using the bi
combinator:
bi (+1) (subtract 1) (+)
is equivalent to using the &.
function:
with ((+1) &. (subtract 1)) (+)
and may be generalized to any number of functions:
with ((subtract 10) &. (+1) .&. (*50)) enumFromThenTo
*.
similarly generalizes biSp
, and cl
and sp
generalize
their monadic variants. Generic application presents a problem for the
type system, however, and the library resorts to template haskell:
biAp (+1)
translates to
$(apN 2) (+1)
newtype Concatenative a b c d Source
Concatenative continuation
Concatenative | |
|
cat :: (a -> b) -> Concatenative a b c cSource
Lifts a function into Concatenative
(&.) :: (a -> b) -> (a -> e) -> Concatenative a b (e -> c) cSource
Lift a function and add it to a Concatenative
for cleaving
(.&.) :: Concatenative a b c d -> (a -> e) -> Concatenative a b (e -> c) dSource
Construct a Concatenative
for cleaving
(*.) :: (t -> b) -> (a -> b1) -> Concatenative a b (b1 -> c) (t -> c)Source
Lift a function and add it to a Concatenative
for spreading
(.*.) :: Concatenative a b c d -> (e -> f) -> Concatenative e b (f -> c) (a -> d)Source
Construct a Concatenative
for spreading
catM :: Monad m => (a -> m b) -> Concatenative a b (m c) (m c)Source
Lift a monadic function to a Concatenative
clM :: Monad m => Concatenative a b c (m d) -> (a -> m e) -> Concatenative a b (e -> c) (m d)Source
Construct a Concatenative
for spreading monadic functions
cl :: Monad m => (a -> m b) -> (a -> m e) -> Concatenative a b (e -> m d) (m d)Source
Lift a monadic function and add it to a Concatenative
for cleaving
spM :: Monad m => Concatenative a b c (m d) -> (e -> m f) -> Concatenative e b (f -> c) (a -> m d)Source
Construct a Concatenative
for spreading monadic functions
sp :: Monad m => (a -> m b) -> (e -> m f) -> Concatenative e b (f -> m d) (a -> m d)Source
Lift a monadic function and add it to a Concatenative
for spreading
Create a Concatenative
for applying a monadic function n times
biApM (+1)
translates to
$(apM 2) (+1)