composition-prelude-3.0.0.2: Higher-order function combinators
Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Composition

Synopsis
  • (.*) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
  • (.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
  • (.***) :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f
  • (.****) :: (f -> g) -> (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> g
  • (.*****) :: (g -> h) -> (a -> b -> c -> d -> e -> f -> g) -> a -> b -> c -> d -> e -> f -> h
  • (.******) :: (h -> i) -> (a -> b -> c -> d -> e -> f -> g -> h) -> a -> b -> c -> d -> e -> f -> g -> i
  • (-.) :: (a -> b) -> (b -> c) -> a -> c
  • (.@) :: (b -> c) -> (a -> c -> d) -> a -> b -> d
  • (.@@) :: (c -> d) -> (a -> b -> d -> e) -> a -> b -> c -> e
  • (.@@@) :: (d -> e) -> (a -> b -> c -> e -> f) -> a -> b -> c -> d -> f
  • (.@@@@) :: (e -> f) -> (a -> b -> c -> d -> f -> g) -> a -> b -> c -> d -> e -> g
  • (.@@@@@) :: (f -> g) -> (a -> b -> c -> d -> e -> g -> h) -> a -> b -> c -> d -> e -> f -> h
  • (<=*<) :: Monad m => (c -> m d) -> (a -> b -> m c) -> a -> b -> m d
  • (<=**<) :: Monad m => (d -> m e) -> (a -> b -> c -> m d) -> a -> b -> c -> m e
  • (>=**>) :: Monad m => (a -> b -> c -> m d) -> (d -> m e) -> a -> b -> c -> m e
  • (>=*>) :: Monad m => (a -> b -> m c) -> (c -> m d) -> a -> b -> m d
  • (<-=*<) :: Monad m => (b -> m c) -> (a -> c -> m d) -> a -> b -> m d
  • (>-=*>) :: Monad m => (a -> c -> m d) -> (b -> m c) -> a -> b -> m d
  • (<-=**<) :: Monad m => (c -> m d) -> (a -> b -> d -> m e) -> a -> b -> c -> m e
  • (>-=**>) :: Monad m => (a -> b -> d -> m e) -> (c -> m d) -> a -> b -> c -> m e
  • between :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d
  • (~@~) :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d
  • betweenM :: Monad m => (c -> m d) -> (a -> m b) -> (b -> m c) -> a -> m d
  • (<~@~<) :: Monad m => (c -> m d) -> (a -> m b) -> (b -> m c) -> a -> m d
  • (-$) :: (a -> b -> c) -> b -> a -> c
  • bisequence' :: (Traversable t, Applicative f) => t (a -> b -> f c) -> a -> b -> t (f c)
  • (.$) :: Monad m => m (m a) -> m a
  • axe :: (Traversable t, Applicative f) => t (a -> f ()) -> a -> f ()
  • biaxe :: (Traversable t, Applicative f) => t (a -> b -> f ()) -> a -> b -> f ()
  • thread :: Foldable t => t (a -> a) -> a -> a
  • threadM :: (Monad m, Foldable t, Applicative m) => t (a -> m a) -> a -> m a
  • both :: (a -> b) -> (a, a) -> (b, b)
  • dup :: a -> (a, a)
  • (+>) :: (a -> b) -> (a, a) -> (b, b)
  • (&:) :: (b -> b -> c) -> (a -> b) -> a -> a -> c
  • (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
  • (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
  • (<**>) :: Applicative f => f a -> f (a -> b) -> f b
  • (&) :: a -> (a -> b) -> b
  • (<&>) :: Functor f => f a -> (a -> b) -> f b
  • fix :: (a -> a) -> a
  • on :: (b -> b -> c) -> (a -> b) -> a -> a -> c

Postcomposition

(.*) :: (c -> d) -> (a -> b -> c) -> a -> b -> d infixr 8 Source #

(.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e infixr 8 Source #

(.***) :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f infixr 8 Source #

(.****) :: (f -> g) -> (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> g infixr 8 Source #

Since: 1.0.0.0

(.*****) :: (g -> h) -> (a -> b -> c -> d -> e -> f -> g) -> a -> b -> c -> d -> e -> f -> h infixr 8 Source #

Since: 2.0.5.0

(.******) :: (h -> i) -> (a -> b -> c -> d -> e -> f -> g -> h) -> a -> b -> c -> d -> e -> f -> g -> i infixr 8 Source #

Since: 2.0.5.0

Precomposition

(-.) :: (a -> b) -> (b -> c) -> a -> c infixr 8 Source #

Backwards function composition. This is a specialization of <&>, but it has a different fixity.

(.@) :: (b -> c) -> (a -> c -> d) -> a -> b -> d infixr 8 Source #

Since: 2.0.3.0

(.@@) :: (c -> d) -> (a -> b -> d -> e) -> a -> b -> c -> e infixr 8 Source #

Since: 2.0.3.0

(.@@@) :: (d -> e) -> (a -> b -> c -> e -> f) -> a -> b -> c -> d -> f infixr 8 Source #

Since: 2.0.3.0

(.@@@@) :: (e -> f) -> (a -> b -> c -> d -> f -> g) -> a -> b -> c -> d -> e -> g infixr 8 Source #

Since: 2.0.3.0

(.@@@@@) :: (f -> g) -> (a -> b -> c -> d -> e -> g -> h) -> a -> b -> c -> d -> e -> f -> h infixr 8 Source #

Since: 3.0.0.0

Monadic postcomposition

(<=*<) :: Monad m => (c -> m d) -> (a -> b -> m c) -> a -> b -> m d infixr 1 Source #

A monadic version of .*. Compare <=<.

As an example, one could use this to rewrite

\x y z -> f (g x y z) z

to

f <=*< g

Since: 1.5.2.0

(<=**<) :: Monad m => (d -> m e) -> (a -> b -> c -> m d) -> a -> b -> c -> m e infixr 1 Source #

The bleeding fish operator

Since: 1.5.2.0

(>=**>) :: Monad m => (a -> b -> c -> m d) -> (d -> m e) -> a -> b -> c -> m e infixr 1 Source #

Since: 1.5.2.0

(>=*>) :: Monad m => (a -> b -> m c) -> (c -> m d) -> a -> b -> m d infixr 1 Source #

Compare >=>.

Since: 1.5.2.0

Monadic precomposition

(<-=*<) :: Monad m => (b -> m c) -> (a -> c -> m d) -> a -> b -> m d infixr 1 Source #

Since: 1.5.2.0

(>-=*>) :: Monad m => (a -> c -> m d) -> (b -> m c) -> a -> b -> m d infixr 1 Source #

Since: 1.5.2.0

(<-=**<) :: Monad m => (c -> m d) -> (a -> b -> d -> m e) -> a -> b -> c -> m e infixr 1 Source #

Since: 1.5.2.0

(>-=**>) :: Monad m => (a -> b -> d -> m e) -> (c -> m d) -> a -> b -> c -> m e infixr 1 Source #

Since: 1.5.2.0

Between combinators

between :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d Source #

Can be used to rewrite

\g -> f . g . h

to

between f h

Since: 1.5.3.0

(~@~) :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d infixl 8 Source #

betweenM :: Monad m => (c -> m d) -> (a -> m b) -> (b -> m c) -> a -> m d Source #

(<~@~<) :: Monad m => (c -> m d) -> (a -> m b) -> (b -> m c) -> a -> m d infixl 8 Source #

Fancy function application

(-$) :: (a -> b -> c) -> b -> a -> c infixl 8 Source #

Backwards function application. This is an infix synonym for flip

Monadic helpers

bisequence' :: (Traversable t, Applicative f) => t (a -> b -> f c) -> a -> b -> t (f c) Source #

(.$) :: Monad m => m (m a) -> m a infixl 3 Source #

Infix version of join

As an example, one could use this to rewrite

between (char '"') (char '"')

to

between .$ (char '"')

Or

fromEither :: Either a a -> a
fromEither = either id id

to

fromEither :: Either a a -> a
fromEither = either .$ id

Since: 2.0.2.0

Monadic actions

axe :: (Traversable t, Applicative f) => t (a -> f ()) -> a -> f () Source #

biaxe :: (Traversable t, Applicative f) => t (a -> b -> f ()) -> a -> b -> f () Source #

Composition with lists of functions

thread :: Foldable t => t (a -> a) -> a -> a Source #

Since: 1.1.0.1

threadM :: (Monad m, Foldable t, Applicative m) => t (a -> m a) -> a -> m a Source #

Tuple helpers

both :: (a -> b) -> (a, a) -> (b, b) Source #

dup :: a -> (a, a) Source #

Since: 2.0.1.0

(+>) :: (a -> b) -> (a, a) -> (b, b) infixr 6 Source #

Infix synonym for both

Since: 3.0.0.0

J inspired

(&:) :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 Source #

Pronounced 'appose'. Synonym for on

Since: 3.0.0.0

Reëxports from base

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 #

Right-to-left composition of Kleisli arrows. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right composition of Kleisli arrows.

'(bs >=> cs) a' can be understood as the do expression

do b <- bs a
   cs b

(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #

A variant of <*> with the arguments reversed.

Using ApplicativeDo: 'as <**> fs' can be understood as the do expression

do a <- as
   f <- fs
   pure (f a)

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 #

Flipped version of <$>.

(<&>) = flip fmap

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

Since: base-4.11.0.0

fix :: (a -> a) -> a #

fix f is the least fixed point of the function f, i.e. the least defined x such that f x = x.

For example, we can write the factorial function using direct recursion as

>>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
120

This uses the fact that Haskell’s let introduces recursive bindings. We can rewrite this definition using fix,

>>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
120

Instead of making a recursive call, we introduce a dummy parameter rec; when used within fix, this parameter then refers to fix’s argument, hence the recursion is reintroduced.

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 #

on b u x y runs the binary function b on the results of applying unary function u to two arguments x and y. From the opposite perspective, it transforms two inputs and combines the outputs.

((+) `on` f) x y = f x + f y

Typical usage: sortBy (compare `on` fst).

Algebraic properties:

  • (*) `on` id = (*) -- (if (*) ∉ {⊥, const ⊥})
  • ((*) `on` f) `on` g = (*) `on` (f . g)
  • flip on f . flip on g = flip on (g . f)