base-4.19.1.0: Basic libraries
CopyrightNils Anders Danielsson 2006
Alexander Berntsen 2014
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Function

Contents

Description

Simple combinators working solely on and with functions.

Synopsis

Prelude re-exports

id :: a -> a Source #

Identity function.

id x = x

This function might seem useless at first glance, but it can be very useful in a higher order context.

Examples

Expand
>>> length $ filter id [True, True, False, True]
3
>>> Just (Just 3) >>= id
Just 3
>>> foldr id 0 [(^3), (*5), (+2)]
1000

const :: a -> b -> a Source #

const x y always evaluates to x, ignoring its second argument.

const x = \_ -> x

This function might seem useless at first glance, but it can be very useful in a higher order context.

Examples

Expand
>>> const 42 "hello"
42
>>> map (const 42) [0..3]
[42,42,42,42]

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

Right to left function composition.

(f . g) x = f (g x)
f . id = f = id . f

Examples

Expand
>>> map ((*2) . length) [[], [0, 1, 2], [0]]
[0,6,2]
>>> foldr (.) id [(+1), (*3), (^3)] 2
25
>>> let (...) = (.).(.) in ((*2)...(+)) 5 10
30

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

flip f takes its (first) two arguments in the reverse order of f.

flip f x y = f y x
flip . flip = id

Examples

Expand
>>> flip (++) "hello" "world"
"worldhello"
>>> let (.>) = flip (.) in (+1) .> show $ 5
"6"

($) :: forall (repa :: RuntimeRep) (repb :: RuntimeRep) (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b infixr 0 Source #

($) is the function application operator.

Applying ($) to a function f and an argument x gives the same result as applying f to x directly. The definition is akin to this:

($) :: (a -> b) -> a -> b
($) f x = f x

This is id specialized from a -> a to (a -> b) -> (a -> b) which by the associativity of (->) is the same as (a -> b) -> a -> b.

On the face of it, this may appear pointless! But it's actually one of the most useful and important operators in Haskell.

The order of operations is very different between ($) and normal function application. Normal function application has precedence 10 - higher than any operator - and associates to the left. So these two definitions are equivalent:

expr = min 5 1 + 5
expr = ((min 5) 1) + 5

($) has precedence 0 (the lowest) and associates to the right, so these are equivalent:

expr = min 5 $ 1 + 5
expr = (min 5) (1 + 5)

Examples

Expand

A common use cases of ($) is to avoid parentheses in complex expressions.

For example, instead of using nested parentheses in the following Haskell function:

-- | Sum numbers in a string: strSum "100  5 -7" == 98
strSum :: String -> Int
strSum s = sum (mapMaybe readMaybe (words s))

we can deploy the function application operator:

-- | Sum numbers in a string: strSum "100  5 -7" == 98
strSum :: String -> Int
strSum s = sum $ mapMaybe readMaybe $ words s

($) is also used as a section (a partially applied operator), in order to indicate that we wish to apply some yet-unspecified function to a given value. For example, to apply the argument 5 to a list of functions:

applyFive :: [Int]
applyFive = map ($ 5) [(+1), (2^)]
>>> [6, 32]

Technical Remark (Representation Polymorphism)

Expand

($) is fully representation-polymorphic. This allows it to also be used with arguments of unlifted and even unboxed kinds, such as unboxed integers:

fastMod :: Int -> Int -> Int
fastMod (I# x) (I# m) = I# $ remInt# x m

Other combinators

(&) :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> (a -> b) -> b infixl 1 Source #

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

This is a version of flip id, where id is specialized from a -> a to (a -> b) -> (a -> b) which by the associativity of (->) is (a -> b) -> a -> b. flipping this yields a -> (a -> b) -> b which is the type signature of &

Examples

Expand
>>> 5 & (+1) & show
"6"
>>> sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
3.1406380562059946

Since: base-4.8.0.0

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

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

When f is strict, this means that because, by the definition of strictness, f ⊥ = ⊥ and such the least defined fixed point of any strict function is .

Examples

Expand

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,

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.

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

Using fix, we can implement versions of repeat as fix . (:) and cycle as fix . (++)

>>> take 10 $ fix (0:)
[0,0,0,0,0,0,0,0,0,0]
>>> map (fix (\rec n -> if n < 2 then n else rec (n - 1) + rec (n - 2))) [1..10]
[1,1,2,3,5,8,13,21,34,55]

Implementation Details

Expand

The current implementation of fix uses structural sharing

fix f = let x = f x in x

A more straightforward but non-sharing version would look like

fix f = f (fix f)

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

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.

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

Examples

Expand
>>> sortBy (compare `on` length) [[0, 1, 2], [0, 1], [], [0]]
[[],[0],[0,1],[0,1,2]]
>>> ((+) `on` length) [1, 2, 3] [-1]
4
>>> ((,) `on` (*2)) 2 3
(4,6)

Algebraic properties

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

applyWhen :: Bool -> (a -> a) -> a -> a Source #

applyWhen applies a function to a value if a condition is true, otherwise, it returns the value unchanged.

It is equivalent to flip (bool id).

Examples

Expand
>>> map (\x -> applyWhen (odd x) (*2) x) [1..10]
[2,2,6,4,10,6,14,8,18,10]
>>> map (\x -> applyWhen (length x > 6) ((++ "...") . take 3) x) ["Hi!", "This is amazing", "Hope you're doing well today!", ":D"]
["Hi!","Thi...","Hop...",":D"]

Algebraic properties

Expand

Since: base-4.18.0.0