1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100
|
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Function
-- Copyright : Nils Anders Danielsson 2006
-- , Alexander Berntsen 2014
-- License : BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : portable
--
-- Simple combinators working solely on and with functions.
--
-----------------------------------------------------------------------------
module Data.Function
( -- * "Prelude" re-exports
id, const, (.), flip, ($)
-- * Other combinators
, (&)
, fix
, on
) where
import GHC.Base ( ($), (.), id, const, flip )
infixl 0 `on`
infixl 1 &
-- | @'fix' f@ is the least fixed point of the function @f@,
-- i.e. the least defined @x@ such that @f x = x@.
fix :: (a -> a) -> a
fix f = let x = f x in x
-- | @(*) \`on\` f = \\x y -> f x * f y@.
--
-- Typical usage: @'Data.List.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)@
-- Proofs (so that I don't have to edit the test-suite):
-- (*) `on` id
-- =
-- \x y -> id x * id y
-- =
-- \x y -> x * y
-- = { If (*) /= _|_ or const _|_. }
-- (*)
-- (*) `on` f `on` g
-- =
-- ((*) `on` f) `on` g
-- =
-- \x y -> ((*) `on` f) (g x) (g y)
-- =
-- \x y -> (\x y -> f x * f y) (g x) (g y)
-- =
-- \x y -> f (g x) * f (g y)
-- =
-- \x y -> (f . g) x * (f . g) y
-- =
-- (*) `on` (f . g)
-- =
-- (*) `on` f . g
-- flip on f . flip on g
-- =
-- (\h (*) -> (*) `on` h) f . (\h (*) -> (*) `on` h) g
-- =
-- (\(*) -> (*) `on` f) . (\(*) -> (*) `on` g)
-- =
-- \(*) -> (*) `on` g `on` f
-- = { See above. }
-- \(*) -> (*) `on` g . f
-- =
-- (\h (*) -> (*) `on` h) (g . f)
-- =
-- flip on (g . f)
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
(.*.) `on` f = \x y -> f x .*. f y
-- | '&' 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
(&) :: a -> (a -> b) -> b
x & f = f x
|