Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
A
is just any function Getter
s a(s -> a)
, which we've flipped
into continuation passing style, (a -> r) -> s -> r
and decorated
with Accessor
to obtain:
typeGetting
r s t a b = (a ->Accessor
r b) -> s ->Accessor
r t
If we restrict access to knowledge about the type r
and can work for
any b and t, we could get:
typeGetter
s a = forall r.Getting
r s s a a
But we actually hide the use of Accessor
behind a class Gettable
to error messages from type class resolution rather than at unification
time, where they are much uglier.
typeGetter
s a = forall f.Gettable
f => (a -> f a) -> s -> f s
Everything you can do with a function, you can do with a Getter
, but
note that because of the continuation passing style (.
) composes them
in the opposite order.
Since it is only a function, every Getter
obviously only retrieves a
single value for a given input.
- type Getter s a = forall f. Gettable f => (a -> f a) -> s -> f s
- type Getting r s t a b = (a -> Accessor r b) -> s -> Accessor r t
- to :: (s -> a) -> Getter s a
- (^.) :: s -> Getting a s t a b -> a
- (^$) :: Getting a s t a b -> s -> a
- (%) :: a -> (a -> b) -> b
- (^%) :: a -> (a -> b) -> b
- view :: Getting a s t a b -> s -> a
- views :: Getting r s t a b -> (a -> r) -> s -> r
- use :: MonadState s m => Getting a s t a b -> m a
- uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m r
- query :: MonadReader s m => Getting a s t a b -> m a
- queries :: MonadReader s m => Getting r s t a b -> (a -> r) -> m r
- newtype ReifiedGetter s a = ReifyGetter {
- reflectGetter :: Getter s a
- class Functor f => Gettable f
- data Accessor r a
Getters
type Getter s a = forall f. Gettable f => (a -> f a) -> s -> f sSource
A Getter
describes how to retrieve a single value in a way that can be
composed with other lens-like constructions.
Unlike a Lens
a Getter
is read-only. Since a Getter
cannot be used to write back there are no lens laws that can be applied to
it. In fact, it is isomorphic to an arbitrary function from (a -> s)
.
Moreover, a Getter
can be used directly as a Fold
,
since it just ignores the Applicative
.
type Getting r s t a b = (a -> Accessor r b) -> s -> Accessor r tSource
Most Getter
combinators are able to be used with both a Getter
or a
Fold
in limited situations, to do so, they need to be
monomorphic in what we are going to extract with Const
. To be compatible
with Lens
, Traversal
and
Iso
we also restricted choices of the irrelevant t
and
b
parameters.
If a function accepts a
, then when Getting
r s t a br
is a Monoid
, then
you can pass a Fold
(or
Traversal
), otherwise you can only pass this a
Getter
or Lens
.
Building Getters
Combinators for Getters and Folds
(^.) :: s -> Getting a s t a b -> aSource
View the value pointed to by a Getter
or Lens
or the
result of folding over all the results of a Fold
or
Traversal
that points at a monoidal values.
This is the same operation as view
with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.
)
>>>
("hello","world")^._2
"world"
>>>
import Data.Complex
>>>
((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.
) :: s ->Getter
s a -> a (^.
) ::Monoid
m => s ->Fold
s m -> m (^.
) :: s ->Simple
Iso
s a -> a (^.
) :: s ->Simple
Lens
s a -> a (^.
) ::Monoid
m => s ->Simple
Traversal
s m -> m
(^$) :: Getting a s t a b -> s -> aSource
View the value pointed to by a Getter
, Iso
or
Lens
or the result of folding over all the results of a
Fold
or Traversal
that points
at a monoidal values.
This is the same operation as view
, only infix.
to
f^$
x = f x
>>>
_2 ^$ (1, "hello")
"hello"
(^$
) ::Getter
s a -> s -> a (^$
) ::Monoid
m =>Fold
s m -> s -> m (^$
) ::Simple
Iso
s a -> s -> a (^$
) ::Simple
Lens
s a -> s -> a (^$
) ::Monoid
m =>Simple
Traversal
s m -> s -> m
(%) :: a -> (a -> b) -> bSource
Passes the result of the left side to the function on the right side (forward pipe operator).
This is the flipped version of ($
), which is more common in languages like F# as (|>
) where it is needed
for inference. Here it is supplied for notational convenience and given a precedence that allows it
to be nested inside uses of ($
).
>>>
"hello" % length % succ
6
view :: Getting a s t a b -> s -> aSource
View the value pointed to by a Getter
, Iso
or
Lens
or the result of folding over all the results of a
Fold
or Traversal
that points
at a monoidal values.
view
.to
=id
>>>
view _2 (1,"hello")
"hello"
>>>
view (to succ) 5
6
>>>
view (_2._1) ("hello",("world","!!!"))
"world"
It may be useful to think of view
as having one of these more restrictive
signatures:
view
::Getter
s a -> s -> aview
::Monoid
m =>Fold
s m -> s -> mview
::Simple
Iso
s a -> s -> aview
::Simple
Lens
s a -> s -> aview
::Monoid
m =>Simple
Traversal
s m -> s -> m
views :: Getting r s t a b -> (a -> r) -> s -> rSource
View the value of a Getter
, Iso
,
Lens
or the result of folding over the result of mapping
the targets of a Fold
or
Traversal
.
It may be useful to think of views
as having these more restrictive
signatures:
views
l f =view
(l.
to
f)
>>>
views _2 length (1,"hello")
5
views
::Getter
s a -> (a -> r) -> s -> rviews
::Monoid
m =>Fold
s a -> (a -> m) -> s -> mviews
::Simple
Iso
s a -> (a -> r) -> s -> rviews
::Simple
Lens
s a -> (a -> r) -> s -> rviews
::Monoid
m =>Simple
Traversal
s a -> (a -> m) -> s -> m
use :: MonadState s m => Getting a s t a b -> m aSource
Use the target of a Lens
, Iso
, or
Getter
in the current state, or use a summary of a
Fold
or Traversal
that points
to a monoidal value.
use
::MonadState
s m =>Getter
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Fold
s r -> m ruse
::MonadState
s m =>Simple
Iso
s a -> m ause
::MonadState
s m =>Simple
Lens
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Simple
Traversal
s r -> m r
uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m rSource
Use the target of a Lens
, Iso
or
Getter
in the current state, or use a summary of a
Fold
or Traversal
that
points to a monoidal value.
uses
::MonadState
s m =>Getter
s a -> (a -> r) -> m ruses
:: (MonadState
s m,Monoid
r) =>Fold
s a -> (a -> r) -> m ruses
::MonadState
s m =>Simple
Lens
s a -> (a -> r) -> m ruses
::MonadState
s m =>Simple
Iso
s a -> (a -> r) -> m ruses
:: (MonadState
s m,Monoid
r) =>Simple
Traversal
s a -> (a -> r) -> m r
query :: MonadReader s m => Getting a s t a b -> m aSource
Query the target of a Lens
, Iso
or
Getter
in the current state, or use a summary of a
Fold
or Traversal
that points
to a monoidal value.
query
::MonadReader
s m =>Getter
s a -> m aquery
:: (MonadReader
s m,Monoid
a) =>Fold
s a -> m aquery
::MonadReader
s m =>Simple
Iso
s a -> m aquery
::MonadReader
s m =>Simple
Lens
s a -> m aquery
:: (MonadReader
s m,Monoid
a) =>Simple
Traversal
s a -> m a
queries :: MonadReader s m => Getting r s t a b -> (a -> r) -> m rSource
Use the target of a Lens
, Iso
or
Getter
in the current state, or use a summary of a
Fold
or Traversal
that points
to a monoidal value.
queries
::MonadReader
s m =>Getter
s a -> (a -> r) -> m rqueries
:: (MonadReader
s m,Monoid
a) =>Fold
s a -> (a -> r) -> m rqueries
::MonadReader
s m =>Simple
Iso
s a -> (a -> r) -> m rqueries
::MonadReader
s m =>Simple
Lens
s a -> (a -> r) -> m rqueries
:: (MonadReader
s m,Monoid
a) =>Simple
Traversal
s a -> (a -> r) -> m r
Storing Getters
newtype ReifiedGetter s a Source
Useful for storing getters in containers.
ReifyGetter | |
|
class Functor f => Gettable f Source
Generalizing Const
so we can apply simple Applicative
transformations to it and so we can get nicer error messages
A Gettable
Functor
ignores its argument, which it carries solely as a
phantom type parameter.
To ensure this, an instance of Gettable
is required to satisfy:
id
=fmap
f =coerce
Functor (Const r) => Gettable (Const r) | |
(Functor (Backwards f), Gettable f) => Gettable (Backwards f) | |
Functor (Accessor r) => Gettable (Accessor r) | |
(Functor (Indexing f), Gettable f) => Gettable (Indexing f) | |
(Functor (Compose f g), Functor f, Gettable g) => Gettable (Compose f g) | |
Functor (Effect m r) => Gettable (Effect m r) | |
Functor (EffectRWS w st m s) => Gettable (EffectRWS w st m s) |
Used instead of Const
to report
No instance of (Settable
Accessor
)
when the user attempts to misuse a Setter
as a
Getter
, rather than a monolithic unification error.
(Monad Identity, Gettable (Accessor r)) => Effective Identity r (Accessor r) | |
Functor (Accessor r) | |
(Functor (Accessor r), Monoid r) => Applicative (Accessor r) | |
Functor (Accessor r) => Gettable (Accessor r) | |
(MonadReader b ((->) b), MonadReader a ((->) a)) => Magnify ((->) b) ((->) a) Accessor b a |
|