pointless-fun-1.1.0.8: Some common point-free combinators.
CopyrightCopyright (c) 2009--2021 wren gayle romano
LicenseBSD
Maintainerwren@cpan.org
Stabilityprovisional
PortabilityHaskell98
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Function.Pointless

Description

Pointless fun :)

Synopsis
  • ($::) :: (a -> b) -> ((a -> b) -> c -> d) -> c -> d
  • (~>) :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d
  • (!~>) :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d
  • (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
  • (.^) :: (a -> c -> d) -> (b -> c) -> a -> b -> d
  • (.!) :: (b -> c) -> (a -> b) -> a -> c

Multicomposition

Based on http://matt.immute.net/content/pointless-fun. These combinators allow you to easily modify the types of a many-argument function with syntax that looks like giving type signatures. For example,

foo    :: A -> B -> C

albert :: X -> A
beth   :: Y -> B
carol  :: C -> Z

bar :: X -> Y -> Z
bar = foo $:: albert ~> beth ~> carol

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

Lift a function for multicomposition. This is like the :: of a type signature.

(~>) :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d infixr 2 Source #

Multicompose a function on the appropriate argument. This is like the -> arrows in a type signature.

(!~>) :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d infixr 2 Source #

Multicompose a function on the appropriate argument, calling the left function eagerly. That is, the resulting function will be strict in a if the left argument is strict in a (assuming the final function of the multicomposition, the one applied to the return value, is also strict).

Composition for arity 2

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

Binary composition: pass two args to the right argument before composing.

(f .: g) x y = f (g x y)

or,

f .: g = curry (f . uncurry g)

This is the same as the common idiom (f .) . g but more easily extended to multiple uses, due to the fixity declaration.

(.^) :: (a -> c -> d) -> (b -> c) -> a -> b -> d infix 9 Source #

Secondary composition: compose the right argument on the second arg of the left argument.

(f .^ g) x y = f x (g y)

Strict composition

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

Function composition which calls the right-hand function eagerly; i.e., making the left-hand function strict in its first argument.

(f .! g) x = f $! g x

This defines the composition for the sub-category of strict Haskell functions. If the Functor class were parameterized by the domain and codomain categories (e.g., a regular Functor f would be CFunctor (->) (->) f instead) then this would allow us to define functors CFunctor (->) (!->) f where fmap f . fmap g = fmap (f .! g).