Copyright | (c) 2013-2015, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | NoImplicitPrelude |
Safe Haskell | Safe |
Language | Haskell98 |
Implementation of lazy between
combinator and its variations. For
introductory documentation see module Data.Function.Between and
for strict versions import Data.Function.Between.Strict module.
Prior to version 0.10.0.0 functions defined in this module were directly in Data.Function.Between.
Module available since version 0.10.0.0.
- between :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d
- (~@~) :: (c -> d) -> (a -> b) -> (b -> c) -> a -> d
- (~@@~) :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d
- (^@~) :: (a -> c -> d) -> (a -> b) -> (b -> c) -> a -> d
- (~@@^) :: (a -> b) -> (a -> c -> d) -> (b -> c) -> a -> d
- (^@^) :: (a -> d -> e) -> (a -> b -> c) -> (c -> d) -> a -> b -> e
- (^@@^) :: (a -> b -> c) -> (a -> d -> e) -> (c -> d) -> a -> b -> e
- between2l :: (c -> d) -> (a -> b) -> (b -> b -> c) -> a -> a -> d
- between3l :: (c -> d) -> (a -> b) -> (b -> b -> b -> c) -> a -> a -> a -> d
- (<~@~>) :: (Functor f, Functor g) => (c -> d) -> (a -> b) -> (f b -> g c) -> f a -> g d
- (<~@@~>) :: (Functor f, Functor g) => (a -> b) -> (c -> d) -> (f b -> g c) -> f a -> g d
- (<~@~) :: Functor f => (c -> d) -> (a -> b) -> (b -> f c) -> a -> f d
- (~@@~>) :: Functor f => (a -> b) -> (c -> d) -> (b -> f c) -> a -> f d
- (~@~>) :: Functor f => (c -> d) -> (a -> b) -> (f b -> c) -> f a -> d
- (<~@@~) :: Functor f => (a -> b) -> (c -> d) -> (f b -> c) -> f a -> d
- (<^@~) :: Functor f => (a -> c -> d) -> (a -> b) -> (b -> f c) -> a -> f d
- (~@@^>) :: Functor f => (a -> b) -> (a -> c -> d) -> (b -> f c) -> a -> f d
- (<^@^>) :: (Functor f, Functor g) => (a -> d -> e) -> (a -> b -> c) -> (f c -> g d) -> a -> f b -> g e
- (<^@@^>) :: (Functor f, Functor g) => (a -> b -> c) -> (a -> d -> e) -> (f c -> g d) -> a -> f b -> g e
- (<^@^) :: Functor f => (a -> d -> e) -> (a -> b -> c) -> (c -> f d) -> a -> b -> f e
- (^@@^>) :: Functor f => (a -> b -> c) -> (a -> d -> e) -> (c -> f d) -> a -> b -> f e
- (^@^>) :: Functor f => (a -> d -> e) -> (a -> b -> c) -> (f c -> d) -> a -> f b -> e
- (<^@@^) :: Functor f => (a -> b -> c) -> (a -> d -> e) -> (f c -> d) -> a -> f b -> e
- inbetween :: a -> b -> (a -> b -> r) -> r
- (~$~) :: a -> b -> (a -> b -> r) -> r
- (~$$~) :: b -> a -> (a -> b -> r) -> r
- withIn :: ((a -> b -> r) -> r) -> (a -> b -> r) -> r
- withReIn :: ((b -> a -> r) -> r) -> (a -> b -> r) -> r
- type PreIso r s t a b = ((b -> t) -> (s -> a) -> r) -> r
- type PreIso' r s a = PreIso r s s a a
- preIso :: (s -> a) -> (b -> t) -> PreIso r s t a b
- preIso' :: (b -> t) -> (s -> a) -> PreIso r s t a b
- type PreLens r s t a b = ((b -> s -> t) -> (s -> a) -> r) -> r
- type PreLens' r s a = PreLens r s s a a
- preLens :: (s -> b -> t) -> (s -> a) -> PreLens r s t a b
- preLens' :: (s -> a) -> (s -> b -> t) -> PreLens r s t a b
- preIsoToPreLens :: PreIso r s t a b -> PreLens r s t a b
- le :: Functor f => PreLens ((a -> f b) -> s -> f t) s t a b -> (a -> f b) -> s -> f t
- type PrePrism r s t a b = ((b -> t) -> (s -> Either t a) -> r) -> r
- type PrePrism' r s a = PrePrism r s s a a
- prePrism :: (b -> t) -> (s -> Either t a) -> PrePrism r s t a b
- prePrism' :: (b -> s) -> (s -> Maybe a) -> PrePrism r s s a b
Between Function Combinator
Derived Combinators
(^@~) :: (a -> c -> d) -> (a -> b) -> (b -> c) -> a -> d infixl 8 Source
As ~@~
, but first function is also parametrised with a
, hence the name
^@~
. Character ^
indicates which argument is parametrised with
additional argument.
This function is defined as:
(f^@~
g) h a -> (f a~@~
g) h a
Fixity is left associative and set to value 8, which is one less then
fixity of function composition (.
).
(^@^) :: (a -> d -> e) -> (a -> b -> c) -> (c -> d) -> a -> b -> e infix 8 Source
Pass additional argument to first two function arguments.
This function is defined as:
(f^@^
g) h a b -> (f a~@~
g a) h b
See also ^@~
to note the difference, most importantly that ^@~
passes
the same argument to all its functional arguments. Function ^@~
can be
defined in terms of this one as:
(f^@~
g) h a = (f^@^
const
g) h a a
We can do it also the other way around and define ^@^
using ^@~
:
f^@^
g =curry
. (f .snd
^@~
uncurry
g)
Fixity is set to value 8, which is one less then of function composition
(.
).
between3l :: (c -> d) -> (a -> b) -> (b -> b -> b -> c) -> a -> a -> a -> d Source
Apply function g
to each argument of ternary function and f
to its
result. In suffix "3l" the number is equal to arity of the function it
accepts as a third argument and character "l" is for "left associative".
This function is defined as:
between3l
f g = ((f~@~
g)~@~
g)~@~
g
Alternatively it can be defined using between2l
:
between3l
f g =between2l
f g~@~
g
Lifted Combinators
Combinators based on ~@~
, ^@~
, ^@^
, and their flipped variants,
that use fmap
to lift one or more of its arguments to operate in
Functor
context.
(<~@~>) :: (Functor f, Functor g) => (c -> d) -> (a -> b) -> (f b -> g c) -> f a -> g d infix 8 Source
(<~@@~>) :: (Functor f, Functor g) => (a -> b) -> (c -> d) -> (f b -> g c) -> f a -> g d infix 8 Source
(<~@~) :: Functor f => (c -> d) -> (a -> b) -> (b -> f c) -> a -> f d infixl 8 Source
Apply fmap
to first argument of ~@~
. Dual to ~@~>
which applies
fmap
to second argument.
Defined as:
f<~@~
g =fmap
f~@~
g
This function allows us to define lenses mostly for pair of functions that form an isomorphism. See section Constructing Lenses for details.
Name of <~@~
simply says that we apply <$>
(fmap
) to
first (left) argument and then we apply ~@~
.
Fixity is left associative and set to value 8, which is one less then
of function composition (.
).
(~@@~>) :: Functor f => (a -> b) -> (c -> d) -> (b -> f c) -> a -> f d infixr 8 Source
Flipped variant of <~@~
.
This function allows us to define lenses mostly for pair of functions that form an isomorphism. See section Constructing Lenses for details.
Name of ~@@~>
simply says that we apply <$>
(fmap
) to
second (right) argument and then we apply ~@@~
.
Fixity is right associative and set to value 8, which is one less then
fixity of function composition (.
).
(~@~>) :: Functor f => (c -> d) -> (a -> b) -> (f b -> c) -> f a -> d infixl 8 Source
Apply fmap
to second argument of ~@~
. Dual to <~@~
which applies
fmap
to first argument.
Defined as:
f~@~>
g -> f~@~
fmap
g
Name of ~@~>
simply says that we apply <$>
(fmap
) to
second (right) argument and then we apply ~@~
.
Fixity is right associative and set to value 8, which is one less then
of function composition (.
).
(<^@~) :: Functor f => (a -> c -> d) -> (a -> b) -> (b -> f c) -> a -> f d infixl 8 Source
Convenience wrapper for: \f g ->
~' g@.fmap
. f '^
This function has the same functionality as function
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
Which is defined in lens package.
Only difference is that arguments of <^@~
are flipped. See also section
Constructing Lenses.
Name of <^@~
simply says that we apply <$>
(fmap
) to
first (left) arguments and then we apply ^@~
.
Fixity is left associative and set to value 8, which is one less then
of function composition (.
).
(~@@^>) :: Functor f => (a -> b) -> (a -> c -> d) -> (b -> f c) -> a -> f d infixl 8 Source
Flipped variant of ~@^>
.
This function has the same functionality as function
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
Which is defined in lens package. See also section Constructing Lenses.
Name of ~@^>
simply says that we apply <$>
(fmap
) to
second (right) arguments and then we apply ~@^>
.
Fixity is left associative and set to value 8, which is one less then
of function composition (.
).
(<^@^>) :: (Functor f, Functor g) => (a -> d -> e) -> (a -> b -> c) -> (f c -> g d) -> a -> f b -> g e infix 8 Source
(<^@@^>) :: (Functor f, Functor g) => (a -> b -> c) -> (a -> d -> e) -> (f c -> g d) -> a -> f b -> g e infix 8 Source
(<^@^) :: Functor f => (a -> d -> e) -> (a -> b -> c) -> (c -> f d) -> a -> b -> f e infix 8 Source
Convenience wrapper for: \f g ->
^' g@.fmap
. f '^
This function allows us to define generic lenses from gettern and setter. See section Constructing Lenses for details.
Name of <^@^
simply says that we apply <$>
(fmap
) to
first (left) arguments and then we apply ^@^
.
Fixity is left associative and set to value 8, which is one less then
of function composition (.
).
(^@@^>) :: Functor f => (a -> b -> c) -> (a -> d -> e) -> (c -> f d) -> a -> b -> f e infix 8 Source
Flipped variant of <^@^
.
This function allows us to define generic lenses from gettern and setter. See section Constructing Lenses for details.
Name of ^@@^>
simply says that we apply <$>
(fmap
) to
second (right) arguments and then we apply ^@@^
.
Fixity is set to value 8, which is one less then of function composition
(.
).
(<^@@^) :: Functor f => (a -> b -> c) -> (a -> d -> e) -> (f c -> d) -> a -> f b -> e infix 8 Source
In-Between Function Application Combinator
Captures common pattern of \f -> (a `f` b)
where a
and b
are
fixed parameters. It doesn't look impressive untill one thinks about a
and b
as functions.
Since version 0.11.0.0.
inbetween :: a -> b -> (a -> b -> r) -> r infix 8 Source
Prefix version of common pattern:
\f -> a `f` b
Where a
and b
are fixed parameters. There is also infix version named
~$~
. This function is defined as:
inbetween
a b f = f a b
Based on the above definition one can think of it as a variant function
application that deals with two arguments, where in example
$
only deals with one.
Since version 0.11.0.0.
(~$~) :: a -> b -> (a -> b -> r) -> r infix 8 Source
Infix version of common pattern:
\f -> a `f` b
Where a
and b
are fixed parameters. There is also prefix version named
inbetween
.
Since version 0.11.0.0.
(~$$~) :: b -> a -> (a -> b -> r) -> r infix 8 Source
Infix version of common pattern:
\f -> a `f` b -- Notice the order of 'a' and 'b'.
Since version 0.11.0.0.
withIn :: ((a -> b -> r) -> r) -> (a -> b -> r) -> r Source
Construct a function that encodes idiom:
\f -> a `f` b -- Notice the order of 'b' and 'a'.
Function inbetween
can be redefined in terms of withIn
as:
a `inbetween
` b =withIn
$
\f -> a `f` b
On one hand you can think of this function as a specialized id
function
and on the other as a function application $
. All the
following definitions work:
withIn
f g = f gwithIn
=id
withIn
= ($
)
Usage examples:
newtype Foo a = Foo a inFoo :: ((a -> Foo a) -> (Foo t -> t) -> r) -> r inFoo =withIn
$
\f -> Foo `f` \(Foo a) -> Foo
data Coords2D = Coords2D {_x :: Int, _y :: Int} inX :: ((Int -> Coords2D -> Coords2D) -> (Coords2D -> Int) -> r) -> r inX =withIn
$
\f -> (\b s -> s{_x = b}) `f` _x
Since version 0.11.0.0.
withReIn :: ((b -> a -> r) -> r) -> (a -> b -> r) -> r Source
Construct a function that encodes idiom:
\f -> b `f` a -- Notice the order of 'b' and 'a'.
Function ~$$~
can be redefined in terms of withReIn
as:
b~$$~
a =withReIn
$
\f -> b `f` a
As withIn
, but the function is flipped before applied. All of the
following definitions work:
withReIn
f g = f (flip
g)withReIn
= (.
flip
)
Usage examples:
newtype Foo a = Foo a inFoo :: ((a -> Foo a) -> (Foo t -> t) -> r) -> r inFoo =withReIn
$
\f -> (\(Foo a) -> Foo) `f` Foo
data Coords2D = Coords2D {_x :: Int, _y :: Int} inX :: ((Int -> Coords2D -> Coords2D) -> (Coords2D -> Int) -> r) -> r inX =withReIn
$
\f -> _x `f` \b s -> s{_x = b}
Since version 0.11.0.0.
Precursors to Iso, Lens and Prism
Since version 0.11.0.0.
PreIso
type PreIso r s t a b = ((b -> t) -> (s -> a) -> r) -> r Source
Family of types that can construct isomorphism between types.
Since version 0.11.0.0.
PreLens
type PreLens' r s a = PreLens r s s a a Source
A simple PreLens
, where we can not change the type of the information
we are focusing on. As a consequence neither the type of the container data
type can be changed.
Since version 0.11.0.0.
preIsoToPreLens :: PreIso r s t a b -> PreLens r s t a b Source
Convert PreIso
in to PreLens
by injecting const to a setter function.
preIsoToPreLens
aPreIso f = aPreIso$
\fbt fsa ->const
fbt `f` fsa
PrePrism
type PrePrism r s t a b = ((b -> t) -> (s -> Either t a) -> r) -> r Source
We can also get PrePrism
by specializing PreIso
:
PrePrism
r s t a b =PreIso
r s t (Either
t a) b
This fact is not surprising, since Prisms are actually a special case of isomorphism between two types.
Let's have a type s
, and we want to extract specific information out of
it, but that information may not be there. Because of the fact that the type
s
can be a sum type. Imagine e.g. standard Maybe
data type:
Maybe
a =Nothing
|Just
a
How do we create something that can extrat that information from a sum type,
and if necessary, also reconstructs that sum type. The answer is Prism,
which is defined as an isomorphism between that type s
and
where Either
t aa
is the information we want to extract and t
is the rest that we
don't care about.
You may have noticed, that definition of PrePrism
contains some type
variables that aren't mentioned in the above definition. The reason for this
is that, as with Lenses we may want to extract value of type a
, but when
constructing new data type we may want to change the type of that value in
to b
and therefore type s
may not fit, which is the reason why we have
type t
in there. Once again we can ilustrate this with Maybe
. Lets say
that we have a value of s =
, but if we change the type of Maybe
aa
in
to b
, and try to create Maybe
again, then it would have type
.Maybe
b
= t
Since version 0.11.0.0.
type PrePrism' r s a = PrePrism r s s a a Source
A simple PrePrism
, where we can not change the type of the information
we are focusing on. As a consequence neither the type of the container data
type can be changed.
If we define PrePrism'
in terms of PreIso'
then we have even better
ilustration of Prism concept in terms of isomorphism:
PrePrism'
r s a =PreIso'
r s (Either
t a)
Since version 0.11.0.0.
prePrism :: (b -> t) -> (s -> Either t a) -> PrePrism r s t a b Source
Constract a PrePrism
; this function is similar to Prism constructor
function from lens package:
prism :: (b -> t) -> (s -> Either
t a) -> Prism s t a b
Usage example:
{-# LANGUAGE LambdaCase #-} data Sum a b = A a | B b preA ::PrePrism
r (Sum a c) (Sum b c) a b preA =prePrism
A$
\case A a ->Right
a B b ->Left
(B b)
prePrism' :: (b -> s) -> (s -> Maybe a) -> PrePrism r s s a b Source
Simplified construction of PrePrism
, which can be used in following
situations:
- Constructing Prism for types isomorphic to
Maybe
or - when using
cast
operation, or similar, which either returns what you want orNothing
.
Alternative type signature of this function is also:
prePrism'
::PreIso
r s s (Maybe
a) b ->PrePrism
r s s a b