Copyright | Nils Anders Danielsson 2006 Alexander Berntsen 2014 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
- Prelude re-exports
- Other combinators
Simple combinators working solely on and with functions.
Synopsis
- id :: a -> a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: forall (repa :: RuntimeRep) (repb :: RuntimeRep) (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
- (&) :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> (a -> b) -> b
- fix :: (a -> a) -> a
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- applyWhen :: Bool -> (a -> a) -> a -> a
Prelude re-exports
const x y
always evaluates to x
, ignoring its second argument.
>>>
const 42 "hello"
42
>>>
map (const 42) [0..3]
[42,42,42,42]
flip :: (a -> b -> c) -> b -> a -> c Source #
takes its (first) two arguments in the reverse order of flip
ff
.
>>>
flip (++) "hello" "world"
"worldhello"
($) :: 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
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)
Uses
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)
($)
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 the least fixed point of the function fix
ff
,
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
’s argument, hence
the recursion is reintroduced.
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 Source #