composition-prelude-1.5.0.6: Higher-order function combinators

Safe HaskellNone
LanguageHaskell98

Control.Composition

Contents

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
  • (-.) :: (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
  • (-$) :: (a -> b -> c) -> b -> a -> c
  • bisequence' :: (Traversable t, Monad m) => t (a -> b -> m c) -> a -> b -> t (m c)
  • axe :: (Traversable t, Monad m) => t (a -> m ()) -> a -> m ()
  • biaxe :: (Traversable t, Monad m) => t (a -> b -> m ()) -> a -> b -> m ()
  • thread :: [a -> a] -> a -> a
  • both :: (a -> b) -> (a, a) -> (b, b)
  • (<&>) :: Functor f => f a -> (a -> b) -> f b
  • (&) :: a -> (a -> b) -> 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 #

As an example:

λ:> ((*2) .* (+)) 1 3 4
16

(.**) :: (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 #

Precomposition

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

Backwards function composition

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

The Oedipus combinator

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

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

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

Fancy function application

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

Backwards function application

Monadic helpers

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

Monadic actions

axe :: (Traversable t, Monad m) => t (a -> m ()) -> a -> m () Source #

biaxe :: (Traversable t, Monad m) => t (a -> b -> m ()) -> a -> b -> m () Source #

Composition with lists of functions

thread :: [a -> a] -> a -> a Source #

Tuple helpers

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

Functor helpers

(<&>) :: 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

Reëxports from base

(&) :: 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

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' argument, hence the recursion is reintroduced.

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