composition-prelude-1.5.0.1: Higher-order function combinators

Safe HaskellNone
LanguageHaskell98

Control.Composition

Contents

Synopsis

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 Source #

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 $.

Since: 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.

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

(*) `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)