composition-prelude-1.1.0.0: Higher-order function combinators

Safe HaskellSafe
LanguageHaskell2010

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

Tuple helpers

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

Functor helpers

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

Reexports from Control.Arrow

(&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') infixr 3 #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

(***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c') infixr 3 #

Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

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.

Reexports from Control.Monad

join :: Monad m => m (m a) -> m a #

The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

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

Same as >>=, but with the arguments interchanged.

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

Left-to-right Kleisli composition of monads.

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

Right-to-left Kleisli composition of monads. (>=>), 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

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

when :: Applicative f => Bool -> f () -> f () #

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f () #

The reverse of when.

Reexports 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)

ap :: Monad m => m (a -> b) -> m a -> m b #

In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.

      return f `ap` x1 `ap` ... `ap` xn

is equivalent to

      liftMn f x1 x2 ... xn